diff options
author | Takenobu Tani <takenobu.hs@gmail.com> | 2020-05-27 22:43:46 +0900 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-06-01 06:39:05 -0400 |
commit | 11390e3ab038a18c2a7bf6b2423657614a439afb (patch) | |
tree | eccde174cd2054fd87e89da0f6aa5eac2f1dd744 | |
parent | 7002d0cbbe1581dd157b530e95c62195f37cfe00 (diff) | |
download | haskell-11390e3ab038a18c2a7bf6b2423657614a439afb.tar.gz |
Clean up file paths for new module hierarchy
This updates comments only.
This patch replaces file references according to new module hierarchy.
See also:
* https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular
* https://gitlab.haskell.org/ghc/ghc/issues/13009
40 files changed, 51 insertions, 51 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs index f51e3b3a68..12930e04c1 100644 --- a/compiler/GHC.hs +++ b/compiler/GHC.hs @@ -1346,7 +1346,7 @@ getNameToInstancesIndex visible_mods mods_to_load = do -- ----------------------------------------------------------------------------- -{- ToDo: Move the primary logic here to compiler/main/Packages.hs +{- ToDo: Move the primary logic here to compiler/GHC/Unit/State.hs -- | Return all /external/ modules available in the package database. -- Modules from the current session (i.e., from the 'HomePackageTable') are -- not included. This includes module names which are reexported by packages. diff --git a/compiler/GHC/Cmm/Utils.hs b/compiler/GHC/Cmm/Utils.hs index e81ccafb71..9679f4f311 100644 --- a/compiler/GHC/Cmm/Utils.hs +++ b/compiler/GHC/Cmm/Utils.hs @@ -542,7 +542,7 @@ toBlockListEntryFirst g -- have both true and false successors. Block ordering can make a big difference -- in performance in the LLVM backend. Note that we rely crucially on the order -- of successors returned for CmmCondBranch by the NonLocal instance for CmmNode --- defined in cmm/CmmNode.hs. -GBM +-- defined in GHC/Cmm/Node.hs. -GBM toBlockListEntryFirstFalseFallthrough :: CmmGraph -> [CmmBlock] toBlockListEntryFirstFalseFallthrough g | mapNull m = [] diff --git a/compiler/GHC/CmmToAsm/SPARC/Base.hs b/compiler/GHC/CmmToAsm/SPARC/Base.hs index a7929081b3..bf71c172df 100644 --- a/compiler/GHC/CmmToAsm/SPARC/Base.hs +++ b/compiler/GHC/CmmToAsm/SPARC/Base.hs @@ -3,7 +3,7 @@ -- Also import the required constants, so we know what we're using. -- -- In the interests of cross-compilation, we want to free ourselves --- from the autoconf generated modules like main/Constants +-- from the autoconf generated modules like GHC/Settings/Constants module GHC.CmmToAsm.SPARC.Base ( wordLength, diff --git a/compiler/GHC/Core/Coercion/Opt.hs b/compiler/GHC/Core/Coercion/Opt.hs index e8a276e9ed..5b53936354 100644 --- a/compiler/GHC/Core/Coercion/Opt.hs +++ b/compiler/GHC/Core/Coercion/Opt.hs @@ -866,7 +866,7 @@ False) and that all is OK. But, all is not OK: we want to use the first branch of the axiom in this case, not the second. The problem is that the parameters of the first branch can unify with the supplied coercions, thus meaning that the first branch should be taken. See also Note [Apartness] in -types/FamInstEnv.hs. +GHC/Core/FamInstEnv.hs. Note [Why call checkAxInstCo during optimisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/GHC/Core/InstEnv.hs b/compiler/GHC/Core/InstEnv.hs index ef05747920..424a94e965 100644 --- a/compiler/GHC/Core/InstEnv.hs +++ b/compiler/GHC/Core/InstEnv.hs @@ -674,7 +674,7 @@ in this case by a little known `optimization' that was disabled in an instance declaration. In this case, it silently inserts the `C [a]', and everything happens to work out. -(See `basicTypes/MkId:mkDictFunId' for the code in question. Search for +(See `GHC/Types/Id/Make:mkDictFunId' for the code in question. Search for `Mark Jones', although Mark claims no credit for the `optimization' in question, and would rather it stopped being called the `Mark Jones optimization' ;-) diff --git a/compiler/GHC/Core/Opt/ConstantFold.hs b/compiler/GHC/Core/Opt/ConstantFold.hs index 470b920e94..cc4324c536 100644 --- a/compiler/GHC/Core/Opt/ConstantFold.hs +++ b/compiler/GHC/Core/Opt/ConstantFold.hs @@ -1552,7 +1552,7 @@ match_inline (Type _ : e : _) match_inline _ = Nothing --- See Note [magicDictId magic] in `basicTypes/MkId.hs` +-- See Note [magicDictId magic] in `GHC/Types/Id/Make.hs` -- for a description of what is going on here. match_magicDict :: [Expr CoreBndr] -> Maybe (Expr CoreBndr) match_magicDict [Type _, Var wrap `App` Type a `App` Type _ `App` f, x, y ] diff --git a/compiler/GHC/Core/TyCo/Tidy.hs b/compiler/GHC/Core/TyCo/Tidy.hs index 8ec4b5818b..4674a0a2fe 100644 --- a/compiler/GHC/Core/TyCo/Tidy.hs +++ b/compiler/GHC/Core/TyCo/Tidy.hs @@ -146,7 +146,7 @@ tidyType env (CoercionTy co) = CoercionTy $! (tidyCo env co) -- The following two functions differ from mkForAllTys and splitForAllTys in that --- they expect/preserve the ArgFlag argument. These belong to types/Type.hs, but +-- they expect/preserve the ArgFlag argument. These belong to GHC/Core/Type.hs, but -- how should they be named? mkForAllTys' :: [(TyCoVar, ArgFlag)] -> Type -> Type mkForAllTys' tvvs ty = foldr strictMkForAllTy ty tvvs diff --git a/compiler/GHC/Core/TyCon.hs b/compiler/GHC/Core/TyCon.hs index fdff076567..1dc54f47bc 100644 --- a/compiler/GHC/Core/TyCon.hs +++ b/compiler/GHC/Core/TyCon.hs @@ -1372,7 +1372,7 @@ although it's probably true that we could merge some of these. Roughly in order of "includes more information": - - A Width (cmm/CmmType) is simply a binary value with the specified + - A Width (GHC/Cmm/Type) is simply a binary value with the specified number of bits. It may represent a signed or unsigned integer, a floating-point value, or an address. diff --git a/compiler/GHC/Core/Unfold.hs b/compiler/GHC/Core/Unfold.hs index f19d89ed59..ebfdaabea1 100644 --- a/compiler/GHC/Core/Unfold.hs +++ b/compiler/GHC/Core/Unfold.hs @@ -991,7 +991,7 @@ binary sizes shrink significantly either. Note [Discounts and thresholds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Constants for discounts and thesholds are defined in main/DynFlags, +Constants for discounts and thesholds are defined in GHC/Driver/Session, all of form ufXxxx. They are: ufCreationThreshold diff --git a/compiler/GHC/HsToCore/PmCheck/Oracle.hs b/compiler/GHC/HsToCore/PmCheck/Oracle.hs index 633bfea12d..b2a4587b1b 100644 --- a/compiler/GHC/HsToCore/PmCheck/Oracle.hs +++ b/compiler/GHC/HsToCore/PmCheck/Oracle.hs @@ -1276,7 +1276,7 @@ for all other cases, apart from EmptyCase). This gave rise to #10746. Instead, we do the following: 1. We normalise the outermost type family redex, data family redex or newtype, - using pmTopNormaliseType (in types/FamInstEnv.hs). This computes 3 + using pmTopNormaliseType (in GHC/Core/FamInstEnv.hs). This computes 3 things: (a) A normalised type src_ty, which is equal to the type of the scrutinee in source Haskell (does not normalise newtypes or data families) @@ -1291,7 +1291,7 @@ we do the following: newtype rewrite performed in (b). For an example see also Note [Type normalisation] - in types/FamInstEnv.hs. + in GHC/Core/FamInstEnv.hs. 2. Function Check.checkEmptyCase' performs the check: - If core_ty is not an algebraic type, then we cannot check for diff --git a/compiler/GHC/HsToCore/PmCheck/Types.hs b/compiler/GHC/HsToCore/PmCheck/Types.hs index 310786b01c..8740c9acdb 100644 --- a/compiler/GHC/HsToCore/PmCheck/Types.hs +++ b/compiler/GHC/HsToCore/PmCheck/Types.hs @@ -271,7 +271,7 @@ The impact of this treatment of overloaded literals is the following: * We have instant equality check for overloaded literals (we do not rely on the term oracle which is rather expensive, both in terms of performance and memory). This significantly improves the performance of functions `covered` - `uncovered` and `divergent` in deSugar/Check.hs and effectively addresses + `uncovered` and `divergent` in GHC/HsToCore/PmCheck.hs and effectively addresses #11161. * The warnings issued are simpler. diff --git a/compiler/GHC/Iface/Ext/Ast.hs b/compiler/GHC/Iface/Ext/Ast.hs index ea0643351c..c50514ffe1 100644 --- a/compiler/GHC/Iface/Ext/Ast.hs +++ b/compiler/GHC/Iface/Ext/Ast.hs @@ -200,7 +200,7 @@ call and just recurse directly in to the subexpressions. -} --- These synonyms match those defined in main/GHC.hs +-- These synonyms match those defined in compiler/GHC.hs type RenamedSource = ( HsGroup GhcRn, [LImportDecl GhcRn] , Maybe [(LIE GhcRn, Avails)] , Maybe LHsDocString ) diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs index 63b6b33734..32df13d1ef 100644 --- a/compiler/GHC/Iface/Type.hs +++ b/compiler/GHC/Iface/Type.hs @@ -187,7 +187,7 @@ mkIfaceForAllTvBndr :: ArgFlag -> IfaceTvBndr -> IfaceForAllBndr mkIfaceForAllTvBndr vis var = Bndr (IfaceTvBndr var) vis -- | Build the 'tyConKind' from the binders and the result kind. --- Keep in sync with 'mkTyConKind' in types/TyCon. +-- Keep in sync with 'mkTyConKind' in GHC/Core/TyCon. mkIfaceTyConKind :: [IfaceTyConBinder] -> IfaceKind -> IfaceKind mkIfaceTyConKind bndrs res_kind = foldr mk res_kind bndrs where diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x index 7606dd3f9e..72f88e8018 100644 --- a/compiler/GHC/Parser/Lexer.x +++ b/compiler/GHC/Parser/Lexer.x @@ -119,7 +119,7 @@ import GHC.Parser.Annotation -- ----------------------------------------------------------------------------- -- Alex "Character set macros" --- NB: The logic behind these definitions is also reflected in basicTypes/Lexeme.hs +-- NB: The logic behind these definitions is also reflected in GHC/Utils/Lexeme.hs -- Any changes here should likely be reflected there. $unispace = \x05 -- Trick Alex into handling Unicode. See [Unicode in Alex]. $nl = [\n\r\f] @@ -2261,7 +2261,7 @@ adjustChar c = fromIntegral $ ord adj_c -- with the actual character value hidden in the state. | otherwise = -- NB: The logic behind these definitions is also reflected - -- in basicTypes/Lexeme.hs + -- in GHC/Utils/Lexeme.hs -- Any changes here should likely be reflected there. case generalCategory c of diff --git a/compiler/GHC/Runtime/Interpreter.hs b/compiler/GHC/Runtime/Interpreter.hs index b261a2b690..3229d003f6 100644 --- a/compiler/GHC/Runtime/Interpreter.hs +++ b/compiler/GHC/Runtime/Interpreter.hs @@ -166,7 +166,7 @@ Other Notes on Remote GHCi ~~~~~~~~~~~~~~~~~~~~~~~~~~ * This wiki page has an implementation overview: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/external-interpreter - * Note [External GHCi pointers] in compiler/ghci/GHCi.hs + * Note [External GHCi pointers] in compiler/GHC/Runtime/Interpreter.hs * Note [Remote Template Haskell] in libraries/ghci/GHCi/TH.hs -} diff --git a/compiler/GHC/StgToCmm/Expr.hs b/compiler/GHC/StgToCmm/Expr.hs index b05da01d1b..3605b96149 100644 --- a/compiler/GHC/StgToCmm/Expr.hs +++ b/compiler/GHC/StgToCmm/Expr.hs @@ -902,7 +902,7 @@ cgIdApp fun_id args = do -- -- Self-recursive tail calls can be optimized into a local jump in the same -- way as let-no-escape bindings (see Note [What is a non-escaping let] in --- stgSyn/CoreToStg.hs). Consider this: +-- GHC/CoreToStg.hs). Consider this: -- -- foo.info: -- a = R1 // calling convention diff --git a/compiler/GHC/StgToCmm/Utils.hs b/compiler/GHC/StgToCmm/Utils.hs index 0660c6dd75..3fb18f0ea8 100644 --- a/compiler/GHC/StgToCmm/Utils.hs +++ b/compiler/GHC/StgToCmm/Utils.hs @@ -241,7 +241,7 @@ emitRtsCallGen res lbl args safe -- here, as we don't have liveness information. And really, we -- shouldn't be doing the workaround at this point in the pipeline, see -- Note [Register parameter passing] and the ToDo on CmmCall in --- cmm/CmmNode.hs. Right now the workaround is to avoid inlining across +-- GHC/Cmm/Node.hs. Right now the workaround is to avoid inlining across -- unsafe foreign calls in rewriteAssignments, but this is strictly -- temporary. callerSaveVolatileRegs :: DynFlags -> (CmmAGraph, CmmAGraph) diff --git a/compiler/GHC/SysTools/ExtraObj.hs b/compiler/GHC/SysTools/ExtraObj.hs index 46081df98c..1f1d8fd3d6 100644 --- a/compiler/GHC/SysTools/ExtraObj.hs +++ b/compiler/GHC/SysTools/ExtraObj.hs @@ -155,7 +155,7 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do -- ALL generated assembly must have this section to disable -- executable stacks. See also - -- compiler/nativeGen/AsmCodeGen.hs for another instance + -- compiler/GHC/CmmToAsm.hs for another instance -- where we need to do this. if platformHasGnuNonexecStack platform then text ".section .note.GNU-stack,\"\"," diff --git a/compiler/GHC/Tc/Deriv.hs b/compiler/GHC/Tc/Deriv.hs index eca079ed23..7819a8712e 100644 --- a/compiler/GHC/Tc/Deriv.hs +++ b/compiler/GHC/Tc/Deriv.hs @@ -452,7 +452,7 @@ makeDerivSpecs deriv_infos deriv_decls -- | Process the derived classes in a single @deriving@ clause. deriveClause :: TyCon -> [(Name, TcTyVar)] -- Scoped type variables taken from tcTyConScopedTyVars - -- See Note [Scoped tyvars in a TcTyCon] in types/TyCon + -- See Note [Scoped tyvars in a TcTyCon] in GHC/Core/TyCon -> Maybe (LDerivStrategy GhcRn) -> [LHsSigType GhcRn] -> SDoc -> TcM [EarlyDerivSpec] diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs index b6fb65df88..556b251f4c 100644 --- a/compiler/GHC/ThToHs.hs +++ b/compiler/GHC/ThToHs.hs @@ -2041,7 +2041,7 @@ specially in `GHC.HsToCore.Quote`, `GHC.ThToHs`, and (where ty is the AST representation of t1 -> t2 -> ... -> tn -> t) (b) When converting pattern synonyms from TH.Dec to HsSyn in - `hsSyn/Convert.hs`, we convert their TH type signatures back to an + `GHC/ThToHs.hs`, we convert their TH type signatures back to an appropriate Haskell pattern synonym type of the form forall univs. reqs => forall exis. provs => t1 -> t2 -> ... -> tn -> t diff --git a/compiler/GHC/Utils/Outputable.hs b/compiler/GHC/Utils/Outputable.hs index 149713773d..9827e53f9e 100644 --- a/compiler/GHC/Utils/Outputable.hs +++ b/compiler/GHC/Utils/Outputable.hs @@ -1005,7 +1005,7 @@ pprHsBytes bs = let escaped = concatMap escape $ BS.unpack bs else '\\' : show w -- Postfix modifiers for unboxed literals. --- See Note [Printing of literals in Core] in `basicTypes/Literal.hs`. +-- See Note [Printing of literals in Core] in `GHC/Types/Literal.hs`. primCharSuffix, primFloatSuffix, primIntSuffix :: SDoc primDoubleSuffix, primWordSuffix, primInt64Suffix, primWord64Suffix :: SDoc primCharSuffix = char '#' diff --git a/compiler/GHC/Utils/Ppr.hs b/compiler/GHC/Utils/Ppr.hs index 559088e415..96e1328ff7 100644 --- a/compiler/GHC/Utils/Ppr.hs +++ b/compiler/GHC/Utils/Ppr.hs @@ -21,7 +21,7 @@ ----------------------------------------------------------------------------- {- -Note [Differences between libraries/pretty and compiler/utils/Pretty.hs] +Note [Differences between libraries/pretty and compiler/GHC/Utils/Ppr.hs] For historical reasons, there are two different copies of `Pretty` in the GHC source tree: @@ -29,7 +29,7 @@ source tree: https://github.com/haskell/pretty. This is the `pretty` library as released on hackage. It is used by several other libraries in the GHC source tree (e.g. template-haskell and Cabal). - * `compiler/utils/Pretty.hs` (this module). It is used by GHC only. + * `compiler/GHC/Utils/Ppr.hs` (this module). It is used by GHC only. There is an ongoing effort in https://github.com/haskell/pretty/issues/1 and https://gitlab.haskell.org/ghc/ghc/issues/10735 to try to get rid of GHC's copy @@ -49,7 +49,7 @@ ghc git tree: $ cd libraries/pretty $ git checkout v1.1.2.0 $ cd - - $ vimdiff compiler/utils/Pretty.hs \ + $ vimdiff compiler/GHC/Utils/Ppr.hs \ libraries/pretty/src/Text/PrettyPrint/HughesPJ.hs For parity with `pretty-1.1.2.1`, the following two `pretty` commits would diff --git a/compiler/ghc.mk b/compiler/ghc.mk index 6e86b73e8d..05a6d9def1 100644 --- a/compiler/ghc.mk +++ b/compiler/ghc.mk @@ -102,8 +102,8 @@ $(eval $(call compilerConfig,1)) $(eval $(call compilerConfig,2)) # ---------------------------------------------------------------------------- -# Generate supporting stuff for prelude/PrimOp.hs -# from prelude/primops.txt +# Generate supporting stuff for GHC/Builtin/PrimOps.hs +# from GHC/Builtin/primops.txt PRIMOP_BITS_NAMES = primop-data-decl.hs-incl \ primop-tag.hs-incl \ diff --git a/hadrian/src/Way.hs b/hadrian/src/Way.hs index 2375a122a7..99aa7e28a9 100644 --- a/hadrian/src/Way.hs +++ b/hadrian/src/Way.hs @@ -27,7 +27,7 @@ dynamic = wayFromUnits [Dynamic] profilingDynamic :: Way profilingDynamic = wayFromUnits [Profiling, Dynamic] --- RTS only ways below. See compiler/main/DynFlags.hs. +-- RTS only ways below. See compiler/GHC/Driver/Session.hs. -- | Build RTS with event logging. logging :: Way logging = wayFromUnits [Logging] diff --git a/includes/CodeGen.Platform.hs b/includes/CodeGen.Platform.hs index c8f4ee1c69..2ae86d303b 100644 --- a/includes/CodeGen.Platform.hs +++ b/includes/CodeGen.Platform.hs @@ -925,7 +925,7 @@ freeReg 13 = False -- reserved for system thread ID on 64 bit freeReg 30 = False {- TODO: reserve r13 on 64 bit systems only and r30 on 32 bit respectively. For now we use r30 on 64 bit and r13 on 32 bit as a temporary register - in stack handling code. See compiler/nativeGen/PPC/Instr.hs. + in stack handling code. See compiler/GHC/CmmToAsm/PPC/Instr.hs. Later we might want to reserve r13 and r30 only where it is required. Then use r12 as temporary register, which is also what the C ABI does. diff --git a/includes/stg/MachRegs.h b/includes/stg/MachRegs.h index ea1125bbf8..82cce6e66a 100644 --- a/includes/stg/MachRegs.h +++ b/includes/stg/MachRegs.h @@ -341,7 +341,7 @@ the stack. See Note [Overlapping global registers] for implications. The Sun SPARC register mapping !! IMPORTANT: if you change this register mapping you must also update - compiler/nativeGen/SPARC/Regs.hs. That file handles the + compiler/GHC/CmmToAsm/SPARC/Regs.hs. That file handles the mapping for the NCG. This one only affects via-c code. The SPARC register (window) story: Remember, within the Haskell diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index b95cec7505..b496bac35e 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -319,7 +319,7 @@ mechanism to define mconcat and the Applicative and Monad instances for lists. We mark them INLINE because the inliner is not generally too keen to inline build forms such as the ones these desugar to without our insistence. Defining these using list comprehensions instead of foldr has an additional potential -benefit, as described in compiler/deSugar/DsListComp.hs: if optimizations +benefit, as described in compiler/GHC/HsToCore/ListComp.hs: if optimizations needed to make foldr/build forms efficient are turned off, we'll get reasonably efficient translations anyway. -} diff --git a/libraries/ghci/GHCi/Message.hs b/libraries/ghci/GHCi/Message.hs index b7c402ccfa..ad94776a9f 100644 --- a/libraries/ghci/GHCi/Message.hs +++ b/libraries/ghci/GHCi/Message.hs @@ -6,7 +6,7 @@ -- Remote GHCi message types and serialization. -- -- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/ghci/GHCi.hs. +-- compiler/GHC/Runtime/Interpreter.hs. -- module GHCi.Message ( Message(..), Msg(..) @@ -83,7 +83,7 @@ data Message a where -- | Create a set of BCO objects, and return HValueRefs to them -- Note: Each ByteString contains a Binary-encoded [ResolvedBCO], not -- a ResolvedBCO. The list is to allow us to serialise the ResolvedBCOs - -- in parallel. See @createBCOs@ in compiler/ghci/GHCi.hsc. + -- in parallel. See @createBCOs@ in compiler/GHC/Runtime/Interpreter.hs. CreateBCOs :: [LB.ByteString] -> Message [HValueRef] -- | Release 'HValueRef's diff --git a/libraries/ghci/GHCi/RemoteTypes.hs b/libraries/ghci/GHCi/RemoteTypes.hs index 6a552f37da..bbd7d32bed 100644 --- a/libraries/ghci/GHCi/RemoteTypes.hs +++ b/libraries/ghci/GHCi/RemoteTypes.hs @@ -2,10 +2,10 @@ -- | -- Types for referring to remote objects in Remote GHCi. For more --- details, see Note [External GHCi pointers] in compiler/ghci/GHCi.hs +-- details, see Note [External GHCi pointers] in compiler/GHC/Runtime/Interpreter.hs -- -- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/ghci/GHCi.hs. +-- compiler/GHC/Runtime/Interpreter.hs. -- module GHCi.RemoteTypes ( RemotePtr(..), toRemotePtr, fromRemotePtr, castRemotePtr diff --git a/libraries/ghci/GHCi/Run.hs b/libraries/ghci/GHCi/Run.hs index ab55502f8e..b34ba1553f 100644 --- a/libraries/ghci/GHCi/Run.hs +++ b/libraries/ghci/GHCi/Run.hs @@ -6,7 +6,7 @@ -- Execute GHCi messages. -- -- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/ghci/GHCi.hs. +-- compiler/GHC/Runtime/Interpreter.hs. -- module GHCi.Run ( run, redirectInterrupts diff --git a/libraries/ghci/GHCi/TH.hs b/libraries/ghci/GHCi/TH.hs index 15d70ceb4f..56e38c0244 100644 --- a/libraries/ghci/GHCi/TH.hs +++ b/libraries/ghci/GHCi/TH.hs @@ -85,8 +85,8 @@ The server runs any finalizers that were added by addModuleFinalizer. Other Notes on TH / Remote GHCi - * Note [Remote GHCi] in compiler/ghci/GHCi.hs - * Note [External GHCi pointers] in compiler/ghci/GHCi.hs + * Note [Remote GHCi] in compiler/GHC/Runtime/Interpreter.hs + * Note [External GHCi pointers] in compiler/GHC/Runtime/Interpreter.hs * Note [TH recover with -fexternal-interpreter] in GHC.Tc.Gen.Splice -} diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index d994aa686d..53d9aabb7d 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -2256,7 +2256,7 @@ data Foreign = ImportF Callconv Safety String Name Type | ExportF Callconv String Name Type deriving( Show, Eq, Ord, Data, Generic ) --- keep Callconv in sync with module ForeignCall in ghc/compiler/prelude/ForeignCall.hs +-- keep Callconv in sync with module ForeignCall in ghc/compiler/GHC/Types/ForeignCall.hs data Callconv = CCall | StdCall | CApi | Prim | JavaScript deriving( Show, Eq, Ord, Data, Generic ) diff --git a/mk/config.mk.in b/mk/config.mk.in index 250d41ebe6..ef2ee685ab 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -912,6 +912,6 @@ endif # Note [Disable -O2 in unregisterised mode] # Disable -O2 optimization in unregisterised mode. Otherwise amount # of generated C code # makes things very slow to compile (~5 minutes -# on core-i7 for 'compiler/hsSyn/HsExpr.hs') and sometimes not compile -# at all: powerpc64 overflows TOC section on 'compiler/hsSyn/HsExpr.hs' -# ia64 overflows short data section on 'compiler/main/DynFlags.hs' +# on core-i7 for 'compiler/GHC/Hs/Expr.hs') and sometimes not compile +# at all: powerpc64 overflows TOC section on 'compiler/GHC/Hs/Expr.hs' +# ia64 overflows short data section on 'compiler/GHC/Driver/Session.hs' diff --git a/rts/Interpreter.c b/rts/Interpreter.c index 463ddae18b..b7575b3051 100644 --- a/rts/Interpreter.c +++ b/rts/Interpreter.c @@ -290,7 +290,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 main/GHC.hs:runStmt + // it is set in compiler/GHC.hs:runStmt Capability * interpretBCO (Capability* cap) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 090f915035..1bd30b3af0 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -13,7 +13,7 @@ * * Entry convention: the entry convention for a primop is the * NativeNodeCall convention, and the return convention is - * NativeReturn. (see compiler/cmm/CmmCallConv.hs) + * NativeReturn. (see compiler/GHC/Cmm/CallConv.hs) * * This file is written in a subset of C--, extended with various * features specific to GHC. It is compiled by GHC directly. For the diff --git a/rts/RtsStartup.c b/rts/RtsStartup.c index a628a8633b..f73d0bd742 100644 --- a/rts/RtsStartup.c +++ b/rts/RtsStartup.c @@ -70,7 +70,7 @@ static void flushStdHandles(void); /* ----------------------------------------------------------------------------- Initialise floating point unit on x86 (currently disabled; See Note - [x86 Floating point precision] in compiler/nativeGen/X86/Instr.hs) + [x86 Floating point precision] in compiler/GHC/CmmToAsm/X86/Instr.hs) -------------------------------------------------------------------------- */ #define X86_INIT_FPU 0 diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 55a3bf0c2d..316d90cd18 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -151,7 +151,7 @@ STG_NO_OPTIMIZE StgWord8 *win32AllocStack(void) * procedure entry and calls, which led to bugs (see #4211 and #5250). * * To change this convention you need to change the code here, and in - * compiler/nativeGen/X86/CodeGen.hs::GenCCall, and maybe the adjustor + * compiler/GHC/CmmToAsm/X86/CodeGen.hs::GenCCall, and maybe the adjustor * code for thunks in rts/AdjustorAsm.s, rts/Adjustor.c. * * A quick way to see if this is wrong is to compile this code: @@ -395,7 +395,7 @@ StgRunIsImplementedInAssembler(void) #if defined(mingw32_HOST_OS) /* * Additional callee saved registers on Win64. This must match - * callClobberedRegisters in compiler/nativeGen/X86/Regs.hs as + * callClobberedRegisters in compiler/GHC/CmmToAsm/X86/Regs.hs as * both represent the Win64 calling convention. */ "movq %%rdi,48(%%rax)\n\t" diff --git a/rts/StgMiscClosures.cmm b/rts/StgMiscClosures.cmm index 5af3a06b89..85c1ad398e 100644 --- a/rts/StgMiscClosures.cmm +++ b/rts/StgMiscClosures.cmm @@ -504,7 +504,7 @@ CLOSURE(stg_NO_TREC_closure,stg_NO_TREC); /* ---------------------------------------------------------------------------- SRTs - See Note [SRTs] in compiler/cmm/CmmBuildInfoTable.hs + See Note [SRTs] in compiler/GHC/Cmm/Info/Build.hs ------------------------------------------------------------------------- */ INFO_TABLE_CONSTR(stg_SRT_1, 1, 0, 0, CONSTR_1_0, "SRT_1", "SRT_1") diff --git a/rules/sdist-ghc-file.mk b/rules/sdist-ghc-file.mk index 81e1c5c105..b1e13a1ea0 100644 --- a/rules/sdist-ghc-file.mk +++ b/rules/sdist-ghc-file.mk @@ -16,7 +16,7 @@ # $(eval $(call sdist-ghc-file,compiler,stage2,parser,Parser,y)) # # This adds the file 'compiler/stage2/build/Parser.hs' to the sdist, in the -# same directory as 'compiler/parser/Parser.y' (which is renamed). +# same directory as 'compiler/GHC/Parser.y' (which is renamed). define sdist-ghc-file # $1 = dir diff --git a/utils/iserv/src/Main.hs b/utils/iserv/src/Main.hs index 15ea9f5030..6915552f91 100644 --- a/utils/iserv/src/Main.hs +++ b/utils/iserv/src/Main.hs @@ -4,7 +4,7 @@ -- The Remote GHCi server. -- -- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/ghci/GHCi.hs. +-- compiler/GHC/Runtime/Interpreter.hs. -- module Main (main) where |