Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b253013e by Georgios Karachalias at 2025-11-07T17:21:57-05:00
Remove the `CoreBindings` constructor from `LinkablePart`
Adjust HscRecompStatus to disallow unhydrated WholeCoreBindings
from being passed as input to getLinkDeps (which would previously
panic in this case).
Fixes #26497
- - - - -
ac7b737e by Sylvain Henry at 2025-11-07T17:22:51-05:00
Testsuite: pass ext-interp test way (#26552)
Note that some tests are still marked as broken with the ext-interp way
(see #26552 and #14335)
- - - - -
04abb6bf by Vladislav Zavialov at 2025-11-08T08:52:11-05:00
Comments only in GHC.Parser.PostProcess.Haddock
Remove outdated Note [Register keyword location], as the issue it describes
was addressed by commit 05eb50dff2fcc78d025e77b9418ddb369db49b9f.
- - - - -
dc1cb4be by ARATA Mizuki at 2025-11-08T08:52:23-05:00
Fix the order of spill/reload instructions
The AArch64 NCG could emit multiple instructions for a single spill/reload,
but their order was not consistent between the definition and a use.
Fixes #26537
Co-authored-by: sheaf
- - - - -
19 changed files:
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Unit/Home/ModInfo.hs
- compiler/GHC/Unit/Module/Status.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- libraries/base/tests/all.T
- testsuite/driver/testlib.py
- + testsuite/tests/codeGen/should_run/T26537.hs
- + testsuite/tests/codeGen/should_run/T26537.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/driver/T20696/all.T
- testsuite/tests/driver/fat-iface/all.T
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/splice-imports/all.T
Changes:
=====================================
compiler/GHC/CmmToAsm/Reg/Liveness.hs
=====================================
@@ -48,6 +48,7 @@ import GHC.Cmm
import GHC.CmmToAsm.Reg.Target
import GHC.Data.Graph.Directed
+import GHC.Data.OrdList
import GHC.Utils.Monad
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -562,30 +563,26 @@ stripLiveBlock config (BasicBlock i lis)
= BasicBlock i instrs'
where (instrs', _)
- = runState (spillNat [] lis) 0
+ = runState (spillNat nilOL lis) 0
- -- spillNat :: [instr] -> [LiveInstr instr] -> State Int [instr]
- spillNat :: Instruction instr => [instr] -> [LiveInstr instr] -> State Int [instr]
+ spillNat :: Instruction instr => OrdList instr -> [LiveInstr instr] -> State Int [instr]
spillNat acc []
- = return (reverse acc)
+ = return (fromOL acc)
- -- The SPILL/RELOAD cases do not appear to be exercised by our codegens
- --
spillNat acc (LiveInstr (SPILL reg slot) _ : instrs)
= do delta <- get
- spillNat (mkSpillInstr config reg delta slot ++ acc) instrs
+ spillNat (acc `appOL` toOL (mkSpillInstr config reg delta slot)) instrs
spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs)
= do delta <- get
- spillNat (mkLoadInstr config reg delta slot ++ acc) instrs
+ spillNat (acc `appOL` toOL (mkLoadInstr config reg delta slot)) instrs
spillNat acc (LiveInstr (Instr instr) _ : instrs)
| Just i <- takeDeltaInstr instr
= do put i
spillNat acc instrs
-
- spillNat acc (LiveInstr (Instr instr) _ : instrs)
- = spillNat (instr : acc) instrs
+ | otherwise
+ = spillNat (acc `snocOL` instr) instrs
-- | Erase Delta instructions.
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -277,6 +277,7 @@ import Data.Data hiding (Fixity, TyCon)
import Data.Functor ((<&>))
import Data.List ( nub, isPrefixOf, partition )
import qualified Data.List.NonEmpty as NE
+import Data.Traversable (for)
import Control.Monad
import Data.IORef
import System.FilePath as FilePath
@@ -850,11 +851,11 @@ hscRecompStatus
if | not (backendGeneratesCode (backend lcl_dflags)) -> do
-- No need for a linkable, we're good to go
msg UpToDate
- return $ HscUpToDate checked_iface emptyHomeModInfoLinkable
+ return $ HscUpToDate checked_iface emptyRecompLinkables
| not (backendGeneratesCodeForHsBoot (backend lcl_dflags))
, IsBoot <- isBootSummary mod_summary -> do
msg UpToDate
- return $ HscUpToDate checked_iface emptyHomeModInfoLinkable
+ return $ HscUpToDate checked_iface emptyRecompLinkables
-- Always recompile with the JS backend when TH is enabled until
-- #23013 is fixed.
@@ -883,7 +884,7 @@ hscRecompStatus
let just_o = justObjects <$> obj_linkable
bytecode_or_object_code
- | gopt Opt_WriteByteCode lcl_dflags = justBytecode <$> definitely_bc
+ | gopt Opt_WriteByteCode lcl_dflags = justBytecode . Left <$> definitely_bc
| otherwise = (justBytecode <$> maybe_bc) `choose` just_o
@@ -900,13 +901,13 @@ hscRecompStatus
definitely_bc = bc_obj_linkable `prefer` bc_in_memory_linkable
-- If not -fwrite-byte-code, then we could use core bindings or object code if that's available.
- maybe_bc = bc_in_memory_linkable `choose`
- bc_obj_linkable `choose`
- bc_core_linkable
+ maybe_bc = (Left <$> bc_in_memory_linkable) `choose`
+ (Left <$> bc_obj_linkable) `choose`
+ (Right <$> bc_core_linkable)
bc_result = if gopt Opt_WriteByteCode lcl_dflags
-- If the byte-code artifact needs to be produced, then we certainly need bytecode.
- then definitely_bc
+ then Left <$> definitely_bc
else maybe_bc
trace_if (hsc_logger hsc_env)
@@ -1021,14 +1022,13 @@ checkByteCodeFromObject hsc_env mod_sum = do
-- | Attempt to load bytecode from whole core bindings in the interface if they exist.
-- This is a legacy code-path, these days it should be preferred to use the bytecode object linkable.
-checkByteCodeFromIfaceCoreBindings :: HscEnv -> ModIface -> ModSummary -> IO (MaybeValidated Linkable)
+checkByteCodeFromIfaceCoreBindings :: HscEnv -> ModIface -> ModSummary -> IO (MaybeValidated WholeCoreBindingsLinkable)
checkByteCodeFromIfaceCoreBindings _hsc_env iface mod_sum = do
let
this_mod = ms_mod mod_sum
if_date = fromJust $ ms_iface_date mod_sum
case iface_core_bindings iface (ms_location mod_sum) of
- Just fi -> do
- return (UpToDateItem (Linkable if_date this_mod (NE.singleton (CoreBindings fi))))
+ Just fi -> return $ UpToDateItem (Linkable if_date this_mod fi)
_ -> return $ outOfDateItemBecause MissingBytecode Nothing
--------------------------------------------------------------
@@ -1142,20 +1142,22 @@ initWholeCoreBindings ::
HscEnv ->
ModIface ->
ModDetails ->
- Linkable ->
- IO Linkable
-initWholeCoreBindings hsc_env iface details (Linkable utc_time this_mod uls) = do
- Linkable utc_time this_mod <$> mapM (go hsc_env) uls
+ RecompLinkables ->
+ IO HomeModLinkable
+initWholeCoreBindings hsc_env iface details (RecompLinkables bc o) = do
+ bc' <- go bc
+ pure $ HomeModLinkable bc' o
where
- go hsc_env' = \case
- CoreBindings wcb -> do
+ type_env = md_types details
+
+ go :: RecompBytecodeLinkable -> IO (Maybe Linkable)
+ go (NormalLinkable l) = pure l
+ go (WholeCoreBindingsLinkable wcbl) =
+ fmap Just $ for wcbl $ \wcb -> do
add_iface_to_hpt iface details hsc_env
bco <- unsafeInterleaveIO $
- compileWholeCoreBindings hsc_env' type_env wcb
- pure (DotGBC bco)
- l -> pure l
-
- type_env = md_types details
+ compileWholeCoreBindings hsc_env type_env wcb
+ pure $ NE.singleton (DotGBC bco)
-- | Hydrate interface Core bindings and compile them to bytecode.
--
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -109,6 +109,7 @@ import GHC.Unit.Env
import GHC.Unit.Finder
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.ModIface
+import GHC.Unit.Module.Status
import GHC.Unit.Home.ModInfo
import GHC.Unit.Home.PackageTable
@@ -249,8 +250,8 @@ compileOne' mHscMessage
(iface, linkable) <- runPipeline (hsc_hooks plugin_hsc_env) pipeline
-- See Note [ModDetails and --make mode]
details <- initModDetails plugin_hsc_env iface
- linkable' <- traverse (initWholeCoreBindings plugin_hsc_env iface details) (homeMod_bytecode linkable)
- return $! HomeModInfo iface details (linkable { homeMod_bytecode = linkable' })
+ linkable' <- initWholeCoreBindings plugin_hsc_env iface details linkable
+ return $! HomeModInfo iface details linkable'
where lcl_dflags = ms_hspp_opts summary
location = ms_location summary
@@ -759,7 +760,7 @@ preprocessPipeline pipe_env hsc_env input_fn = do
$ phaseIfFlag hsc_env flag def action
-- | The complete compilation pipeline, from start to finish
-fullPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> HscSource -> m (ModIface, HomeModLinkable)
+fullPipeline :: P m => PipeEnv -> HscEnv -> FilePath -> HscSource -> m (ModIface, RecompLinkables)
fullPipeline pipe_env hsc_env pp_fn src_flavour = do
(dflags, input_fn) <- preprocessPipeline pipe_env hsc_env pp_fn
let hsc_env' = hscSetFlags dflags hsc_env
@@ -768,7 +769,7 @@ fullPipeline pipe_env hsc_env pp_fn src_flavour = do
hscPipeline pipe_env (hsc_env_with_plugins, mod_sum, hsc_recomp_status)
-- | Everything after preprocess
-hscPipeline :: P m => PipeEnv -> ((HscEnv, ModSummary, HscRecompStatus)) -> m (ModIface, HomeModLinkable)
+hscPipeline :: P m => PipeEnv -> (HscEnv, ModSummary, HscRecompStatus) -> m (ModIface, RecompLinkables)
hscPipeline pipe_env (hsc_env_with_plugins, mod_sum, hsc_recomp_status) = do
case hsc_recomp_status of
HscUpToDate iface mb_linkable -> return (iface, mb_linkable)
@@ -777,7 +778,7 @@ hscPipeline pipe_env (hsc_env_with_plugins, mod_sum, hsc_recomp_status) = do
hscBackendAction <- use (T_HscPostTc hsc_env_with_plugins mod_sum tc_result warnings mb_old_hash )
hscBackendPipeline pipe_env hsc_env_with_plugins mod_sum hscBackendAction
-hscBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, HomeModLinkable)
+hscBackendPipeline :: P m => PipeEnv -> HscEnv -> ModSummary -> HscBackendAction -> m (ModIface, RecompLinkables)
hscBackendPipeline pipe_env hsc_env mod_sum result =
if backendGeneratesCode (backend (hsc_dflags hsc_env)) then
do
@@ -796,15 +797,15 @@ hscBackendPipeline pipe_env hsc_env mod_sum result =
return res
else
case result of
- HscUpdate iface -> return (iface, emptyHomeModInfoLinkable)
- HscRecomp {} -> (,) <$> liftIO (mkFullIface hsc_env (hscs_partial_iface result) Nothing Nothing NoStubs []) <*> pure emptyHomeModInfoLinkable
+ HscUpdate iface -> return (iface, emptyRecompLinkables)
+ HscRecomp {} -> (,) <$> liftIO (mkFullIface hsc_env (hscs_partial_iface result) Nothing Nothing NoStubs []) <*> pure emptyRecompLinkables
hscGenBackendPipeline :: P m
=> PipeEnv
-> HscEnv
-> ModSummary
-> HscBackendAction
- -> m (ModIface, HomeModLinkable)
+ -> m (ModIface, RecompLinkables)
hscGenBackendPipeline pipe_env hsc_env mod_sum result = do
let mod_name = moduleName (ms_mod mod_sum)
src_flavour = (ms_hsc_src mod_sum)
@@ -812,7 +813,7 @@ hscGenBackendPipeline pipe_env hsc_env mod_sum result = do
(fos, miface, mlinkable, o_file) <- use (T_HscBackend pipe_env hsc_env mod_name src_flavour location result)
final_fp <- hscPostBackendPipeline pipe_env hsc_env (ms_hsc_src mod_sum) (backend (hsc_dflags hsc_env)) (Just location) o_file
final_linkable <-
- case final_fp of
+ safeCastHomeModLinkable <$> case final_fp of
-- No object file produced, bytecode or NoBackend
Nothing -> return mlinkable
Just o_fp -> do
@@ -936,7 +937,7 @@ pipelineStart pipe_env hsc_env input_fn mb_phase =
as :: P m => Bool -> m (Maybe FilePath)
as use_cpp = asPipeline use_cpp pipe_env hsc_env Nothing input_fn
- objFromLinkable (_, homeMod_object -> Just (Linkable _ _ (DotO lnk _ :| []))) = Just lnk
+ objFromLinkable (_, recompLinkables_object -> Just (Linkable _ _ (DotO lnk _ :| []))) = Just lnk
objFromLinkable _ = Nothing
fromPhase :: P m => Phase -> m (Maybe FilePath)
=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -33,7 +33,6 @@ import GHC.Utils.Error
import GHC.Unit.Env
import GHC.Unit.Finder
import GHC.Unit.Module
-import GHC.Unit.Module.WholeCoreBindings
import GHC.Unit.Home.ModInfo
import GHC.Iface.Errors.Types
@@ -206,10 +205,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
DotO file ForeignObject -> pure (DotO file ForeignObject)
DotA fp -> panic ("adjust_ul DotA " ++ show fp)
DotDLL fp -> panic ("adjust_ul DotDLL " ++ show fp)
- DotGBC {} -> pure part
- CoreBindings WholeCoreBindings {wcb_module} ->
- pprPanic "Unhydrated core bindings" (ppr wcb_module)
-
+ DotGBC {} -> pure part
{-
=====================================
compiler/GHC/Linker/Types.hs
=====================================
@@ -1,5 +1,6 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE DeriveTraversable #-}
-----------------------------------------------------------------------------
--
@@ -30,7 +31,9 @@ module GHC.Linker.Types
, PkgsLoaded
-- * Linkable
- , Linkable(..)
+ , Linkable
+ , WholeCoreBindingsLinkable
+ , LinkableWith(..)
, mkModuleByteCodeLinkable
, LinkablePart(..)
, LinkableObjectSort (..)
@@ -254,7 +257,7 @@ instance Outputable LoadedPkgInfo where
-- | Information we can use to dynamically link modules into the compiler
-data Linkable = Linkable
+data LinkableWith parts = Linkable
{ linkableTime :: !UTCTime
-- ^ Time at which this linkable was built
-- (i.e. when the bytecodes were produced,
@@ -263,9 +266,13 @@ data Linkable = Linkable
, linkableModule :: !Module
-- ^ The linkable module itself
- , linkableParts :: NonEmpty LinkablePart
+ , linkableParts :: parts
-- ^ Files and chunks of code to link.
- }
+ } deriving (Functor, Traversable, Foldable)
+
+type Linkable = LinkableWith (NonEmpty LinkablePart)
+
+type WholeCoreBindingsLinkable = LinkableWith WholeCoreBindings
type LinkableSet = ModuleEnv Linkable
@@ -282,7 +289,7 @@ unionLinkableSet = plusModuleEnv_C go
| linkableTime l1 > linkableTime l2 = l1
| otherwise = l2
-instance Outputable Linkable where
+instance Outputable a => Outputable (LinkableWith a) where
ppr (Linkable when_made mod parts)
= (text "Linkable" <+> parens (text (show when_made)) <+> ppr mod)
$$ nest 3 (ppr parts)
@@ -318,11 +325,6 @@ data LinkablePart
| DotDLL FilePath
-- ^ Dynamically linked library file (.so, .dll, .dylib)
- | CoreBindings WholeCoreBindings
- -- ^ Serialised core which we can turn into BCOs (or object files), or
- -- used by some other backend See Note [Interface Files with Core
- -- Definitions]
-
| DotGBC ModuleByteCode
-- ^ A byte-code object, lives only in memory.
@@ -350,7 +352,6 @@ instance Outputable LinkablePart where
ppr (DotA path) = text "DotA" <+> text path
ppr (DotDLL path) = text "DotDLL" <+> text path
ppr (DotGBC bco) = text "DotGBC" <+> ppr bco
- ppr (CoreBindings {}) = text "CoreBindings"
-- | Return true if the linkable only consists of native code (no BCO)
linkableIsNativeCodeOnly :: Linkable -> Bool
@@ -391,7 +392,6 @@ isNativeCode = \case
DotA {} -> True
DotDLL {} -> True
DotGBC {} -> False
- CoreBindings {} -> False
-- | Is the part a native library? (.so/.dll)
isNativeLib :: LinkablePart -> Bool
@@ -400,7 +400,6 @@ isNativeLib = \case
DotA {} -> True
DotDLL {} -> True
DotGBC {} -> False
- CoreBindings {} -> False
-- | Get the FilePath of linkable part (if applicable)
linkablePartPath :: LinkablePart -> Maybe FilePath
@@ -408,7 +407,6 @@ linkablePartPath = \case
DotO fn _ -> Just fn
DotA fn -> Just fn
DotDLL fn -> Just fn
- CoreBindings {} -> Nothing
DotGBC {} -> Nothing
-- | Return the paths of all object code files (.o, .a, .so) contained in this
@@ -418,7 +416,6 @@ linkablePartNativePaths = \case
DotO fn _ -> [fn]
DotA fn -> [fn]
DotDLL fn -> [fn]
- CoreBindings {} -> []
DotGBC {} -> []
-- | Return the paths of all object files (.o) contained in this 'LinkablePart'.
@@ -427,7 +424,6 @@ linkablePartObjectPaths = \case
DotO fn _ -> [fn]
DotA _ -> []
DotDLL _ -> []
- CoreBindings {} -> []
DotGBC bco -> gbc_foreign_files bco
-- | Retrieve the compiled byte-code from the linkable part.
@@ -444,12 +440,11 @@ linkableFilter f linkable = do
Just linkable {linkableParts = new}
linkablePartNative :: LinkablePart -> [LinkablePart]
-linkablePartNative = \case
- u@DotO {} -> [u]
- u@DotA {} -> [u]
- u@DotDLL {} -> [u]
+linkablePartNative u = case u of
+ DotO {} -> [u]
+ DotA {} -> [u]
+ DotDLL {} -> [u]
DotGBC bco -> [DotO f ForeignObject | f <- gbc_foreign_files bco]
- _ -> []
linkablePartByteCode :: LinkablePart -> [LinkablePart]
linkablePartByteCode = \case
=====================================
compiler/GHC/Parser/PostProcess/Haddock.hs
=====================================
@@ -1115,7 +1115,6 @@ runHdkA (HdkA _ m) = unHdkM m mempty
-- To take it into account, we must register its location using registerLocHdkA
-- or registerHdkA.
--
--- See Note [Register keyword location].
-- See Note [Adding Haddock comments to the syntax tree].
registerLocHdkA :: SrcSpan -> HdkA ()
registerLocHdkA l = HdkA (getBufSpan l) (pure ())
@@ -1544,18 +1543,3 @@ that GHC could parse successfully:
This declaration was accepted by ghc but rejected by ghc -haddock.
-}
-
-{- Note [Register keyword location]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-At the moment, 'addHaddock' erroneously associates some comments with
-constructs that are separated by a keyword. For example:
-
- data Foo -- | Comment for MkFoo
- where MkFoo :: Foo
-
-We could use EPA (exactprint annotations) to fix this, but not without
-modification. For example, EpaLocation contains RealSrcSpan but not BufSpan.
-Also, the fix would be more straightforward after #19623.
-
-For examples, see tests/haddock/should_compile_flag_haddock/T17544_kw.hs
--}
=====================================
compiler/GHC/Unit/Home/ModInfo.hs
=====================================
@@ -3,13 +3,10 @@
module GHC.Unit.Home.ModInfo
(
HomeModInfo (..)
- , HomeModLinkable(..)
+ , HomeModLinkable (..)
, homeModInfoObject
, homeModInfoByteCode
, emptyHomeModInfoLinkable
- , justBytecode
- , justObjects
- , bytecodeAndObjects
)
where
@@ -18,11 +15,9 @@ import GHC.Prelude
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.ModDetails
-import GHC.Linker.Types ( Linkable(..), linkableIsNativeCodeOnly )
+import GHC.Linker.Types ( Linkable )
import GHC.Utils.Outputable
-import GHC.Utils.Panic
-
-- | Information about modules in the package being compiled
data HomeModInfo = HomeModInfo
@@ -68,22 +63,6 @@ data HomeModLinkable = HomeModLinkable { homeMod_bytecode :: !(Maybe Linkable)
instance Outputable HomeModLinkable where
ppr (HomeModLinkable l1 l2) = ppr l1 $$ ppr l2
-justBytecode :: Linkable -> HomeModLinkable
-justBytecode lm =
- assertPpr (not (linkableIsNativeCodeOnly lm)) (ppr lm)
- $ emptyHomeModInfoLinkable { homeMod_bytecode = Just lm }
-
-justObjects :: Linkable -> HomeModLinkable
-justObjects lm =
- assertPpr (linkableIsNativeCodeOnly lm) (ppr lm)
- $ emptyHomeModInfoLinkable { homeMod_object = Just lm }
-
-bytecodeAndObjects :: Linkable -> Linkable -> HomeModLinkable
-bytecodeAndObjects bc o =
- assertPpr (not (linkableIsNativeCodeOnly bc) && linkableIsNativeCodeOnly o) (ppr bc $$ ppr o)
- (HomeModLinkable (Just bc) (Just o))
-
-
{-
Note [Home module build products]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Unit/Module/Status.hs
=====================================
@@ -1,22 +1,35 @@
+{-# LANGUAGE LambdaCase #-}
+
module GHC.Unit.Module.Status
- ( HscBackendAction(..), HscRecompStatus (..)
+ ( HscBackendAction(..)
+ , HscRecompStatus (..)
+ , RecompLinkables (..)
+ , RecompBytecodeLinkable (..)
+ , emptyRecompLinkables
+ , justBytecode
+ , justObjects
+ , bytecodeAndObjects
+ , safeCastHomeModLinkable
)
where
import GHC.Prelude
import GHC.Unit
+import GHC.Unit.Home.ModInfo
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface
+import GHC.Linker.Types ( Linkable, WholeCoreBindingsLinkable, linkableIsNativeCodeOnly )
+
import GHC.Utils.Fingerprint
import GHC.Utils.Outputable
-import GHC.Unit.Home.ModInfo
+import GHC.Utils.Panic
-- | Status of a module in incremental compilation
data HscRecompStatus
-- | Nothing to do because code already exists.
- = HscUpToDate ModIface HomeModLinkable
+ = HscUpToDate ModIface RecompLinkables
-- | Recompilation of module, or update of interface is required. Optionally
-- pass the old interface hash to avoid updating the existing interface when
-- it has not changed.
@@ -41,6 +54,16 @@ data HscBackendAction
-- changed.
}
+-- | Linkables produced by @hscRecompStatus@. Might contain serialized core
+-- which can be turned into BCOs (or object files), or used by some other
+-- backend. See Note [Interface Files with Core Definitions].
+data RecompLinkables = RecompLinkables { recompLinkables_bytecode :: !RecompBytecodeLinkable
+ , recompLinkables_object :: !(Maybe Linkable) }
+
+data RecompBytecodeLinkable
+ = NormalLinkable !(Maybe Linkable)
+ | WholeCoreBindingsLinkable !WholeCoreBindingsLinkable
+
instance Outputable HscRecompStatus where
ppr HscUpToDate{} = text "HscUpToDate"
ppr HscRecompNeeded{} = text "HscRecompNeeded"
@@ -48,3 +71,37 @@ instance Outputable HscRecompStatus where
instance Outputable HscBackendAction where
ppr (HscUpdate mi) = text "Update:" <+> (ppr (mi_module mi))
ppr (HscRecomp _ ml _mi _mf) = text "Recomp:" <+> ppr ml
+
+instance Outputable RecompLinkables where
+ ppr (RecompLinkables l1 l2) = ppr l1 $$ ppr l2
+
+instance Outputable RecompBytecodeLinkable where
+ ppr (NormalLinkable lm) = text "NormalLinkable:" <+> ppr lm
+ ppr (WholeCoreBindingsLinkable lm) = text "WholeCoreBindingsLinkable:" <+> ppr lm
+
+emptyRecompLinkables :: RecompLinkables
+emptyRecompLinkables = RecompLinkables (NormalLinkable Nothing) Nothing
+
+safeCastHomeModLinkable :: HomeModLinkable -> RecompLinkables
+safeCastHomeModLinkable (HomeModLinkable bc o) = RecompLinkables (NormalLinkable bc) o
+
+justBytecode :: Either Linkable WholeCoreBindingsLinkable -> RecompLinkables
+justBytecode = \case
+ Left lm ->
+ assertPpr (not (linkableIsNativeCodeOnly lm)) (ppr lm)
+ $ emptyRecompLinkables { recompLinkables_bytecode = NormalLinkable (Just lm) }
+ Right lm -> emptyRecompLinkables { recompLinkables_bytecode = WholeCoreBindingsLinkable lm }
+
+justObjects :: Linkable -> RecompLinkables
+justObjects lm =
+ assertPpr (linkableIsNativeCodeOnly lm) (ppr lm)
+ $ emptyRecompLinkables { recompLinkables_object = Just lm }
+
+bytecodeAndObjects :: Either Linkable WholeCoreBindingsLinkable -> Linkable -> RecompLinkables
+bytecodeAndObjects either_bc o = case either_bc of
+ Left bc ->
+ assertPpr (not (linkableIsNativeCodeOnly bc) && linkableIsNativeCodeOnly o) (ppr bc $$ ppr o)
+ $ RecompLinkables (NormalLinkable (Just bc)) (Just o)
+ Right bc ->
+ assertPpr (linkableIsNativeCodeOnly o) (ppr o)
+ $ RecompLinkables (WholeCoreBindingsLinkable bc) (Just o)
=====================================
compiler/GHC/Unit/Module/WholeCoreBindings.hs
=====================================
@@ -130,6 +130,9 @@ data WholeCoreBindings = WholeCoreBindings
, wcb_foreign :: IfaceForeign
}
+instance Outputable WholeCoreBindings where
+ ppr (WholeCoreBindings {}) = text "WholeCoreBindings"
+
{-
Note [Foreign stubs and TH bytecode linking]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
libraries/base/tests/all.T
=====================================
@@ -80,7 +80,7 @@ test('length001',
# excessive amounts of stack space. So we specifically set a low
# stack limit and mark it as failing under a few conditions.
[extra_run_opts('+RTS -K8m -RTS'),
- expect_fail_for(['normal', 'threaded1', 'llvm', 'nonmoving', 'nonmoving_thr', 'nonmoving_thr_ghc']),
+ expect_fail_for(['normal', 'threaded1', 'llvm', 'nonmoving', 'nonmoving_thr', 'nonmoving_thr_ghc', 'ext-interp']),
# JS doesn't support stack limit so the test sometimes passes just fine. Therefore the test is
# marked as fragile.
when(js_arch(), fragile(22921))],
=====================================
testsuite/driver/testlib.py
=====================================
@@ -352,6 +352,9 @@ def req_plugins( name, opts ):
"""
req_interp(name, opts)
+ # Plugins aren't supported with the external interpreter (#14335)
+ expect_broken_for(14335,['ext-interp'])(name,opts)
+
if config.cross:
opts.skip = True
=====================================
testsuite/tests/codeGen/should_run/T26537.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+import GHC.Exts
+
+type D8 = (# Double#, Double#, Double#, Double#, Double#, Double#, Double#, Double# #)
+type D64 = (# D8, D8, D8, D8, D8, D8, D8, D8 #)
+type D512 = (# D64, D64, D64, D64, D64, D64, D64, D64 #)
+
+unD# :: Double -> Double#
+unD# (D# x) = x
+
+mkD8 :: Double -> D8
+mkD8 x = (# unD# x, unD# (x + 1), unD# (x + 2), unD# (x + 3), unD# (x + 4), unD# (x + 5), unD# (x + 6), unD# (x + 7) #)
+{-# NOINLINE mkD8 #-}
+
+mkD64 :: Double -> D64
+mkD64 x = (# mkD8 x, mkD8 (x + 8), mkD8 (x + 16), mkD8 (x + 24), mkD8 (x + 32), mkD8 (x + 40), mkD8 (x + 48), mkD8 (x + 56) #)
+{-# NOINLINE mkD64 #-}
+
+mkD512 :: Double -> D512
+mkD512 x = (# mkD64 x, mkD64 (x + 64), mkD64 (x + 128), mkD64 (x + 192), mkD64 (x + 256), mkD64 (x + 320), mkD64 (x + 384), mkD64 (x + 448) #)
+{-# NOINLINE mkD512 #-}
+
+addD8 :: D8 -> D8 -> D8
+addD8 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# x0 +## y0, x1 +## y1, x2 +## y2, x3 +## y3, x4 +## y4, x5 +## y5, x6 +## y6, x7 +## y7 #)
+{-# NOINLINE addD8 #-}
+
+addD64 :: D64 -> D64 -> D64
+addD64 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# addD8 x0 y0, addD8 x1 y1, addD8 x2 y2, addD8 x3 y3, addD8 x4 y4, addD8 x5 y5, addD8 x6 y6, addD8 x7 y7 #)
+{-# NOINLINE addD64 #-}
+
+addD512 :: D512 -> D512 -> D512
+addD512 (# x0, x1, x2, x3, x4, x5, x6, x7 #) (# y0, y1, y2, y3, y4, y5, y6, y7 #) = (# addD64 x0 y0, addD64 x1 y1, addD64 x2 y2, addD64 x3 y3, addD64 x4 y4, addD64 x5 y5, addD64 x6 y6, addD64 x7 y7 #)
+{-# NOINLINE addD512 #-}
+
+toListD8 :: D8 -> [Double]
+toListD8 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = [D# x0, D# x1, D# x2, D# x3, D# x4, D# x5, D# x6, D# x7]
+{-# NOINLINE toListD8 #-}
+
+toListD64 :: D64 -> [Double]
+toListD64 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = concat [toListD8 x0, toListD8 x1, toListD8 x2, toListD8 x3, toListD8 x4, toListD8 x5, toListD8 x6, toListD8 x7]
+{-# NOINLINE toListD64 #-}
+
+toListD512 :: D512 -> [Double]
+toListD512 (# x0, x1, x2, x3, x4, x5, x6, x7 #) = concat [toListD64 x0, toListD64 x1, toListD64 x2, toListD64 x3, toListD64 x4, toListD64 x5, toListD64 x6, toListD64 x7]
+{-# NOINLINE toListD512 #-}
+
+data T = MkT D512 D64
+
+mkT :: Double -> T
+mkT x = MkT (mkD512 x) (mkD64 (x + 512))
+{-# NOINLINE mkT #-}
+
+addT :: T -> T -> T
+addT (MkT x0 x1) (MkT y0 y1) = MkT (addD512 x0 y0) (addD64 x1 y1)
+{-# NOINLINE addT #-}
+
+toListT :: T -> [Double]
+toListT (MkT x0 x1) = toListD512 x0 ++ toListD64 x1
+{-# NOINLINE toListT #-}
+
+main :: IO ()
+main = do
+ let n = 512 + 64
+ let !x = mkT 0
+ !y = mkT n
+ print $ toListT x
+ print $ toListT y
+ print $ toListT (addT x y)
+ print $ toListT x == [0..n-1]
+ print $ toListT y == [n..2*n-1]
+ print $ toListT (addT x y) == zipWith (+) [0..n-1] [n..2*n-1]
=====================================
testsuite/tests/codeGen/should_run/T26537.stdout
=====================================
@@ -0,0 +1,6 @@
+[0.0,1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0,10.0,11.0,12.0,13.0,14.0,15.0,16.0,17.0,18.0,19.0,20.0,21.0,22.0,23.0,24.0,25.0,26.0,27.0,28.0,29.0,30.0,31.0,32.0,33.0,34.0,35.0,36.0,37.0,38.0,39.0,40.0,41.0,42.0,43.0,44.0,45.0,46.0,47.0,48.0,49.0,50.0,51.0,52.0,53.0,54.0,55.0,56.0,57.0,58.0,59.0,60.0,61.0,62.0,63.0,64.0,65.0,66.0,67.0,68.0,69.0,70.0,71.0,72.0,73.0,74.0,75.0,76.0,77.0,78.0,79.0,80.0,81.0,82.0,83.0,84.0,85.0,86.0,87.0,88.0,89.0,90.0,91.0,92.0,93.0,94.0,95.0,96.0,97.0,98.0,99.0,100.0,101.0,102.0,103.0,104.0,105.0,106.0,107.0,108.0,109.0,110.0,111.0,112.0,113.0,114.0,115.0,116.0,117.0,118.0,119.0,120.0,121.0,122.0,123.0,124.0,125.0,126.0,127.0,128.0,129.0,130.0,131.0,132.0,133.0,134.0,135.0,136.0,137.0,138.0,139.0,140.0,141.0,142.0,143.0,144.0,145.0,146.0,147.0,148.0,149.0,150.0,151.0,152.0,153.0,154.0,155.0,156.0,157.0,158.0,159.0,160.0,161.0,162.0,163.0,164.0,165.0,166.0,167.0,168.0,169.0,170.0,171.0,172.0,173.0,174.0,175.0,176.0,177.0,178.0,179.0,180.0,181.0,182.0,183.0,184.0,185.0,186.0,187.0,188.0,189.0,190.0,191.0,192.0,193.0,194.0,195.0,196.0,197.0,198.0,199.0,200.0,201.0,202.0,203.0,204.0,205.0,206.0,207.0,208.0,209.0,210.0,211.0,212.0,213.0,214.0,215.0,216.0,217.0,218.0,219.0,220.0,221.0,222.0,223.0,224.0,225.0,226.0,227.0,228.0,229.0,230.0,231.0,232.0,233.0,234.0,235.0,236.0,237.0,238.0,239.0,240.0,241.0,242.0,243.0,244.0,245.0,246.0,247.0,248.0,249.0,250.0,251.0,252.0,253.0,254.0,255.0,256.0,257.0,258.0,259.0,260.0,261.0,262.0,263.0,264.0,265.0,266.0,267.0,268.0,269.0,270.0,271.0,272.0,273.0,274.0,275.0,276.0,277.0,278.0,279.0,280.0,281.0,282.0,283.0,284.0,285.0,286.0,287.0,288.0,289.0,290.0,291.0,292.0,293.0,294.0,295.0,296.0,297.0,298.0,299.0,300.0,301.0,302.0,303.0,304.0,305.0,306.0,307.0,308.0,309.0,310.0,311.0,312.0,313.0,314.0,315.0,316.0,317.0,318.0,319.0,320.0,321.0,322.0,323.0,324.0,325.0,326.0,327.0,328.0,329.0,330.0,331.0,332.0,333.0,334.0,335.0,336.0,337.0,338.0,339.0,340.0,341.0,342.0,343.0,344.0,345.0,346.0,347.0,348.0,349.0,350.0,351.0,352.0,353.0,354.0,355.0,356.0,357.0,358.0,359.0,360.0,361.0,362.0,363.0,364.0,365.0,366.0,367.0,368.0,369.0,370.0,371.0,372.0,373.0,374.0,375.0,376.0,377.0,378.0,379.0,380.0,381.0,382.0,383.0,384.0,385.0,386.0,387.0,388.0,389.0,390.0,391.0,392.0,393.0,394.0,395.0,396.0,397.0,398.0,399.0,400.0,401.0,402.0,403.0,404.0,405.0,406.0,407.0,408.0,409.0,410.0,411.0,412.0,413.0,414.0,415.0,416.0,417.0,418.0,419.0,420.0,421.0,422.0,423.0,424.0,425.0,426.0,427.0,428.0,429.0,430.0,431.0,432.0,433.0,434.0,435.0,436.0,437.0,438.0,439.0,440.0,441.0,442.0,443.0,444.0,445.0,446.0,447.0,448.0,449.0,450.0,451.0,452.0,453.0,454.0,455.0,456.0,457.0,458.0,459.0,460.0,461.0,462.0,463.0,464.0,465.0,466.0,467.0,468.0,469.0,470.0,471.0,472.0,473.0,474.0,475.0,476.0,477.0,478.0,479.0,480.0,481.0,482.0,483.0,484.0,485.0,486.0,487.0,488.0,489.0,490.0,491.0,492.0,493.0,494.0,495.0,496.0,497.0,498.0,499.0,500.0,501.0,502.0,503.0,504.0,505.0,506.0,507.0,508.0,509.0,510.0,511.0,512.0,513.0,514.0,515.0,516.0,517.0,518.0,519.0,520.0,521.0,522.0,523.0,524.0,525.0,526.0,527.0,528.0,529.0,530.0,531.0,532.0,533.0,534.0,535.0,536.0,537.0,538.0,539.0,540.0,541.0,542.0,543.0,544.0,545.0,546.0,547.0,548.0,549.0,550.0,551.0,552.0,553.0,554.0,555.0,556.0,557.0,558.0,559.0,560.0,561.0,562.0,563.0,564.0,565.0,566.0,567.0,568.0,569.0,570.0,571.0,572.0,573.0,574.0,575.0]
+[576.0,577.0,578.0,579.0,580.0,581.0,582.0,583.0,584.0,585.0,586.0,587.0,588.0,589.0,590.0,591.0,592.0,593.0,594.0,595.0,596.0,597.0,598.0,599.0,600.0,601.0,602.0,603.0,604.0,605.0,606.0,607.0,608.0,609.0,610.0,611.0,612.0,613.0,614.0,615.0,616.0,617.0,618.0,619.0,620.0,621.0,622.0,623.0,624.0,625.0,626.0,627.0,628.0,629.0,630.0,631.0,632.0,633.0,634.0,635.0,636.0,637.0,638.0,639.0,640.0,641.0,642.0,643.0,644.0,645.0,646.0,647.0,648.0,649.0,650.0,651.0,652.0,653.0,654.0,655.0,656.0,657.0,658.0,659.0,660.0,661.0,662.0,663.0,664.0,665.0,666.0,667.0,668.0,669.0,670.0,671.0,672.0,673.0,674.0,675.0,676.0,677.0,678.0,679.0,680.0,681.0,682.0,683.0,684.0,685.0,686.0,687.0,688.0,689.0,690.0,691.0,692.0,693.0,694.0,695.0,696.0,697.0,698.0,699.0,700.0,701.0,702.0,703.0,704.0,705.0,706.0,707.0,708.0,709.0,710.0,711.0,712.0,713.0,714.0,715.0,716.0,717.0,718.0,719.0,720.0,721.0,722.0,723.0,724.0,725.0,726.0,727.0,728.0,729.0,730.0,731.0,732.0,733.0,734.0,735.0,736.0,737.0,738.0,739.0,740.0,741.0,742.0,743.0,744.0,745.0,746.0,747.0,748.0,749.0,750.0,751.0,752.0,753.0,754.0,755.0,756.0,757.0,758.0,759.0,760.0,761.0,762.0,763.0,764.0,765.0,766.0,767.0,768.0,769.0,770.0,771.0,772.0,773.0,774.0,775.0,776.0,777.0,778.0,779.0,780.0,781.0,782.0,783.0,784.0,785.0,786.0,787.0,788.0,789.0,790.0,791.0,792.0,793.0,794.0,795.0,796.0,797.0,798.0,799.0,800.0,801.0,802.0,803.0,804.0,805.0,806.0,807.0,808.0,809.0,810.0,811.0,812.0,813.0,814.0,815.0,816.0,817.0,818.0,819.0,820.0,821.0,822.0,823.0,824.0,825.0,826.0,827.0,828.0,829.0,830.0,831.0,832.0,833.0,834.0,835.0,836.0,837.0,838.0,839.0,840.0,841.0,842.0,843.0,844.0,845.0,846.0,847.0,848.0,849.0,850.0,851.0,852.0,853.0,854.0,855.0,856.0,857.0,858.0,859.0,860.0,861.0,862.0,863.0,864.0,865.0,866.0,867.0,868.0,869.0,870.0,871.0,872.0,873.0,874.0,875.0,876.0,877.0,878.0,879.0,880.0,881.0,882.0,883.0,884.0,885.0,886.0,887.0,888.0,889.0,890.0,891.0,892.0,893.0,894.0,895.0,896.0,897.0,898.0,899.0,900.0,901.0,902.0,903.0,904.0,905.0,906.0,907.0,908.0,909.0,910.0,911.0,912.0,913.0,914.0,915.0,916.0,917.0,918.0,919.0,920.0,921.0,922.0,923.0,924.0,925.0,926.0,927.0,928.0,929.0,930.0,931.0,932.0,933.0,934.0,935.0,936.0,937.0,938.0,939.0,940.0,941.0,942.0,943.0,944.0,945.0,946.0,947.0,948.0,949.0,950.0,951.0,952.0,953.0,954.0,955.0,956.0,957.0,958.0,959.0,960.0,961.0,962.0,963.0,964.0,965.0,966.0,967.0,968.0,969.0,970.0,971.0,972.0,973.0,974.0,975.0,976.0,977.0,978.0,979.0,980.0,981.0,982.0,983.0,984.0,985.0,986.0,987.0,988.0,989.0,990.0,991.0,992.0,993.0,994.0,995.0,996.0,997.0,998.0,999.0,1000.0,1001.0,1002.0,1003.0,1004.0,1005.0,1006.0,1007.0,1008.0,1009.0,1010.0,1011.0,1012.0,1013.0,1014.0,1015.0,1016.0,1017.0,1018.0,1019.0,1020.0,1021.0,1022.0,1023.0,1024.0,1025.0,1026.0,1027.0,1028.0,1029.0,1030.0,1031.0,1032.0,1033.0,1034.0,1035.0,1036.0,1037.0,1038.0,1039.0,1040.0,1041.0,1042.0,1043.0,1044.0,1045.0,1046.0,1047.0,1048.0,1049.0,1050.0,1051.0,1052.0,1053.0,1054.0,1055.0,1056.0,1057.0,1058.0,1059.0,1060.0,1061.0,1062.0,1063.0,1064.0,1065.0,1066.0,1067.0,1068.0,1069.0,1070.0,1071.0,1072.0,1073.0,1074.0,1075.0,1076.0,1077.0,1078.0,1079.0,1080.0,1081.0,1082.0,1083.0,1084.0,1085.0,1086.0,1087.0,1088.0,1089.0,1090.0,1091.0,1092.0,1093.0,1094.0,1095.0,1096.0,1097.0,1098.0,1099.0,1100.0,1101.0,1102.0,1103.0,1104.0,1105.0,1106.0,1107.0,1108.0,1109.0,1110.0,1111.0,1112.0,1113.0,1114.0,1115.0,1116.0,1117.0,1118.0,1119.0,1120.0,1121.0,1122.0,1123.0,1124.0,1125.0,1126.0,1127.0,1128.0,1129.0,1130.0,1131.0,1132.0,1133.0,1134.0,1135.0,1136.0,1137.0,1138.0,1139.0,1140.0,1141.0,1142.0,1143.0,1144.0,1145.0,1146.0,1147.0,1148.0,1149.0,1150.0,1151.0]
+[576.0,578.0,580.0,582.0,584.0,586.0,588.0,590.0,592.0,594.0,596.0,598.0,600.0,602.0,604.0,606.0,608.0,610.0,612.0,614.0,616.0,618.0,620.0,622.0,624.0,626.0,628.0,630.0,632.0,634.0,636.0,638.0,640.0,642.0,644.0,646.0,648.0,650.0,652.0,654.0,656.0,658.0,660.0,662.0,664.0,666.0,668.0,670.0,672.0,674.0,676.0,678.0,680.0,682.0,684.0,686.0,688.0,690.0,692.0,694.0,696.0,698.0,700.0,702.0,704.0,706.0,708.0,710.0,712.0,714.0,716.0,718.0,720.0,722.0,724.0,726.0,728.0,730.0,732.0,734.0,736.0,738.0,740.0,742.0,744.0,746.0,748.0,750.0,752.0,754.0,756.0,758.0,760.0,762.0,764.0,766.0,768.0,770.0,772.0,774.0,776.0,778.0,780.0,782.0,784.0,786.0,788.0,790.0,792.0,794.0,796.0,798.0,800.0,802.0,804.0,806.0,808.0,810.0,812.0,814.0,816.0,818.0,820.0,822.0,824.0,826.0,828.0,830.0,832.0,834.0,836.0,838.0,840.0,842.0,844.0,846.0,848.0,850.0,852.0,854.0,856.0,858.0,860.0,862.0,864.0,866.0,868.0,870.0,872.0,874.0,876.0,878.0,880.0,882.0,884.0,886.0,888.0,890.0,892.0,894.0,896.0,898.0,900.0,902.0,904.0,906.0,908.0,910.0,912.0,914.0,916.0,918.0,920.0,922.0,924.0,926.0,928.0,930.0,932.0,934.0,936.0,938.0,940.0,942.0,944.0,946.0,948.0,950.0,952.0,954.0,956.0,958.0,960.0,962.0,964.0,966.0,968.0,970.0,972.0,974.0,976.0,978.0,980.0,982.0,984.0,986.0,988.0,990.0,992.0,994.0,996.0,998.0,1000.0,1002.0,1004.0,1006.0,1008.0,1010.0,1012.0,1014.0,1016.0,1018.0,1020.0,1022.0,1024.0,1026.0,1028.0,1030.0,1032.0,1034.0,1036.0,1038.0,1040.0,1042.0,1044.0,1046.0,1048.0,1050.0,1052.0,1054.0,1056.0,1058.0,1060.0,1062.0,1064.0,1066.0,1068.0,1070.0,1072.0,1074.0,1076.0,1078.0,1080.0,1082.0,1084.0,1086.0,1088.0,1090.0,1092.0,1094.0,1096.0,1098.0,1100.0,1102.0,1104.0,1106.0,1108.0,1110.0,1112.0,1114.0,1116.0,1118.0,1120.0,1122.0,1124.0,1126.0,1128.0,1130.0,1132.0,1134.0,1136.0,1138.0,1140.0,1142.0,1144.0,1146.0,1148.0,1150.0,1152.0,1154.0,1156.0,1158.0,1160.0,1162.0,1164.0,1166.0,1168.0,1170.0,1172.0,1174.0,1176.0,1178.0,1180.0,1182.0,1184.0,1186.0,1188.0,1190.0,1192.0,1194.0,1196.0,1198.0,1200.0,1202.0,1204.0,1206.0,1208.0,1210.0,1212.0,1214.0,1216.0,1218.0,1220.0,1222.0,1224.0,1226.0,1228.0,1230.0,1232.0,1234.0,1236.0,1238.0,1240.0,1242.0,1244.0,1246.0,1248.0,1250.0,1252.0,1254.0,1256.0,1258.0,1260.0,1262.0,1264.0,1266.0,1268.0,1270.0,1272.0,1274.0,1276.0,1278.0,1280.0,1282.0,1284.0,1286.0,1288.0,1290.0,1292.0,1294.0,1296.0,1298.0,1300.0,1302.0,1304.0,1306.0,1308.0,1310.0,1312.0,1314.0,1316.0,1318.0,1320.0,1322.0,1324.0,1326.0,1328.0,1330.0,1332.0,1334.0,1336.0,1338.0,1340.0,1342.0,1344.0,1346.0,1348.0,1350.0,1352.0,1354.0,1356.0,1358.0,1360.0,1362.0,1364.0,1366.0,1368.0,1370.0,1372.0,1374.0,1376.0,1378.0,1380.0,1382.0,1384.0,1386.0,1388.0,1390.0,1392.0,1394.0,1396.0,1398.0,1400.0,1402.0,1404.0,1406.0,1408.0,1410.0,1412.0,1414.0,1416.0,1418.0,1420.0,1422.0,1424.0,1426.0,1428.0,1430.0,1432.0,1434.0,1436.0,1438.0,1440.0,1442.0,1444.0,1446.0,1448.0,1450.0,1452.0,1454.0,1456.0,1458.0,1460.0,1462.0,1464.0,1466.0,1468.0,1470.0,1472.0,1474.0,1476.0,1478.0,1480.0,1482.0,1484.0,1486.0,1488.0,1490.0,1492.0,1494.0,1496.0,1498.0,1500.0,1502.0,1504.0,1506.0,1508.0,1510.0,1512.0,1514.0,1516.0,1518.0,1520.0,1522.0,1524.0,1526.0,1528.0,1530.0,1532.0,1534.0,1536.0,1538.0,1540.0,1542.0,1544.0,1546.0,1548.0,1550.0,1552.0,1554.0,1556.0,1558.0,1560.0,1562.0,1564.0,1566.0,1568.0,1570.0,1572.0,1574.0,1576.0,1578.0,1580.0,1582.0,1584.0,1586.0,1588.0,1590.0,1592.0,1594.0,1596.0,1598.0,1600.0,1602.0,1604.0,1606.0,1608.0,1610.0,1612.0,1614.0,1616.0,1618.0,1620.0,1622.0,1624.0,1626.0,1628.0,1630.0,1632.0,1634.0,1636.0,1638.0,1640.0,1642.0,1644.0,1646.0,1648.0,1650.0,1652.0,1654.0,1656.0,1658.0,1660.0,1662.0,1664.0,1666.0,1668.0,1670.0,1672.0,1674.0,1676.0,1678.0,1680.0,1682.0,1684.0,1686.0,1688.0,1690.0,1692.0,1694.0,1696.0,1698.0,1700.0,1702.0,1704.0,1706.0,1708.0,1710.0,1712.0,1714.0,1716.0,1718.0,1720.0,1722.0,1724.0,1726.0]
+True
+True
+True
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -256,3 +256,4 @@ test('T24893', normal, compile_and_run, ['-O'])
test('CCallConv', [req_c], compile_and_run, ['CCallConv_c.c'])
test('T25364', normal, compile_and_run, [''])
test('T26061', normal, compile_and_run, [''])
+test('T26537', normal, compile_and_run, ['-O2 -fregs-graph'])
=====================================
testsuite/tests/driver/T20696/all.T
=====================================
@@ -1,4 +1,5 @@
test('T20696', [extra_files(['A.hs', 'B.hs', 'C.hs'])
+ , expect_broken_for(26552, ['ext-interp'])
, unless(ghc_dynamic(), skip)], multimod_compile, ['A', ''])
test('T20696-static', [extra_files(['A.hs', 'B.hs', 'C.hs'])
, when(ghc_dynamic(), skip)], multimod_compile, ['A', ''])
=====================================
testsuite/tests/driver/fat-iface/all.T
=====================================
@@ -9,12 +9,12 @@ test('fat010', [req_th,extra_files(['THA.hs', 'THB.hs', 'THC.hs']), copy_files],
# Check linking works when using -fbyte-code-and-object-code
test('fat011', [req_th, extra_files(['FatMain.hs', 'FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatMain', '-fbyte-code-and-object-code -fprefer-byte-code'])
# Check that we use interpreter rather than enable dynamic-too if needed for TH
-test('fat012', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
+test('fat012', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fprefer-byte-code'])
# Check that no objects are generated if using -fno-code and -fprefer-byte-code
test('fat013', [req_th, req_bco, extra_files(['FatTH.hs', 'FatQuote.hs'])], multimod_compile, ['FatTH', '-fno-code -fprefer-byte-code'])
# When using interpreter should not produce objects
test('fat014', [req_th, extra_files(['FatTH.hs', 'FatQuote.hs']), extra_run_opts('-fno-code')], ghci_script, ['fat014.script'])
-test('fat015', [req_th, unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
+test('fat015', [req_th, expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(['FatQuote.hs', 'FatQuote1.hs', 'FatQuote2.hs', 'FatTH1.hs', 'FatTH2.hs', 'FatTHTop.hs'])], multimod_compile, ['FatTHTop', '-fno-code -fwrite-interface'])
test('T22807', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807A.hs', 'T22807B.hs'])]
, makefile_test, ['T22807'])
test('T22807_ghci', [req_th, unless(ghc_dynamic(), skip), extra_files(['T22807_ghci.hs'])]
=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
=====================================
@@ -2,8 +2,6 @@
{-# OPTIONS -haddock -ddump-parsed-ast #-}
-- Haddock comments in this test case are all rejected.
---
--- See Note [Register keyword location] in GHC.Parser.PostProcess.Haddock
module
-- | Bad comment for the module
=====================================
testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
=====================================
@@ -10,15 +10,15 @@
(AnnsModule
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:8:1-6 }))
+ (EpaSpan { T17544_kw.hs:6:1-6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:12-16 }))
+ (EpaSpan { T17544_kw.hs:11:12-16 }))
[]
[]
(Just
((,)
- { T17544_kw.hs:25:1 }
- { T17544_kw.hs:24:18 })))
+ { T17544_kw.hs:23:1 }
+ { T17544_kw.hs:22:18 })))
(EpaCommentsBalanced
[]
[]))
@@ -29,7 +29,7 @@
(Just
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:10:3-11 })
+ (EpaSpan { T17544_kw.hs:8:3-11 })
(AnnListItem
[])
(EpaComments
@@ -38,14 +38,14 @@
(Just
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(10,13)-(13,10) })
+ (EpaSpan { T17544_kw.hs:(8,13)-(11,10) })
(AnnList
(Nothing)
(ListParens
(EpTok
- (EpaSpan { T17544_kw.hs:10:13 }))
+ (EpaSpan { T17544_kw.hs:8:13 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:10 })))
+ (EpaSpan { T17544_kw.hs:11:10 })))
[]
((,)
(NoEpTok)
@@ -55,11 +55,11 @@
[]))
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-9 })
+ (EpaSpan { T17544_kw.hs:9:3-9 })
(AnnListItem
[(AddCommaAnn
(EpTok
- (EpaSpan { T17544_kw.hs:11:10 })))])
+ (EpaSpan { T17544_kw.hs:9:10 })))])
(EpaComments
[]))
(IEThingAll
@@ -67,14 +67,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:11:6 }))
+ (EpaSpan { T17544_kw.hs:9:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:11:7-8 }))
+ (EpaSpan { T17544_kw.hs:9:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:11:9 }))))
+ (EpaSpan { T17544_kw.hs:9:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-5 })
+ (EpaSpan { T17544_kw.hs:9:3-5 })
(AnnListItem
[])
(EpaComments
@@ -83,7 +83,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:11:3-5 })
+ (EpaSpan { T17544_kw.hs:9:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -93,11 +93,11 @@
(Nothing)))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-9 })
+ (EpaSpan { T17544_kw.hs:10:3-9 })
(AnnListItem
[(AddCommaAnn
(EpTok
- (EpaSpan { T17544_kw.hs:12:10 })))])
+ (EpaSpan { T17544_kw.hs:10:10 })))])
(EpaComments
[]))
(IEThingAll
@@ -105,14 +105,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:12:6 }))
+ (EpaSpan { T17544_kw.hs:10:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:12:7-8 }))
+ (EpaSpan { T17544_kw.hs:10:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:12:9 }))))
+ (EpaSpan { T17544_kw.hs:10:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-5 })
+ (EpaSpan { T17544_kw.hs:10:3-5 })
(AnnListItem
[])
(EpaComments
@@ -121,7 +121,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:12:3-5 })
+ (EpaSpan { T17544_kw.hs:10:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -131,7 +131,7 @@
(Nothing)))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-9 })
+ (EpaSpan { T17544_kw.hs:11:3-9 })
(AnnListItem
[])
(EpaComments
@@ -141,14 +141,14 @@
(Nothing)
((,,)
(EpTok
- (EpaSpan { T17544_kw.hs:13:6 }))
+ (EpaSpan { T17544_kw.hs:11:6 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:7-8 }))
+ (EpaSpan { T17544_kw.hs:11:7-8 }))
(EpTok
- (EpaSpan { T17544_kw.hs:13:9 }))))
+ (EpaSpan { T17544_kw.hs:11:9 }))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-5 })
+ (EpaSpan { T17544_kw.hs:11:3-5 })
(AnnListItem
[])
(EpaComments
@@ -157,7 +157,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:13:3-5 })
+ (EpaSpan { T17544_kw.hs:11:3-5 })
(NameAnnTrailing
[])
(EpaComments
@@ -168,7 +168,7 @@
[]
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(15,1)-(16,20) })
+ (EpaSpan { T17544_kw.hs:(13,1)-(14,20) })
(AnnListItem
[])
(EpaComments
@@ -179,7 +179,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:15:6-8 })
+ (EpaSpan { T17544_kw.hs:13:6-8 })
(NameAnnTrailing
[])
(EpaComments
@@ -197,11 +197,11 @@
(NoEpTok)
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:15:1-4 }))
+ (EpaSpan { T17544_kw.hs:13:1-4 }))
(NoEpTok)
(NoEpUniTok)
(EpTok
- (EpaSpan { T17544_kw.hs:16:3-7 }))
+ (EpaSpan { T17544_kw.hs:14:3-7 }))
(NoEpTok)
(NoEpTok)
(NoEpTok))
@@ -212,7 +212,7 @@
(False)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:9-20 })
+ (EpaSpan { T17544_kw.hs:14:9-20 })
(AnnListItem
[])
(EpaComments
@@ -222,12 +222,12 @@
[]
[]
(EpUniTok
- (EpaSpan { T17544_kw.hs:16:15-16 })
+ (EpaSpan { T17544_kw.hs:14:15-16 })
(NormalSyntax)))
(:|
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:9-13 })
+ (EpaSpan { T17544_kw.hs:14:9-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -237,7 +237,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(AnnListItem
[])
(EpaComments
@@ -251,7 +251,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(AnnListItem
[])
(EpaComments
@@ -261,7 +261,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:16:18-20 })
+ (EpaSpan { T17544_kw.hs:14:18-20 })
(NameAnnTrailing
[])
(EpaComments
@@ -272,7 +272,7 @@
[]))))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(18,1)-(19,26) })
+ (EpaSpan { T17544_kw.hs:(16,1)-(17,26) })
(AnnListItem
[])
(EpaComments
@@ -283,7 +283,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:18:9-11 })
+ (EpaSpan { T17544_kw.hs:16:9-11 })
(NameAnnTrailing
[])
(EpaComments
@@ -300,12 +300,12 @@
[]
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:18:1-7 }))
+ (EpaSpan { T17544_kw.hs:16:1-7 }))
(NoEpTok)
(NoEpTok)
(NoEpUniTok)
(EpTok
- (EpaSpan { T17544_kw.hs:19:3-7 }))
+ (EpaSpan { T17544_kw.hs:17:3-7 }))
(NoEpTok)
(NoEpTok)
(NoEpTok))
@@ -315,7 +315,7 @@
(NewTypeCon
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:9-26 })
+ (EpaSpan { T17544_kw.hs:17:9-26 })
(AnnListItem
[])
(EpaComments
@@ -325,12 +325,12 @@
[]
[]
(EpUniTok
- (EpaSpan { T17544_kw.hs:19:15-16 })
+ (EpaSpan { T17544_kw.hs:17:15-16 })
(NormalSyntax)))
(:|
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:9-13 })
+ (EpaSpan { T17544_kw.hs:17:9-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -340,7 +340,7 @@
[])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:18-26 })
+ (EpaSpan { T17544_kw.hs:17:18-26 })
(AnnListItem
[])
(EpaComments
@@ -363,11 +363,11 @@
(HsUnannotated
(EpArrow
(EpUniTok
- (EpaSpan { T17544_kw.hs:19:21-22 })
+ (EpaSpan { T17544_kw.hs:17:21-22 })
(NormalSyntax))))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:18-19 })
+ (EpaSpan { T17544_kw.hs:17:18-19 })
(AnnListItem
[])
(EpaComments
@@ -375,15 +375,15 @@
(HsTupleTy
(AnnParens
(EpTok
- (EpaSpan { T17544_kw.hs:19:18 }))
+ (EpaSpan { T17544_kw.hs:17:18 }))
(EpTok
- (EpaSpan { T17544_kw.hs:19:19 })))
+ (EpaSpan { T17544_kw.hs:17:19 })))
(HsBoxedOrConstraintTuple)
[]))
(Nothing))])
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:24-26 })
+ (EpaSpan { T17544_kw.hs:17:24-26 })
(AnnListItem
[])
(EpaComments
@@ -393,7 +393,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:19:24-26 })
+ (EpaSpan { T17544_kw.hs:17:24-26 })
(NameAnnTrailing
[])
(EpaComments
@@ -404,7 +404,7 @@
[]))))
,(L
(EpAnn
- (EpaSpan { T17544_kw.hs:(21,1)-(24,18) })
+ (EpaSpan { T17544_kw.hs:(19,1)-(22,18) })
(AnnListItem
[])
(EpaComments
@@ -415,12 +415,12 @@
((,,)
(AnnClassDecl
(EpTok
- (EpaSpan { T17544_kw.hs:21:1-5 }))
+ (EpaSpan { T17544_kw.hs:19:1-5 }))
[]
[]
(NoEpTok)
(EpTok
- (EpaSpan { T17544_kw.hs:23:3-7 }))
+ (EpaSpan { T17544_kw.hs:21:3-7 }))
(NoEpTok)
(NoEpTok)
[])
@@ -430,7 +430,7 @@
(Nothing)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:7-9 })
+ (EpaSpan { T17544_kw.hs:19:7-9 })
(NameAnnTrailing
[])
(EpaComments
@@ -441,7 +441,7 @@
(NoExtField)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:11 })
+ (EpaSpan { T17544_kw.hs:19:11 })
(AnnListItem
[])
(EpaComments
@@ -458,7 +458,7 @@
(NoExtField)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:21:11 })
+ (EpaSpan { T17544_kw.hs:19:11 })
(NameAnnTrailing
[])
(EpaComments
@@ -471,7 +471,7 @@
[]
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:5-18 })
+ (EpaSpan { T17544_kw.hs:22:5-18 })
(AnnListItem
[])
(EpaComments
@@ -479,14 +479,14 @@
(ClassOpSig
(AnnSig
(EpUniTok
- (EpaSpan { T17544_kw.hs:24:15-16 })
+ (EpaSpan { T17544_kw.hs:22:15-16 })
(NormalSyntax))
(Nothing)
(Nothing))
(False)
[(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:5-13 })
+ (EpaSpan { T17544_kw.hs:22:5-13 })
(NameAnnTrailing
[])
(EpaComments
@@ -495,7 +495,7 @@
{OccName: clsmethod}))]
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(AnnListItem
[])
(EpaComments
@@ -506,7 +506,7 @@
(NoExtField))
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(AnnListItem
[])
(EpaComments
@@ -516,7 +516,7 @@
(NotPromoted)
(L
(EpAnn
- (EpaSpan { T17544_kw.hs:24:18 })
+ (EpaSpan { T17544_kw.hs:22:18 })
(NameAnnTrailing
[])
(EpaComments
@@ -529,15 +529,15 @@
[])))]))
-T17544_kw.hs:9:3: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:7:3: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:15:10: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:13:10: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:18:13: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:16:13: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
-T17544_kw.hs:22:5: warning: [GHC-94458] [-Winvalid-haddock]
+T17544_kw.hs:20:5: warning: [GHC-94458] [-Winvalid-haddock]
A Haddock comment cannot appear in this position and will be ignored.
=====================================
testsuite/tests/splice-imports/all.T
=====================================
@@ -9,7 +9,7 @@ test('SI03', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI03', '-v0']
test('SI04', [extra_files(["SI01A.hs"])], multimod_compile, ['SI04', '-v0'])
test('SI05', [extra_files(["SI01A.hs"])], multimod_compile_fail, ['SI05', '-v0'])
test('SI06', [extra_files(["SI01A.hs"])], multimod_compile, ['SI06', '-v0'])
-test('SI07', [unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
+test('SI07', [expect_broken_for(26552, ['ext-interp']), unless(ghc_dynamic(), skip), extra_files(["SI05A.hs"])], multimod_compile, ['SI07', '-fwrite-interface -fno-code'])
# Instance tests
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'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/19a1f0d904824c31ab52d9ef239771f...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/19a1f0d904824c31ab52d9ef239771f...
You're receiving this email because of your account on gitlab.haskell.org.