diff options
-rw-r--r-- | compiler/GHC/Driver/Main.hs | 71 | ||||
-rw-r--r-- | compiler/GHC/Driver/Pipeline.hs | 22 | ||||
-rw-r--r-- | compiler/GHC/Driver/Pipeline/Monad.hs | 9 | ||||
-rw-r--r-- | compiler/GHC/Iface/UpdateIdInfos.hs | 160 | ||||
-rw-r--r-- | compiler/GHC/Unit/Module/Status.hs | 1 | ||||
-rw-r--r-- | compiler/ghc.cabal.in | 1 | ||||
-rw-r--r-- | testsuite/tests/ghci.debugger/scripts/print012.stdout | 4 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T10321.stdout | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T15872.stdout | 4 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T4175.stdout | 4 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/ghci025.stdout | 6 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/ghci064.stdout | 2 | ||||
-rw-r--r-- | testsuite/tests/indexed-types/should_fail/Over.stderr | 12 | ||||
-rw-r--r-- | testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr | 12 | ||||
-rw-r--r-- | testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr | 12 | ||||
-rw-r--r-- | testsuite/tests/simplCore/should_compile/T18013.stderr | 4 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_fail/T6018fail.stderr | 24 |
17 files changed, 116 insertions, 234 deletions
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs index 07f1e7acda..296a855acf 100644 --- a/compiler/GHC/Driver/Main.hs +++ b/compiler/GHC/Driver/Main.hs @@ -42,6 +42,7 @@ module GHC.Driver.Main , Messager, batchMsg , HscStatus (..) , hscIncrementalCompile + , initModDetails , hscMaybeWriteIface , hscCompileCmmFile @@ -804,16 +805,7 @@ hscIncrementalCompile always_do_basic_recompilation_check m_tc_result -- We didn't need to do any typechecking; the old interface -- file on disk was good enough. Left iface -> do - -- Knot tying! See Note [Knot-tying typecheckIface] - details <- liftIO . fixIO $ \details' -> do - let act hpt = addToHpt hpt (ms_mod_name mod_summary) - (HomeModInfo iface details' Nothing) - let hsc_env' = hscUpdateHPT act hsc_env - -- NB: This result is actually not that useful - -- in one-shot mode, since we're not going to do - -- any further typechecking. It's much more useful - -- in make mode, since this HMI will go into the HPT. - genModDetails hsc_env' iface + details <- liftIO $ initModDetails hsc_env mod_summary iface return (HscUpToDate iface details, hsc_env') -- We finished type checking. (mb_old_hash is the hash of -- the interface that existed on disk; it's possible we had @@ -823,6 +815,64 @@ hscIncrementalCompile always_do_basic_recompilation_check m_tc_result status <- finish mod_summary tc_result mb_old_hash return (status, hsc_env) +-- Knot tying! See Note [Knot-tying typecheckIface] +-- See Note [ModDetails and --make mode] +initModDetails :: HscEnv -> ModSummary -> ModIface -> IO ModDetails +initModDetails hsc_env mod_summary iface = + fixIO $ \details' -> do + let act hpt = addToHpt hpt (ms_mod_name mod_summary) + (HomeModInfo iface details' Nothing) + let hsc_env' = hscUpdateHPT act hsc_env + -- NB: This result is actually not that useful + -- in one-shot mode, since we're not going to do + -- any further typechecking. It's much more useful + -- in make mode, since this HMI will go into the HPT. + genModDetails hsc_env' iface + + +{- +Note [ModDetails and --make mode] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +An interface file consists of two parts + +* The `ModIface` which ends up getting written to disk. + The `ModIface` is a completely acyclic tree, which can be serialised + and de-serialised completely straightforwardly. The `ModIface` is + also the structure that is finger-printed for recompilation control. + +* The `ModDetails` which provides a more structured view that is suitable + for usage during compilation. The `ModDetails` is heavily cyclic: + An `Id` contains a `Type`, which mentions a `TyCon` that contains kind + that mentions other `TyCons`; the `Id` also includes an unfolding that + in turn mentions more `Id`s; And so on. + +The `ModIface` can be created from the `ModDetails` and the `ModDetails` from +a `ModIface`. + +During tidying, just before interfaces are written to disk, +the ModDetails is calculated and then converted into a ModIface (see GHC.Iface.Make.mkIface_). +Then when GHC needs to restart typechecking from a certain point it can read the +interface file, and regenerate the ModDetails from the ModIface (see GHC.IfaceToCore.typecheckIface). +The key part about the loading is that the ModDetails is regenerated lazily +from the ModIface, so that there's only a detailed in-memory representation +for declarations which are actually used from the interface. This mode is +also used when reading interface files from external packages. + +In the old --make mode implementation, the interface was written after compiling a module +but the in-memory ModDetails which was used to compute the ModIface was retained. +The result was that --make mode used much more memory than `-c` mode, because a large amount of +information about a module would be kept in the ModDetails but never used. + +The new idea is that even in `--make` mode, when there is an in-memory `ModDetails` +at hand, we re-create the `ModDetails` from the `ModIface`. Doing this means that +we only have to keep the `ModIface` decls in memory and then lazily load +detailed representations if needed. It turns out this makes a really big difference +to memory usage, halving maximum memory used in some cases. + +See !5492 and #13586 +-} + -- Runs the post-typechecking frontend (desugar and simplify). We want to -- generate most of the interface as late as possible. This gets us up-to-date -- and good unfoldings and other info in the interface file. @@ -876,7 +926,6 @@ finish summary tc_result mb_old_hash = do return HscRecomp { hscs_guts = cg_guts, hscs_mod_location = ms_location summary, - hscs_mod_details = details, hscs_partial_iface = partial_iface, hscs_old_iface_hash = mb_old_hash } diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs index 0a75b62248..e6b7be62ef 100644 --- a/compiler/GHC/Driver/Pipeline.hs +++ b/compiler/GHC/Driver/Pipeline.hs @@ -87,7 +87,6 @@ import GHC.Data.StringBuffer ( hGetStringBuffer, hPutStringBuffer ) import GHC.Data.Maybe ( expectJust ) import GHC.Iface.Make ( mkFullIface ) -import GHC.Iface.UpdateIdInfos ( updateModDetailsIdInfos ) import GHC.Types.Basic ( SuccessFlag(..) ) import GHC.Types.Target @@ -100,7 +99,6 @@ import GHC.Unit.Env import GHC.Unit.State import GHC.Unit.Finder import GHC.Unit.Module.ModSummary -import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModIface import GHC.Unit.Module.Graph (needsTemplateHaskellOrQQ) import GHC.Unit.Module.Deps @@ -258,13 +256,15 @@ compileOne' m_tc_result mHscMessage return $! HomeModInfo iface hmi_details (Just linkable) (HscRecomp { hscs_guts = cgguts, hscs_mod_location = mod_location, - hscs_mod_details = hmi_details, hscs_partial_iface = partial_iface, hscs_old_iface_hash = mb_old_iface_hash }, Interpreter) -> do -- In interpreted mode the regular codeGen backend is not run so we -- generate a interface without codeGen info. final_iface <- mkFullIface hsc_env' partial_iface Nothing + -- Reconstruct the `ModDetails` from the just-constructed `ModIface` + -- See Note [ModDetails and --make mode] + hmi_details <- liftIO $ initModDetails hsc_env' summary final_iface liftIO $ hscMaybeWriteIface logger dflags True final_iface mb_old_iface_hash (ms_location summary) (hasStub, comp_bc, spt_entries) <- hscInteractive hsc_env' cgguts mod_location @@ -291,7 +291,7 @@ compileOne' m_tc_result mHscMessage (Temporary TFL_CurrentModule) basename dflags next_phase (Just location) -- We're in --make mode: finish the compilation pipeline. - (_, _, Just (iface, details)) <- runPipeline StopLn hsc_env' + (_, _, Just iface) <- runPipeline StopLn hsc_env' (output_fn, Nothing, Just (HscOut src_flavour mod_name status)) @@ -302,6 +302,8 @@ compileOne' m_tc_result mHscMessage -- The object filename comes from the ModLocation o_time <- getModificationUTCTime object_filename let !linkable = LM o_time this_mod [DotO object_filename] + -- See Note [ModDetails and --make mode] + details <- initModDetails hsc_env' summary iface return $! HomeModInfo iface details (Just linkable) where dflags0 = ms_hspp_opts summary @@ -712,7 +714,7 @@ runPipeline -> PipelineOutput -- ^ Output filename -> Maybe ModLocation -- ^ A ModLocation, if this is a Haskell module -> [FilePath] -- ^ foreign objects - -> IO (DynFlags, FilePath, Maybe (ModIface, ModDetails)) + -> IO (DynFlags, FilePath, Maybe ModIface) -- ^ (final flags, output filename, interface) runPipeline stop_phase hsc_env0 (input_fn, mb_input_buf, mb_phase) mb_basename output maybe_loc foreign_os @@ -842,7 +844,7 @@ runPipeline' -> FilePath -- ^ Input filename -> Maybe ModLocation -- ^ A ModLocation, if this is a Haskell module -> [FilePath] -- ^ foreign objects, if we have one - -> IO (DynFlags, FilePath, Maybe (ModIface, ModDetails)) + -> IO (DynFlags, FilePath, Maybe ModIface) -- ^ (final flags, output filename, interface) runPipeline' start_phase hsc_env env input_fn maybe_loc foreign_os @@ -1374,7 +1376,6 @@ runPhase (HscOut src_flavour mod_name result) _ = do return (RealPhase StopLn, o_file) HscRecomp { hscs_guts = cgguts, hscs_mod_location = mod_location, - hscs_mod_details = mod_details, hscs_partial_iface = partial_iface, hscs_old_iface_hash = mb_old_iface_hash } @@ -1387,12 +1388,7 @@ runPhase (HscOut src_flavour mod_name result) _ = do let dflags = hsc_dflags hsc_env' final_iface <- liftIO (mkFullIface hsc_env' partial_iface (Just cg_infos)) - let final_mod_details - | gopt Opt_OmitInterfacePragmas dflags - = mod_details - | otherwise = {-# SCC updateModDetailsIdInfos #-} - updateModDetailsIdInfos cg_infos mod_details - setIface final_iface final_mod_details + setIface final_iface -- See Note [Writing interface files] liftIO $ hscMaybeWriteIface logger dflags False final_iface mb_old_iface_hash mod_location diff --git a/compiler/GHC/Driver/Pipeline/Monad.hs b/compiler/GHC/Driver/Pipeline/Monad.hs index 4a33543527..d95f9a3973 100644 --- a/compiler/GHC/Driver/Pipeline/Monad.hs +++ b/compiler/GHC/Driver/Pipeline/Monad.hs @@ -27,7 +27,6 @@ import GHC.Utils.TmpFs (TempFileLifetime) import GHC.Types.SourceFile import GHC.Unit.Module -import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModIface import GHC.Unit.Module.Status @@ -82,7 +81,7 @@ data PipeState = PipeState { -- ^ additional object files resulting from compiling foreign -- code. They come from two sources: foreign stubs, and -- add{C,Cxx,Objc,Objcxx}File from template haskell - iface :: Maybe (ModIface, ModDetails) + iface :: Maybe ModIface -- ^ Interface generated by HscOut phase. Only available after the -- phase runs. } @@ -90,7 +89,7 @@ data PipeState = PipeState { pipeStateDynFlags :: PipeState -> DynFlags pipeStateDynFlags = hsc_dflags . hsc_env -pipeStateModIface :: PipeState -> Maybe (ModIface, ModDetails) +pipeStateModIface :: PipeState -> Maybe ModIface pipeStateModIface = iface data PipelineOutput @@ -139,5 +138,5 @@ setForeignOs :: [FilePath] -> CompPipeline () setForeignOs os = P $ \_env state -> return (state{ foreign_os = os }, ()) -setIface :: ModIface -> ModDetails -> CompPipeline () -setIface iface details = P $ \_env state -> return (state{ iface = Just (iface, details) }, ()) +setIface :: ModIface -> CompPipeline () +setIface iface = P $ \_env state -> return (state{ iface = Just iface }, ()) diff --git a/compiler/GHC/Iface/UpdateIdInfos.hs b/compiler/GHC/Iface/UpdateIdInfos.hs deleted file mode 100644 index 0c70b5caeb..0000000000 --- a/compiler/GHC/Iface/UpdateIdInfos.hs +++ /dev/null @@ -1,160 +0,0 @@ -{-# LANGUAGE CPP, BangPatterns, Strict, RecordWildCards #-} - -module GHC.Iface.UpdateIdInfos - ( updateModDetailsIdInfos - ) where - -import GHC.Prelude - -import GHC.Core -import GHC.Core.InstEnv - -import GHC.StgToCmm.Types (CgInfos (..)) - -import GHC.Types.Id -import GHC.Types.Id.Info -import GHC.Types.Name.Env -import GHC.Types.Name.Set -import GHC.Types.Var -import GHC.Types.TypeEnv -import GHC.Types.TyThing - -import GHC.Unit.Module.ModDetails - -import GHC.Utils.Misc -import GHC.Utils.Outputable -import GHC.Utils.Panic - -#include "HsVersions.h" - --- | Update CafInfos and LFInfos of all occurrences (in rules, unfoldings, class --- instances). --- --- See Note [Conveying CAF-info and LFInfo between modules] in --- GHC.StgToCmm.Types. -updateModDetailsIdInfos - :: CgInfos - -> ModDetails -- ^ ModDetails to update - -> ModDetails - -updateModDetailsIdInfos cg_infos mod_details = - let - ModDetails{ md_types = type_env -- for unfoldings - , md_insts = insts - , md_rules = rules - } = mod_details - - -- type TypeEnv = NameEnv TyThing - type_env' = mapNameEnv (updateTyThingIdInfos type_env' cg_infos) type_env - -- NB: Knot-tied! The result, type_env', is passed right back into into - -- updateTyThingIdInfos, so that that occurrences of any Ids (e.g. in - -- IdInfos, etc) can be looked up in the tidied env - - !insts' = strictMap (updateInstIdInfos type_env' cg_infos) insts - !rules' = strictMap (updateRuleIdInfos type_env') rules - in - mod_details{ md_types = type_env' - , md_insts = insts' - , md_rules = rules' - } - --------------------------------------------------------------------------------- --- Rules --------------------------------------------------------------------------------- - -updateRuleIdInfos :: TypeEnv -> CoreRule -> CoreRule -updateRuleIdInfos _ rule@BuiltinRule{} = rule -updateRuleIdInfos type_env Rule{ .. } = Rule { ru_rhs = updateGlobalIds type_env ru_rhs, .. } - --------------------------------------------------------------------------------- --- Instances --------------------------------------------------------------------------------- - -updateInstIdInfos :: TypeEnv -> CgInfos -> ClsInst -> ClsInst -updateInstIdInfos type_env cg_infos = - updateClsInstDFun (updateIdUnfolding type_env . updateIdInfo cg_infos) - --------------------------------------------------------------------------------- --- TyThings --------------------------------------------------------------------------------- - -updateTyThingIdInfos :: TypeEnv -> CgInfos -> TyThing -> TyThing - -updateTyThingIdInfos type_env cg_infos (AnId id) = - AnId (updateIdUnfolding type_env (updateIdInfo cg_infos id)) - -updateTyThingIdInfos _ _ other = other -- AConLike, ATyCon, ACoAxiom - --------------------------------------------------------------------------------- --- Unfoldings --------------------------------------------------------------------------------- - -updateIdUnfolding :: TypeEnv -> Id -> Id -updateIdUnfolding type_env id = - case idUnfolding id of - CoreUnfolding{ .. } -> - setIdUnfolding id CoreUnfolding{ uf_tmpl = updateGlobalIds type_env uf_tmpl, .. } - DFunUnfolding{ .. } -> - setIdUnfolding id DFunUnfolding{ df_args = map (updateGlobalIds type_env) df_args, .. } - _ -> id - --------------------------------------------------------------------------------- --- Expressions --------------------------------------------------------------------------------- - -updateIdInfo :: CgInfos -> Id -> Id -updateIdInfo CgInfos{ cgNonCafs = NonCaffySet non_cafs, cgLFInfos = lf_infos } id = - let - not_caffy = elemNameSet (idName id) non_cafs - mb_lf_info = lookupNameEnv lf_infos (idName id) - - id1 = if not_caffy then setIdCafInfo id NoCafRefs else id - id2 = case mb_lf_info of - Nothing -> id1 - Just lf_info -> setIdLFInfo id1 lf_info - in - id2 - --------------------------------------------------------------------------------- - -updateGlobalIds :: NameEnv TyThing -> CoreExpr -> CoreExpr --- Update occurrences of GlobalIds as directed by 'env' --- The 'env' maps a GlobalId to a version with accurate CAF info --- (and in due course perhaps other back-end-related info) -updateGlobalIds env e = go env e - where - go_id :: NameEnv TyThing -> Id -> Id - go_id env var = - case lookupNameEnv env (varName var) of - Nothing -> var - Just (AnId id) -> id - Just other -> pprPanic "UpdateIdInfos.updateGlobalIds" $ - text "Found a non-Id for Id Name" <+> ppr (varName var) $$ - nest 4 (text "Id:" <+> ppr var $$ - text "TyThing:" <+> ppr other) - - go :: NameEnv TyThing -> CoreExpr -> CoreExpr - go env (Var v) = Var (go_id env v) - go _ e@Lit{} = e - go env (App e1 e2) = App (go env e1) (go env e2) - go env (Lam b e) = assertNotInNameEnv env [b] (Lam b (go env e)) - go env (Let bs e) = Let (go_binds env bs) (go env e) - go env (Case e b ty alts) = - assertNotInNameEnv env [b] (Case (go env e) b ty (map go_alt alts)) - where - go_alt (Alt k bs e) = assertNotInNameEnv env bs (Alt k bs (go env e)) - go env (Cast e c) = Cast (go env e) c - go env (Tick t e) = Tick t (go env e) - go _ e@Type{} = e - go _ e@Coercion{} = e - - go_binds :: NameEnv TyThing -> CoreBind -> CoreBind - go_binds env (NonRec b e) = - assertNotInNameEnv env [b] (NonRec b (go env e)) - go_binds env (Rec prs) = - assertNotInNameEnv env (map fst prs) (Rec (mapSnd (go env) prs)) - --- In `updateGlobaLIds` Names of local binders should not shadow Name of --- globals. This assertion is to check that. -assertNotInNameEnv :: NameEnv a -> [Id] -> b -> b -assertNotInNameEnv env ids x = ASSERT(not (any (\id -> elemNameEnv (idName id) env) ids)) x diff --git a/compiler/GHC/Unit/Module/Status.hs b/compiler/GHC/Unit/Module/Status.hs index 539158fdb1..52938154b4 100644 --- a/compiler/GHC/Unit/Module/Status.hs +++ b/compiler/GHC/Unit/Module/Status.hs @@ -28,7 +28,6 @@ data HscStatus -- ^ Information for the code generator. , hscs_mod_location :: !ModLocation -- ^ Module info - , hscs_mod_details :: !ModDetails , hscs_partial_iface :: !PartialModIface -- ^ Partial interface , hscs_old_iface_hash :: !(Maybe Fingerprint) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 4178b9d0f6..f260600ba5 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -456,7 +456,6 @@ Library GHC.Iface.Tidy.StaticPtrTable GHC.IfaceToCore GHC.Iface.Type - GHC.Iface.UpdateIdInfos GHC.Linker GHC.Linker.Dynamic GHC.Linker.ExtraObj diff --git a/testsuite/tests/ghci.debugger/scripts/print012.stdout b/testsuite/tests/ghci.debugger/scripts/print012.stdout index d7a3489f49..e188a90d0c 100644 --- a/testsuite/tests/ghci.debugger/scripts/print012.stdout +++ b/testsuite/tests/ghci.debugger/scripts/print012.stdout @@ -1,6 +1,6 @@ o = O (_t1::a0) () _t1 :: SafeList Int NonEmpty -o = O (Cons 3 (_t4::SafeList Int y0)) +o = O (Cons 3 (_t4::SafeList Int y10)) () -o = O (Cons 3 (Cons 6 (_t9::SafeList Int y0))) +o = O (Cons 3 (Cons 6 (_t9::SafeList Int y10))) diff --git a/testsuite/tests/ghci/scripts/T10321.stdout b/testsuite/tests/ghci/scripts/T10321.stdout index d74ca959a6..c905982364 100644 --- a/testsuite/tests/ghci/scripts/T10321.stdout +++ b/testsuite/tests/ghci/scripts/T10321.stdout @@ -1 +1 @@ -3 :> 4 :> 5 :> Nil :: Num a => Vec 3 a +3 :> 4 :> 5 :> Nil :: Num b => Vec 3 b diff --git a/testsuite/tests/ghci/scripts/T15872.stdout b/testsuite/tests/ghci/scripts/T15872.stdout index e1aa200425..ae90ea73f2 100644 --- a/testsuite/tests/ghci/scripts/T15872.stdout +++ b/testsuite/tests/ghci/scripts/T15872.stdout @@ -1,11 +1,11 @@ -MkFun :: (a -> b) -> Fun a b +MkFun :: (b -> c) -> Fun b c Fun :: (a ~ 'OP) => * -> * -> * type Fun :: forall (a :: WHICH). (a ~ 'OP) => * -> * -> * data Fun b c where MkFun :: (b -> c) -> Fun b c -- Defined at T15872.hs:11:1 MkFun - :: (a -> b) -> Fun @'OP @{'GHC.Types.Eq# @WHICH @'OP @'OP <>} a b + :: (b -> c) -> Fun @'OP @{'GHC.Types.Eq# @WHICH @'OP @'OP <>} b c Fun :: ((a :: WHICH) ~ ('OP :: WHICH)) => * -> * -> * type role Fun nominal nominal representational representational type Fun :: forall (a :: WHICH). diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout index 9f93304ca9..d15ebb4ce1 100644 --- a/testsuite/tests/ghci/scripts/T4175.stdout +++ b/testsuite/tests/ghci/scripts/T4175.stdout @@ -34,9 +34,9 @@ instance Enum () -- Defined in ‘GHC.Enum’ instance Show () -- Defined in ‘GHC.Show’ instance Read () -- Defined in ‘GHC.Read’ instance Bounded () -- Defined in ‘GHC.Enum’ +data instance B () = MkB -- Defined at T4175.hs:14:15 type instance D () () = Bool -- Defined at T4175.hs:23:10 type instance D Int () = String -- Defined at T4175.hs:20:10 -data instance B () = MkB -- Defined at T4175.hs:14:15 type Maybe :: * -> * data Maybe a = Nothing | Just a -- Defined in ‘GHC.Maybe’ @@ -67,8 +67,8 @@ instance Show Int -- Defined in ‘GHC.Show’ instance Read Int -- Defined in ‘GHC.Read’ instance Bounded Int -- Defined in ‘GHC.Enum’ instance Integral Int -- Defined in ‘GHC.Real’ -type instance D Int () = String -- Defined at T4175.hs:20:10 type instance A Int Int = () -- Defined at T4175.hs:9:15 +type instance D Int () = String -- Defined at T4175.hs:20:10 type Z :: * -> Constraint class Z a -- Defined at T4175.hs:29:1 diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout index 3531825a97..8c6c0ad18b 100644 --- a/testsuite/tests/ghci/scripts/ghci025.stdout +++ b/testsuite/tests/ghci/scripts/ghci025.stdout @@ -11,7 +11,7 @@ class C a b ... c1 :: (C a b, N b) => a -> b c2 :: (C a b, N b, S b) => a -> b -c3 :: C a b => a -> b +c3 :: C a b => a1 -> b c4 :: C a b => a1 -> b -- imported via Control.Monad type MonadPlus :: (* -> *) -> Constraint @@ -66,7 +66,7 @@ class C a b ... c1 :: (C a b, N b) => a -> b c2 :: (C a b, N b, S b) => a -> b -c3 :: C a b => a -> b +c3 :: C a b => a1 -> b c4 :: C a b => a1 -> b :browse! T -- with -fprint-explicit-foralls -- defined locally @@ -80,7 +80,7 @@ class C a b ... c1 :: forall a b. (C a b, N b) => a -> b c2 :: forall a b. (C a b, N b, S b) => a -> b -c3 :: forall a b a. C a b => a -> b +c3 :: forall a b a1. C a b => a1 -> b c4 :: forall a b a1. C a b => a1 -> b -- test :browse! <target> relative to different contexts :browse! Ghci025C -- from *Ghci025C> diff --git a/testsuite/tests/ghci/scripts/ghci064.stdout b/testsuite/tests/ghci/scripts/ghci064.stdout index 0fa911e351..b3437226ca 100644 --- a/testsuite/tests/ghci/scripts/ghci064.stdout +++ b/testsuite/tests/ghci/scripts/ghci064.stdout @@ -29,8 +29,8 @@ instance [safe] MyShow w => MyShow [w] instance Monoid [T] -- Defined in ‘GHC.Base’ instance Semigroup [T] -- Defined in ‘GHC.Base’ instance GHC.Generics.Generic [T] -- Defined in ‘GHC.Generics’ -instance [safe] MyShow [T] -- Defined at ghci064.hs:8:10 instance [safe] MyShow [T] -- Defined at ghci064.hs:16:10 +instance [safe] MyShow [T] -- Defined at ghci064.hs:8:10 instance Eq Bool -- Defined in ‘GHC.Classes’ instance Ord Bool -- Defined in ‘GHC.Classes’ instance Enum Bool -- Defined in ‘GHC.Enum’ diff --git a/testsuite/tests/indexed-types/should_fail/Over.stderr b/testsuite/tests/indexed-types/should_fail/Over.stderr index 3e0bc44b57..c53dcb9e06 100644 --- a/testsuite/tests/indexed-types/should_fail/Over.stderr +++ b/testsuite/tests/indexed-types/should_fail/Over.stderr @@ -1,10 +1,10 @@ -OverB.hs:7:15: error: +OverD.hs:1:1: error: Conflicting family instance declarations: - C [Int] [a] -- Defined at OverB.hs:7:15 - C [a] [Int] -- Defined at OverC.hs:7:15 + OverA.D [Int] [a] = Int -- Defined in module OverB + OverA.D [a] [Int] = Char -- Defined in module OverC -OverB.hs:9:15: error: +OverD.hs:1:1: error: Conflicting family instance declarations: - OverA.D [Int] [a] = Int -- Defined at OverB.hs:9:15 - OverA.D [a] [Int] = Char -- Defined at OverC.hs:9:15 + C [Int] [a] -- Defined in module OverB + C [a] [Int] -- Defined in module OverC diff --git a/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr b/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr index 99a3377eb0..e58159ac60 100644 --- a/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr +++ b/testsuite/tests/indexed-types/should_fail/OverDirectThisMod.stderr @@ -1,10 +1,10 @@ -OverDirectThisModB.hs:7:15: error: +OverDirectThisModC.hs:1:1: error: Conflicting family instance declarations: - C [Int] [a] -- Defined at OverDirectThisModB.hs:7:15 - C [a] [Int] -- Defined at OverDirectThisModC.hs:10:15 + D [Int] [a] = Int -- Defined in module OverDirectThisModB + D [a] [Int] = Char -- Defined at OverDirectThisModC.hs:12:15 -OverDirectThisModB.hs:9:15: error: +OverDirectThisModC.hs:1:1: error: Conflicting family instance declarations: - D [Int] [a] = Int -- Defined at OverDirectThisModB.hs:9:15 - D [a] [Int] = Char -- Defined at OverDirectThisModC.hs:12:15 + C [Int] [a] -- Defined in module OverDirectThisModB + C [a] [Int] -- Defined at OverDirectThisModC.hs:10:15 diff --git a/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr b/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr index af136704db..c413a79038 100644 --- a/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr +++ b/testsuite/tests/indexed-types/should_fail/OverIndirectThisMod.stderr @@ -1,10 +1,10 @@ -OverIndirectThisModB.hs:7:15: error: +OverIndirectThisModD.hs:1:1: error: Conflicting family instance declarations: - C [Int] [a] -- Defined at OverIndirectThisModB.hs:7:15 - C [a] [Int] -- Defined at OverIndirectThisModD.hs:11:15 + D [Int] [a] = Int -- Defined in module OverIndirectThisModB + D [a] [Int] = Char -- Defined at OverIndirectThisModD.hs:13:15 -OverIndirectThisModB.hs:9:15: error: +OverIndirectThisModD.hs:1:1: error: Conflicting family instance declarations: - D [Int] [a] = Int -- Defined at OverIndirectThisModB.hs:9:15 - D [a] [Int] = Char -- Defined at OverIndirectThisModD.hs:13:15 + C [Int] [a] -- Defined in module OverIndirectThisModB + C [a] [Int] -- Defined at OverIndirectThisModD.hs:11:15 diff --git a/testsuite/tests/simplCore/should_compile/T18013.stderr b/testsuite/tests/simplCore/should_compile/T18013.stderr index 45640d9ebc..abcf710083 100644 --- a/testsuite/tests/simplCore/should_compile/T18013.stderr +++ b/testsuite/tests/simplCore/should_compile/T18013.stderr @@ -104,7 +104,7 @@ Rule fired: Class op $p1Applicative (BUILTIN) Rule fired: Class op >>= (BUILTIN) Rule fired: Class op >>= (BUILTIN) Rule fired: Class op pure (BUILTIN) -Rule fired: mkRule @(_, ()) (T18013a) +Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) @@ -116,7 +116,7 @@ Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) -Rule fired: mkRule @(_, ()) (T18013a) +Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) Rule fired: mkRule @((), _) (T18013a) Rule fired: Class op fmap (BUILTIN) diff --git a/testsuite/tests/typecheck/should_fail/T6018fail.stderr b/testsuite/tests/typecheck/should_fail/T6018fail.stderr index 152823c80e..78a92e7d1b 100644 --- a/testsuite/tests/typecheck/should_fail/T6018fail.stderr +++ b/testsuite/tests/typecheck/should_fail/T6018fail.stderr @@ -4,18 +4,6 @@ [4 of 5] Compiling T6018Dfail ( T6018Dfail.hs, T6018Dfail.o ) [5 of 5] Compiling T6018fail ( T6018fail.hs, T6018fail.o ) -T6018Afail.hs:9:15: error: - Type family equation right-hand sides overlap; this violates - the family's injectivity annotation: - G Char Bool Int = Int -- Defined at T6018Afail.hs:9:15 - G Bool Int Char = Int -- Defined at T6018fail.hs:17:15 - -T6018Cfail.hs:8:15: error: - Type family equation right-hand sides overlap; this violates - the family's injectivity annotation: - T6018Bfail.H Char Bool Int = Int -- Defined at T6018Cfail.hs:8:15 - T6018Bfail.H Bool Int Char = Int -- Defined at T6018Dfail.hs:7:15 - T6018fail.hs:15:15: error: Type family equation right-hand sides overlap; this violates the family's injectivity annotation: @@ -166,3 +154,15 @@ T6018fail.hs:136:1: error: but these LHS type and kind patterns are not bare variables: ‘*’, ‘Char’ FC Char a = a -- Defined at T6018fail.hs:136:1 + +module T6018Cfail: error: + Type family equation right-hand sides overlap; this violates + the family's injectivity annotation: + T6018Bfail.H Char Bool Int = Int -- Defined in module T6018Cfail + T6018Bfail.H Bool Int Char = Int -- Defined in module T6018Dfail + +module T6018Afail: error: + Type family equation right-hand sides overlap; this violates + the family's injectivity annotation: + G Char Bool Int = Int -- Defined in module T6018Afail + G Bool Int Char = Int -- Defined at T6018fail.hs:17:15 |