summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2019-09-11 21:19:39 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-09-20 05:14:34 -0400
commit5119296440e6846c553c72b8a93afc5ecfa576f0 (patch)
treeff508560a4996afffb24bf3af5dfa9c56a7e5c77
parent4853d962289db1b32886ec73e824cd37c9c5c002 (diff)
downloadhaskell-5119296440e6846c553c72b8a93afc5ecfa576f0.tar.gz
Module hierarchy: Hs (#13009)
Add GHC.Hs module hierarchy replacing hsSyn. Metric Increase: haddock.compiler
-rw-r--r--compiler/GHC/Hs.hs (renamed from compiler/hsSyn/HsSyn.hs)50
-rw-r--r--compiler/GHC/Hs/Binds.hs (renamed from compiler/hsSyn/HsBinds.hs)18
-rw-r--r--compiler/GHC/Hs/Decls.hs (renamed from compiler/hsSyn/HsDecls.hs)20
-rw-r--r--compiler/GHC/Hs/Doc.hs (renamed from compiler/hsSyn/HsDoc.hs)2
-rw-r--r--compiler/GHC/Hs/Dump.hs (renamed from compiler/hsSyn/HsDumpAst.hs)6
-rw-r--r--compiler/GHC/Hs/Expr.hs (renamed from compiler/hsSyn/HsExpr.hs)24
-rw-r--r--compiler/GHC/Hs/Expr.hs-boot (renamed from compiler/hsSyn/HsExpr.hs-boot)8
-rw-r--r--compiler/GHC/Hs/Extension.hs (renamed from compiler/hsSyn/HsExtension.hs)10
-rw-r--r--compiler/GHC/Hs/ImpExp.hs (renamed from compiler/hsSyn/HsImpExp.hs)14
-rw-r--r--compiler/GHC/Hs/Instances.hs (renamed from compiler/hsSyn/HsInstances.hs)32
-rw-r--r--compiler/GHC/Hs/Lit.hs (renamed from compiler/hsSyn/HsLit.hs)10
-rw-r--r--compiler/GHC/Hs/Pat.hs (renamed from compiler/hsSyn/HsPat.hs)20
-rw-r--r--compiler/GHC/Hs/Pat.hs-boot (renamed from compiler/hsSyn/HsPat.hs-boot)6
-rw-r--r--compiler/GHC/Hs/PlaceHolder.hs (renamed from compiler/hsSyn/PlaceHolder.hs)2
-rw-r--r--compiler/GHC/Hs/Types.hs (renamed from compiler/hsSyn/HsTypes.hs)24
-rw-r--r--compiler/GHC/Hs/Utils.hs (renamed from compiler/hsSyn/HsUtils.hs)20
-rw-r--r--compiler/GHC/ThToHs.hs (renamed from compiler/hsSyn/Convert.hs)19
-rw-r--r--compiler/backpack/BkpSyn.hs2
-rw-r--r--compiler/basicTypes/BasicTypes.hs2
-rw-r--r--compiler/coreSyn/CoreSyn.hs6
-rw-r--r--compiler/coreSyn/MkCore.hs2
-rw-r--r--compiler/deSugar/Check.hs4
-rw-r--r--compiler/deSugar/Coverage.hs2
-rw-r--r--compiler/deSugar/Desugar.hs2
-rw-r--r--compiler/deSugar/DsArrows.hs12
-rw-r--r--compiler/deSugar/DsBinds.hs6
-rw-r--r--compiler/deSugar/DsExpr.hs2
-rw-r--r--compiler/deSugar/DsExpr.hs-boot4
-rw-r--r--compiler/deSugar/DsForeign.hs2
-rw-r--r--compiler/deSugar/DsGRHSs.hs2
-rw-r--r--compiler/deSugar/DsListComp.hs2
-rw-r--r--compiler/deSugar/DsMeta.hs2
-rw-r--r--compiler/deSugar/DsMonad.hs2
-rw-r--r--compiler/deSugar/DsUtils.hs4
-rw-r--r--compiler/deSugar/ExtractDocs.hs12
-rw-r--r--compiler/deSugar/Match.hs2
-rw-r--r--compiler/deSugar/Match.hs-boot4
-rw-r--r--compiler/deSugar/MatchCon.hs2
-rw-r--r--compiler/deSugar/MatchLit.hs2
-rw-r--r--compiler/ghc.cabal.in31
-rw-r--r--compiler/hieFile/HieAst.hs2
-rw-r--r--compiler/iface/MkIface.hs2
-rw-r--r--compiler/main/GHC.hs4
-rw-r--r--compiler/main/GhcPlugins.hs2
-rw-r--r--compiler/main/HeaderInfo.hs2
-rw-r--r--compiler/main/Hooks.hs8
-rw-r--r--compiler/main/HscMain.hs4
-rw-r--r--compiler/main/HscStats.hs2
-rw-r--r--compiler/main/HscTypes.hs2
-rw-r--r--compiler/main/InteractiveEval.hs2
-rw-r--r--compiler/main/Plugins.hs2
-rw-r--r--compiler/parser/HaddockUtils.hs2
-rw-r--r--compiler/parser/Parser.y4
-rw-r--r--compiler/parser/RdrHsSyn.hs22
-rw-r--r--compiler/rename/RnBinds.hs4
-rw-r--r--compiler/rename/RnEnv.hs2
-rw-r--r--compiler/rename/RnExpr.hs4
-rw-r--r--compiler/rename/RnExpr.hs-boot2
-rw-r--r--compiler/rename/RnFixity.hs2
-rw-r--r--compiler/rename/RnHsDoc.hs2
-rw-r--r--compiler/rename/RnNames.hs4
-rw-r--r--compiler/rename/RnPat.hs6
-rw-r--r--compiler/rename/RnSource.hs6
-rw-r--r--compiler/rename/RnSplice.hs2
-rw-r--r--compiler/rename/RnSplice.hs-boot2
-rw-r--r--compiler/rename/RnTypes.hs6
-rw-r--r--compiler/rename/RnUtils.hs2
-rw-r--r--compiler/stgSyn/StgSyn.hs6
-rw-r--r--compiler/typecheck/Inst.hs4
-rw-r--r--compiler/typecheck/TcAnnotations.hs2
-rw-r--r--compiler/typecheck/TcArrows.hs4
-rw-r--r--compiler/typecheck/TcBackpack.hs2
-rw-r--r--compiler/typecheck/TcBinds.hs2
-rw-r--r--compiler/typecheck/TcCanonical.hs2
-rw-r--r--compiler/typecheck/TcClassDcl.hs2
-rw-r--r--compiler/typecheck/TcDefaults.hs2
-rw-r--r--compiler/typecheck/TcDeriv.hs2
-rw-r--r--compiler/typecheck/TcDerivUtils.hs2
-rw-r--r--compiler/typecheck/TcEnv.hs4
-rw-r--r--compiler/typecheck/TcErrors.hs4
-rw-r--r--compiler/typecheck/TcExpr.hs6
-rw-r--r--compiler/typecheck/TcExpr.hs-boot4
-rw-r--r--compiler/typecheck/TcForeign.hs2
-rw-r--r--compiler/typecheck/TcGenDeriv.hs2
-rw-r--r--compiler/typecheck/TcGenFunctor.hs2
-rw-r--r--compiler/typecheck/TcGenGenerics.hs2
-rw-r--r--compiler/typecheck/TcHoleErrors.hs2
-rw-r--r--compiler/typecheck/TcHoleFitTypes.hs2
-rw-r--r--compiler/typecheck/TcHsSyn.hs2
-rw-r--r--compiler/typecheck/TcHsType.hs14
-rw-r--r--compiler/typecheck/TcInstDcls.hs2
-rw-r--r--compiler/typecheck/TcInstDcls.hs-boot2
-rw-r--r--compiler/typecheck/TcMatches.hs6
-rw-r--r--compiler/typecheck/TcMatches.hs-boot4
-rw-r--r--compiler/typecheck/TcPat.hs2
-rw-r--r--compiler/typecheck/TcPatSyn.hs2
-rw-r--r--compiler/typecheck/TcPatSyn.hs-boot4
-rw-r--r--compiler/typecheck/TcRnDriver.hs4
-rw-r--r--compiler/typecheck/TcRnExports.hs2
-rw-r--r--compiler/typecheck/TcRnMonad.hs2
-rw-r--r--compiler/typecheck/TcRnTypes.hs2
-rw-r--r--compiler/typecheck/TcRules.hs2
-rw-r--r--compiler/typecheck/TcSigs.hs2
-rw-r--r--compiler/typecheck/TcSimplify.hs2
-rw-r--r--compiler/typecheck/TcSplice.hs6
-rw-r--r--compiler/typecheck/TcSplice.hs-boot6
-rw-r--r--compiler/typecheck/TcTyClsDecls.hs4
-rw-r--r--compiler/typecheck/TcTyDecls.hs2
-rw-r--r--compiler/typecheck/TcTypeable.hs2
-rw-r--r--compiler/typecheck/TcUnify.hs2
-rw-r--r--compiler/typecheck/TcUnify.hs-boot12
-rw-r--r--compiler/typecheck/TcValidity.hs2
-rw-r--r--compiler/types/TyCon.hs2
-rw-r--r--compiler/types/Type.hs6
-rw-r--r--docs/users_guide/extending_ghc.rst10
-rw-r--r--ghc/GHCi/UI.hs4
-rw-r--r--ghc/GHCi/UI/Monad.hs4
m---------nofib0
-rw-r--r--testsuite/tests/ghc-api/annotations/stringSource.hs2
-rw-r--r--testsuite/tests/ghc-api/annotations/t11430.hs2
-rw-r--r--testsuite/tests/package/all.T2
-rw-r--r--testsuite/tests/package/package05.hs6
-rw-r--r--testsuite/tests/package/package06.hs4
-rw-r--r--testsuite/tests/package/package06e.hs2
-rw-r--r--testsuite/tests/package/package06e.stderr2
-rw-r--r--testsuite/tests/package/package07e.hs6
-rw-r--r--testsuite/tests/package/package07e.stderr8
-rw-r--r--testsuite/tests/package/package08e.hs6
-rw-r--r--testsuite/tests/package/package08e.stderr8
-rw-r--r--testsuite/tests/parser/should_fail/readFail001.hs2
-rw-r--r--testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs8
-rw-r--r--testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs10
-rw-r--r--testsuite/tests/plugins/static-plugins.hs10
-rw-r--r--testsuite/tests/pmcheck/should_compile/pmc009.hs2
-rw-r--r--utils/check-ppr/Main.hs2
m---------utils/haddock0
136 files changed, 381 insertions, 377 deletions
diff --git a/compiler/hsSyn/HsSyn.hs b/compiler/GHC/Hs.hs
index 622f1b9c77..aa345f1476 100644
--- a/compiler/hsSyn/HsSyn.hs
+++ b/compiler/GHC/Hs.hs
@@ -13,23 +13,23 @@ therefore, is almost nothing but re-exporting.
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-} -- For deriving instance Data
-module HsSyn (
- module HsBinds,
- module HsDecls,
- module HsExpr,
- module HsImpExp,
- module HsLit,
- module HsPat,
- module HsTypes,
- module HsUtils,
- module HsDoc,
- module PlaceHolder,
- module HsExtension,
+module GHC.Hs (
+ module GHC.Hs.Binds,
+ module GHC.Hs.Decls,
+ module GHC.Hs.Expr,
+ module GHC.Hs.ImpExp,
+ module GHC.Hs.Lit,
+ module GHC.Hs.Pat,
+ module GHC.Hs.Types,
+ module GHC.Hs.Utils,
+ module GHC.Hs.Doc,
+ module GHC.Hs.PlaceHolder,
+ module GHC.Hs.Extension,
Fixity,
HsModule(..),
@@ -38,19 +38,19 @@ module HsSyn (
-- friends:
import GhcPrelude
-import HsDecls
-import HsBinds
-import HsExpr
-import HsImpExp
-import HsLit
-import PlaceHolder
-import HsExtension
-import HsPat
-import HsTypes
+import GHC.Hs.Decls
+import GHC.Hs.Binds
+import GHC.Hs.Expr
+import GHC.Hs.ImpExp
+import GHC.Hs.Lit
+import GHC.Hs.PlaceHolder
+import GHC.Hs.Extension
+import GHC.Hs.Pat
+import GHC.Hs.Types
import BasicTypes ( Fixity, WarningTxt )
-import HsUtils
-import HsDoc
-import HsInstances () -- For Data instances
+import GHC.Hs.Utils
+import GHC.Hs.Doc
+import GHC.Hs.Instances () -- For Data instances
-- others:
import Outputable
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/GHC/Hs/Binds.hs
index 4be761e3ac..01c10b1ea1 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/GHC/Hs/Binds.hs
@@ -12,22 +12,22 @@ Datatype for: @BindGroup@, @Bind@, @Sig@, @Bind@.
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeFamilies #-}
-module HsBinds where
+module GHC.Hs.Binds where
import GhcPrelude
-import {-# SOURCE #-} HsExpr ( pprExpr, LHsExpr,
- MatchGroup, pprFunBind,
- GRHSs, pprPatBind )
-import {-# SOURCE #-} HsPat ( LPat )
+import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, LHsExpr,
+ MatchGroup, pprFunBind,
+ GRHSs, pprPatBind )
+import {-# SOURCE #-} GHC.Hs.Pat ( LPat )
-import HsExtension
-import HsTypes
+import GHC.Hs.Extension
+import GHC.Hs.Types
import CoreSyn
import TcEvidence
import Type
@@ -223,7 +223,7 @@ data HsBindLR idL idR
-- free variables of this defn.
-- See Note [Bind free vars]
- fun_id :: Located (IdP idL), -- Note [fun_id in Match] in HsExpr
+ fun_id :: Located (IdP idL), -- Note [fun_id in Match] in GHC.Hs.Expr
fun_matches :: MatchGroup idR (LHsExpr idR), -- ^ The payload
diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/GHC/Hs/Decls.hs
index 3cac82ed2f..701c8b1a06 100644
--- a/compiler/hsSyn/HsDecls.hs
+++ b/compiler/GHC/Hs/Decls.hs
@@ -8,7 +8,7 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
@@ -16,7 +16,7 @@
--
-- Definitions for: @SynDecl@ and @ConDecl@, @ClassDecl@,
-- @InstDecl@, @DefaultDecl@ and @ForeignDecl@.
-module HsDecls (
+module GHC.Hs.Decls (
-- * Toplevel declarations
HsDecl(..), LHsDecl, HsDataDefn(..), HsDeriving, LHsFunDep,
HsDerivingClause(..), LHsDerivingClause, NewOrData(..), newOrDataToFlavour,
@@ -88,18 +88,18 @@ module HsDecls (
-- friends:
import GhcPrelude
-import {-# SOURCE #-} HsExpr( HsExpr, HsSplice, pprExpr,
- pprSpliceDecl )
+import {-# SOURCE #-} GHC.Hs.Expr( HsExpr, HsSplice, pprExpr,
+ pprSpliceDecl )
-- Because Expr imports Decls via HsBracket
-import HsBinds
-import HsTypes
-import HsDoc
+import GHC.Hs.Binds
+import GHC.Hs.Types
+import GHC.Hs.Doc
import TyCon
import BasicTypes
import Coercion
import ForeignCall
-import HsExtension
+import GHC.Hs.Extension
import NameSet
-- others:
@@ -388,7 +388,7 @@ Default methods
E.g. $dmmax
- If there is a default method name at all, it's recorded in
- the ClassOpSig (in HsBinds), in the DefMethInfo field.
+ the ClassOpSig (in GHC.Hs.Binds), in the DefMethInfo field.
(DefMethInfo is defined in Class.hs)
Source-code class decls and interface-code class decls are treated subtly
@@ -1370,7 +1370,7 @@ There's a wrinkle in ConDeclGADT
con_res_ty = T a
We need the RecCon before the reanmer, so we can find the record field
- binders in HsUtils.hsConDeclsBinders.
+ binders in GHC.Hs.Utils.hsConDeclsBinders.
* However for a GADT constr declaration which is not a record, it can
be hard parse until we know operator fixities. Consider for example
diff --git a/compiler/hsSyn/HsDoc.hs b/compiler/GHC/Hs/Doc.hs
index affbf1bac0..18a820fa6e 100644
--- a/compiler/hsSyn/HsDoc.hs
+++ b/compiler/GHC/Hs/Doc.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-module HsDoc
+module GHC.Hs.Doc
( HsDocString
, LHsDocString
, mkHsDocString
diff --git a/compiler/hsSyn/HsDumpAst.hs b/compiler/GHC/Hs/Dump.hs
index 1a1c259c01..5bdfc8668e 100644
--- a/compiler/hsSyn/HsDumpAst.hs
+++ b/compiler/GHC/Hs/Dump.hs
@@ -5,11 +5,11 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
--- | Contains a debug function to dump parts of the hsSyn AST. It uses a syb
+-- | Contains a debug function to dump parts of the GHC.Hs AST. It uses a syb
-- traversal which falls back to displaying based on the constructor name, so
-- can be used to dump anything having a @Data.Data@ instance.
-module HsDumpAst (
+module GHC.Hs.Dump (
-- * Dumping ASTs
showAstData,
BlankSrcSpan(..),
@@ -25,7 +25,7 @@ import NameSet
import Name
import DataCon
import SrcLoc
-import HsSyn
+import GHC.Hs
import OccName hiding (occName)
import Var
import Module
diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/GHC/Hs/Expr.hs
index 69379bc1ad..2ea1ae3f73 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -7,27 +7,27 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}
-- | Abstract Haskell syntax for expressions.
-module HsExpr where
+module GHC.Hs.Expr where
#include "HsVersions.h"
-- friends:
import GhcPrelude
-import HsDecls
-import HsPat
-import HsLit
-import PlaceHolder ( NameOrRdrName )
-import HsExtension
-import HsTypes
-import HsBinds
+import GHC.Hs.Decls
+import GHC.Hs.Pat
+import GHC.Hs.Lit
+import GHC.Hs.PlaceHolder ( NameOrRdrName )
+import GHC.Hs.Extension
+import GHC.Hs.Types
+import GHC.Hs.Binds
-- others:
import TcEvidence
@@ -629,7 +629,7 @@ data HsExpr p
-- Finally, HsWrap appears only in typechecker output
-- The contained Expr is *NOT* itself an HsWrap.
-- See Note [Detecting forced eta expansion] in DsExpr. This invariant
- -- is maintained by HsUtils.mkHsWrap.
+ -- is maintained by GHC.Hs.Utils.mkHsWrap.
| HsWrap (XWrap p)
HsWrapper -- TRANSLATION
@@ -1630,12 +1630,12 @@ pprMatches MG { mg_alts = matches }
-- Don't print the type; it's only a place-holder before typechecking
pprMatches (XMatchGroup x) = ppr x
--- Exported to HsBinds, which can't see the defn of HsMatchContext
+-- Exported to GHC.Hs.Binds, which can't see the defn of HsMatchContext
pprFunBind :: (OutputableBndrId (GhcPass idR), Outputable body)
=> MatchGroup (GhcPass idR) body -> SDoc
pprFunBind matches = pprMatches matches
--- Exported to HsBinds, which can't see the defn of HsMatchContext
+-- Exported to GHC.Hs.Binds, which can't see the defn of HsMatchContext
pprPatBind :: forall bndr p body. (OutputableBndrId (GhcPass bndr),
OutputableBndrId (GhcPass p),
Outputable body)
diff --git a/compiler/hsSyn/HsExpr.hs-boot b/compiler/GHC/Hs/Expr.hs-boot
index 109e9814e5..8fd8f3857a 100644
--- a/compiler/hsSyn/HsExpr.hs-boot
+++ b/compiler/GHC/Hs/Expr.hs-boot
@@ -1,19 +1,19 @@
{-# LANGUAGE CPP, KindSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeFamilies #-}
-module HsExpr where
+module GHC.Hs.Expr where
import SrcLoc ( Located )
import Outputable ( SDoc, Outputable )
-import {-# SOURCE #-} HsPat ( LPat )
+import {-# SOURCE #-} GHC.Hs.Pat ( LPat )
import BasicTypes ( SpliceExplicitFlag(..))
-import HsExtension ( OutputableBndrId, GhcPass )
+import GHC.Hs.Extension ( OutputableBndrId, GhcPass )
type role HsExpr nominal
type role HsCmd nominal
diff --git a/compiler/hsSyn/HsExtension.hs b/compiler/GHC/Hs/Extension.hs
index c486ad8a11..f360e1c32e 100644
--- a/compiler/hsSyn/HsExtension.hs
+++ b/compiler/GHC/Hs/Extension.hs
@@ -11,17 +11,17 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
-module HsExtension where
+module GHC.Hs.Extension where
-- This module captures the type families to precisely identify the extension
--- points for HsSyn
+-- points for GHC.Hs syntax
import GhcPrelude
import Data.Data hiding ( Fixity )
-import PlaceHolder
+import GHC.Hs.PlaceHolder
import Name
import RdrName
import Var
@@ -152,7 +152,7 @@ type instance IdP GhcTc = Id
type LIdP p = Located (IdP p)
-- | Marks that a field uses the GhcRn variant even when the pass
--- parameter is GhcTc. Useful for storing HsTypes in HsExprs, say, because
+-- parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because
-- HsType GhcTc should never occur.
type family NoGhcTc (p :: Type) where
-- this way, GHC can figure out that the result is a GhcPass
diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/GHC/Hs/ImpExp.hs
index bedb74e05d..56d1691ac4 100644
--- a/compiler/hsSyn/HsImpExp.hs
+++ b/compiler/GHC/Hs/ImpExp.hs
@@ -3,7 +3,7 @@
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-HsImpExp: Abstract syntax: imports, exports, interfaces
+GHC.Hs.ImpExp: Abstract syntax: imports, exports, interfaces
-}
{-# LANGUAGE DeriveDataTypeable #-}
@@ -11,14 +11,14 @@ HsImpExp: Abstract syntax: imports, exports, interfaces
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
-module HsImpExp where
+module GHC.Hs.ImpExp where
import GhcPrelude
import Module ( ModuleName )
-import HsDoc ( HsDocString )
+import GHC.Hs.Doc ( HsDocString )
import OccName ( HasOccName(..), isTcOcc, isSymOcc )
import BasicTypes ( SourceText(..), StringLiteral(..), pprWithSourceText )
import FieldLabel ( FieldLbl(..) )
@@ -26,7 +26,7 @@ import FieldLabel ( FieldLbl(..) )
import Outputable
import FastString
import SrcLoc
-import HsExtension
+import GHC.Hs.Extension
import Data.Data
import Data.Maybe
@@ -213,7 +213,7 @@ data IE pass
-- 'ApiAnnotation.AnnType','ApiAnnotation.AnnVal'
-- For details on above see note [Api annotations] in ApiAnnotation
- -- See Note [Located RdrNames] in HsExpr
+ -- See Note [Located RdrNames] in GHC.Hs.Expr
| IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass))
-- ^ Imported or exported Thing with All imported or exported
--
@@ -224,7 +224,7 @@ data IE pass
-- 'ApiAnnotation.AnnType'
-- For details on above see note [Api annotations] in ApiAnnotation
- -- See Note [Located RdrNames] in HsExpr
+ -- See Note [Located RdrNames] in GHC.Hs.Expr
| IEThingWith (XIEThingWith pass)
(LIEWrappedName (IdP pass))
diff --git a/compiler/hsSyn/HsInstances.hs b/compiler/GHC/Hs/Instances.hs
index 9c0698b7ef..d55e20c2e7 100644
--- a/compiler/hsSyn/HsInstances.hs
+++ b/compiler/GHC/Hs/Instances.hs
@@ -5,7 +5,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-module HsInstances where
+module GHC.Hs.Instances where
-- This module defines the Data instances for the hsSyn AST.
@@ -17,20 +17,20 @@ module HsInstances where
import Data.Data hiding ( Fixity )
import GhcPrelude
-import HsExtension
-import HsBinds
-import HsDecls
-import HsExpr
-import HsLit
-import HsTypes
-import HsPat
-import HsImpExp
+import GHC.Hs.Extension
+import GHC.Hs.Binds
+import GHC.Hs.Decls
+import GHC.Hs.Expr
+import GHC.Hs.Lit
+import GHC.Hs.Types
+import GHC.Hs.Pat
+import GHC.Hs.ImpExp
-- ---------------------------------------------------------------------
--- Data derivations from HsSyn -----------------------------------------
+-- Data derivations from GHC.Hs-----------------------------------------
-- ---------------------------------------------------------------------
--- Data derivations from HsBinds ---------------------------------------
+-- Data derivations from GHC.Hs.Binds ----------------------------------
-- deriving instance (DataIdLR pL pR) => Data (HsLocalBindsLR pL pR)
deriving instance Data (HsLocalBindsLR GhcPs GhcPs)
@@ -92,7 +92,7 @@ deriving instance Data (HsPatSynDir GhcRn)
deriving instance Data (HsPatSynDir GhcTc)
-- ---------------------------------------------------------------------
--- Data derivations from HsDecls ---------------------------------------
+-- Data derivations from GHC.Hs.Decls ----------------------------------
-- deriving instance (DataIdLR p p) => Data (HsDecl p)
deriving instance Data (HsDecl GhcPs)
@@ -235,7 +235,7 @@ deriving instance Data (RoleAnnotDecl GhcRn)
deriving instance Data (RoleAnnotDecl GhcTc)
-- ---------------------------------------------------------------------
--- Data derivations from HsExpr ----------------------------------------
+-- Data derivations from GHC.Hs.Expr -----------------------------------
-- deriving instance (DataIdLR p p) => Data (SyntaxExpr p)
deriving instance Data (SyntaxExpr GhcPs)
@@ -327,7 +327,7 @@ deriving instance Data PendingRnSplice
deriving instance Data PendingTcSplice
-- ---------------------------------------------------------------------
--- Data derivations from HsLit ----------------------------------------
+-- Data derivations from GHC.Hs.Lit ------------------------------------
-- deriving instance (DataId p) => Data (HsLit p)
deriving instance Data (HsLit GhcPs)
@@ -340,7 +340,7 @@ deriving instance Data (HsOverLit GhcRn)
deriving instance Data (HsOverLit GhcTc)
-- ---------------------------------------------------------------------
--- Data derivations from HsPat -----------------------------------------
+-- Data derivations from GHC.Hs.Pat ------------------------------------
-- deriving instance (DataIdLR p p) => Data (Pat p)
deriving instance Data (Pat GhcPs)
@@ -355,7 +355,7 @@ deriving instance (Data body) => Data (HsRecFields GhcRn body)
deriving instance (Data body) => Data (HsRecFields GhcTc body)
-- ---------------------------------------------------------------------
--- Data derivations from HsTypes ---------------------------------------
+-- Data derivations from GHC.Hs.Types ----------------------------------
-- deriving instance (DataIdLR p p) => Data (LHsQTyVars p)
deriving instance Data (LHsQTyVars GhcPs)
diff --git a/compiler/hsSyn/HsLit.hs b/compiler/GHC/Hs/Lit.hs
index 074c7295af..ab30de87ac 100644
--- a/compiler/hsSyn/HsLit.hs
+++ b/compiler/GHC/Hs/Lit.hs
@@ -10,23 +10,23 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
-module HsLit where
+module GHC.Hs.Lit where
#include "HsVersions.h"
import GhcPrelude
-import {-# SOURCE #-} HsExpr( HsExpr, pprExpr )
+import {-# SOURCE #-} GHC.Hs.Expr( HsExpr, pprExpr )
import BasicTypes ( IntegralLit(..),FractionalLit(..),negateIntegralLit,
negateFractionalLit,SourceText(..),pprWithSourceText )
import Type
import Outputable
import FastString
-import HsExtension
+import GHC.Hs.Extension
import Data.ByteString (ByteString)
import Data.Data hiding ( Fixity )
@@ -41,7 +41,7 @@ import Data.Data hiding ( Fixity )
-- Note [Literal source text] in BasicTypes for SourceText fields in
-- the following
--- Note [Trees that grow] in HsExtension for the Xxxxx fields in the following
+-- Note [Trees that grow] in GHC.Hs.Extension for the Xxxxx fields in the following
-- | Haskell Literal
data HsLit x
= HsChar (XHsChar x) {- SourceText -} Char
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/GHC/Hs/Pat.hs
index 06270e8a89..fe8a4e88d5 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/GHC/Hs/Pat.hs
@@ -12,13 +12,13 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
-module HsPat (
+module GHC.Hs.Pat (
Pat(..), InPat, OutPat, LPat,
ListPatTc(..),
@@ -43,13 +43,13 @@ module HsPat (
import GhcPrelude
-import {-# SOURCE #-} HsExpr (SyntaxExpr, LHsExpr, HsSplice, pprLExpr, pprSplice)
+import {-# SOURCE #-} GHC.Hs.Expr (SyntaxExpr, LHsExpr, HsSplice, pprLExpr, pprSplice)
-- friends:
-import HsBinds
-import HsLit
-import HsExtension
-import HsTypes
+import GHC.Hs.Binds
+import GHC.Hs.Lit
+import GHC.Hs.Extension
+import GHC.Hs.Types
import TcEvidence
import BasicTypes
-- others:
@@ -89,7 +89,7 @@ data Pat p
| VarPat (XVarPat p)
(Located (IdP p)) -- ^ Variable Pattern
- -- See Note [Located RdrNames] in HsExpr
+ -- See Note [Located RdrNames] in GHC.Hs.Expr
| LazyPat (XLazyPat p)
(LPat p) -- ^ Lazy Pattern
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
@@ -104,7 +104,7 @@ data Pat p
| ParPat (XParPat p)
(LPat p) -- ^ Parenthesised pattern
- -- See Note [Parens in HsSyn] in HsExpr
+ -- See Note [Parens in HsSyn] in GHC.Hs.Expr
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
-- 'ApiAnnotation.AnnClose' @')'@
@@ -155,7 +155,7 @@ data Pat p
-- 'ApiAnnotation.AnnOpen' @'('@ or @'(#'@,
-- 'ApiAnnotation.AnnClose' @')'@ or @'#)'@
- | SumPat (XSumPat p) -- PlaceHolder before typechecker, filled in
+ | SumPat (XSumPat p) -- GHC.Hs.PlaceHolder before typechecker, filled in
-- afterwards with the types of the
-- alternative
(LPat p) -- Sum sub-pattern
diff --git a/compiler/hsSyn/HsPat.hs-boot b/compiler/GHC/Hs/Pat.hs-boot
index a1067d5dc5..801f481879 100644
--- a/compiler/hsSyn/HsPat.hs-boot
+++ b/compiler/GHC/Hs/Pat.hs-boot
@@ -1,15 +1,15 @@
{-# LANGUAGE CPP, KindSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE TypeFamilies #-}
-module HsPat where
+module GHC.Hs.Pat where
import Outputable
-import HsExtension ( OutputableBndrId, GhcPass )
+import GHC.Hs.Extension ( OutputableBndrId, GhcPass )
type role Pat nominal
data Pat (i :: *)
diff --git a/compiler/hsSyn/PlaceHolder.hs b/compiler/GHC/Hs/PlaceHolder.hs
index 244243a82f..faaa1331ab 100644
--- a/compiler/hsSyn/PlaceHolder.hs
+++ b/compiler/GHC/Hs/PlaceHolder.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
-module PlaceHolder where
+module GHC.Hs.PlaceHolder where
import Name
import NameSet
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/GHC/Hs/Types.hs
index ad9c186c76..f14d59ba4a 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/GHC/Hs/Types.hs
@@ -3,7 +3,7 @@
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-HsTypes: Abstract syntax: user-defined types
+GHC.Hs.Types: Abstract syntax: user-defined types
-}
{-# LANGUAGE DeriveDataTypeable #-}
@@ -12,12 +12,12 @@ HsTypes: Abstract syntax: user-defined types
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
-module HsTypes (
+module GHC.Hs.Types (
HsType(..), NewHsTypeX(..), LHsType, HsKind, LHsKind,
HsTyVarBndr(..), LHsTyVarBndr, ForallVisFlag(..),
LHsQTyVars(..),
@@ -74,9 +74,9 @@ module HsTypes (
import GhcPrelude
-import {-# SOURCE #-} HsExpr ( HsSplice, pprSplice )
+import {-# SOURCE #-} GHC.Hs.Expr ( HsSplice, pprSplice )
-import HsExtension
+import GHC.Hs.Extension
import Id ( Id )
import Name( Name )
@@ -85,7 +85,7 @@ import DataCon( HsSrcBang(..), HsImplBang(..),
SrcStrictness(..), SrcUnpackedness(..) )
import TysPrim( funTyConName )
import Type
-import HsDoc
+import GHC.Hs.Doc
import BasicTypes
import SrcLoc
import Outputable
@@ -489,7 +489,7 @@ data HsTyVarBndr pass
= UserTyVar -- no explicit kinding
(XUserTyVar pass)
(Located (IdP pass))
- -- See Note [Located RdrNames] in HsExpr
+ -- See Note [Located RdrNames] in GHC.Hs.Expr
| KindedTyVar
(XKindedTyVar pass)
(Located (IdP pass))
@@ -542,7 +542,7 @@ data HsType pass
(Located (IdP pass))
-- Type variable, type constructor, or data constructor
-- see Note [Promotions (HsTyVar)]
- -- See Note [Located RdrNames] in HsExpr
+ -- See Note [Located RdrNames] in GHC.Hs.Expr
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in ApiAnnotation
@@ -594,7 +594,7 @@ data HsType pass
-- For details on above see note [Api annotations] in ApiAnnotation
| HsParTy (XParTy pass)
- (LHsType pass) -- See Note [Parens in HsSyn] in HsExpr
+ (LHsType pass) -- See Note [Parens in HsSyn] in GHC.Hs.Expr
-- Parenthesis preserved for the precedence re-arrangement in RnTypes
-- It's important that a * (b + c) doesn't get rearranged to (a*b) + c!
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
@@ -1347,7 +1347,7 @@ type LFieldOcc pass = Located (FieldOcc pass)
-- renamer, the selector function.
data FieldOcc pass = FieldOcc { extFieldOcc :: XCFieldOcc pass
, rdrNameFieldOcc :: Located RdrName
- -- ^ See Note [Located RdrNames] in HsExpr
+ -- ^ See Note [Located RdrNames] in GHC.Hs.Expr
}
| XFieldOcc
@@ -1377,9 +1377,9 @@ mkFieldOcc rdr = FieldOcc noExtField rdr
-- (for unambiguous occurrences) or the typechecker (for ambiguous
-- occurrences).
--
--- See Note [HsRecField and HsRecUpdField] in HsPat and
+-- See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and
-- Note [Disambiguating record fields] in TcExpr.
--- See Note [Located RdrNames] in HsExpr
+-- See Note [Located RdrNames] in GHC.Hs.Expr
data AmbiguousFieldOcc pass
= Unambiguous (XUnambiguous pass) (Located RdrName)
| Ambiguous (XAmbiguous pass) (Located RdrName)
diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/GHC/Hs/Utils.hs
index f3bba0d6a8..5d54196af2 100644
--- a/compiler/hsSyn/HsUtils.hs
+++ b/compiler/GHC/Hs/Utils.hs
@@ -19,7 +19,7 @@ which deal with the instantiated versions are located elsewhere:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
-module HsUtils(
+module GHC.Hs.Utils(
-- Terms
mkHsPar, mkHsApp, mkHsAppType, mkHsAppTypes, mkHsCaseAlt,
mkSimpleMatch, unguardedGRHSs, unguardedRHS,
@@ -93,14 +93,14 @@ module HsUtils(
import GhcPrelude
-import HsDecls
-import HsBinds
-import HsExpr
-import HsPat
-import HsTypes
-import HsLit
-import PlaceHolder
-import HsExtension
+import GHC.Hs.Decls
+import GHC.Hs.Binds
+import GHC.Hs.Expr
+import GHC.Hs.Pat
+import GHC.Hs.Types
+import GHC.Hs.Lit
+import GHC.Hs.PlaceHolder
+import GHC.Hs.Extension
import TcEvidence
import RdrName
@@ -913,7 +913,7 @@ but the local, recursive, monomorphic bindings are:
Here the binding for 'fm' is illegal. So generally we check the abe_mono types.
BUT we have a special case when abs_sig is true;
- see HsBinds Note [The abs_sig field of AbsBinds]
+ see Note [The abs_sig field of AbsBinds] in GHC.Hs.Binds
-}
----------------- Bindings --------------------------
diff --git a/compiler/hsSyn/Convert.hs b/compiler/GHC/ThToHs.hs
index ee6553ce04..ca38d07ddc 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/GHC/ThToHs.hs
@@ -3,7 +3,7 @@
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
-This module converts Template Haskell syntax into HsSyn
+This module converts Template Haskell syntax into Hs syntax
-}
{-# LANGUAGE DeriveFunctor #-}
@@ -12,13 +12,18 @@ This module converts Template Haskell syntax into HsSyn
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
-module Convert( convertToHsExpr, convertToPat, convertToHsDecls,
- convertToHsType,
- thRdrNameGuesses ) where
+module GHC.ThToHs
+ ( convertToHsExpr
+ , convertToPat
+ , convertToHsDecls
+ , convertToHsType
+ , thRdrNameGuesses
+ )
+where
import GhcPrelude
-import HsSyn as Hs
+import GHC.Hs as Hs
import PrelNames
import RdrName
import qualified Name
@@ -941,7 +946,7 @@ cvtl e = wrapL (cvt e)
do { s' <- cvtl s; y' <- cvtl y
; wrapParL (HsPar noExtField) $
SectionR noExtField s' y' }
- -- See Note [Sections in HsSyn] in HsExpr
+ -- See Note [Sections in HsSyn] in GHC.Hs.Expr
cvt (InfixE (Just x) s Nothing ) = ensureValidOpExp s $
do { x' <- cvtl x; s' <- cvtl s
; wrapParL (HsPar noExtField) $
@@ -1928,7 +1933,7 @@ thRdrName. To achieve (b) we want the binders to be Exact RdrNames.
Achieving (a) is a bit awkward, because
- We must check for duplicate and shadowed names on Names,
not RdrNames, *after* renaming.
- See Note [Collect binders only after renaming] in HsUtils
+ See Note [Collect binders only after renaming] in GHC.Hs.Utils
- But to achieve (a) we must distinguish between the Exact
RdrNames arising from TH and the Unqual RdrNames that would
diff --git a/compiler/backpack/BkpSyn.hs b/compiler/backpack/BkpSyn.hs
index 67905c6067..e17c905379 100644
--- a/compiler/backpack/BkpSyn.hs
+++ b/compiler/backpack/BkpSyn.hs
@@ -19,7 +19,7 @@ module BkpSyn (
import GhcPrelude
-import HsSyn
+import GHC.Hs
import SrcLoc
import Outputable
import Module
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index f2d6f2b46a..43ad2cbbba 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -1211,7 +1211,7 @@ data Activation = NeverActive
| ActiveAfter SourceText PhaseNum
-- Active in this phase and later
deriving( Eq, Data )
- -- Eq used in comparing rules in HsDecls
+ -- Eq used in comparing rules in GHC.Hs.Decls
-- | Rule Match Information
data RuleMatchInfo = ConLike -- See Note [CONLIKE pragma]
diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs
index 16123e7b3a..f8fb9ef971 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/coreSyn/CoreSyn.hs
@@ -142,7 +142,7 @@ These data types are the heart of the compiler
-- We get from Haskell source to this Core language in a number of stages:
--
-- 1. The source code is parsed into an abstract syntax tree, which is represented
--- by the data type 'HsExpr.HsExpr' with the names being 'RdrName.RdrNames'
+-- by the data type 'GHC.Hs.Expr.HsExpr' with the names being 'RdrName.RdrNames'
--
-- 2. This syntax tree is /renamed/, which attaches a 'Unique.Unique' to every 'RdrName.RdrName'
-- (yielding a 'Name.Name') to disambiguate identifiers which are lexically identical.
@@ -162,9 +162,9 @@ These data types are the heart of the compiler
-- But see Note [Shadowing] below.
--
-- 3. The resulting syntax tree undergoes type checking (which also deals with instantiating
--- type class arguments) to yield a 'HsExpr.HsExpr' type that has 'Id.Id' as it's names.
+-- type class arguments) to yield a 'GHC.Hs.Expr.HsExpr' type that has 'Id.Id' as it's names.
--
--- 4. Finally the syntax tree is /desugared/ from the expressive 'HsExpr.HsExpr' type into
+-- 4. Finally the syntax tree is /desugared/ from the expressive 'GHC.Hs.Expr.HsExpr' type into
-- this 'Expr' type, which has far fewer constructors and hence is easier to perform
-- optimization, analysis and code generation on.
--
diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs
index f9609f834d..e2c881a1c4 100644
--- a/compiler/coreSyn/MkCore.hs
+++ b/compiler/coreSyn/MkCore.hs
@@ -64,7 +64,7 @@ import HscTypes
import TysWiredIn
import PrelNames
-import HsUtils ( mkChunkified, chunkify )
+import GHC.Hs.Utils ( mkChunkified, chunkify )
import Type
import Coercion ( isCoVar )
import TysPrim
diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index 1c9493bbca..4808b56eae 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -35,7 +35,7 @@ import CoreUtils (exprType)
import FastString (unpackFS)
import Unify( tcMatchTy )
import DynFlags
-import HsSyn
+import GHC.Hs
import TcHsSyn
import Id
import ConLike
@@ -1334,7 +1334,7 @@ available so we can get more precise results. For this reason we have functions
term constraints (respectively) as we go deeper.
The type constraints we propagate inwards are collected by `collectEvVarsPats'
-in HsPat.hs. This handles bug #4139 ( see example
+in GHC.Hs.Pat. This handles bug #4139 ( see example
https://gitlab.haskell.org/ghc/ghc/snippets/672 )
where this is needed.
diff --git a/compiler/deSugar/Coverage.hs b/compiler/deSugar/Coverage.hs
index e587c74121..b7bed75f3d 100644
--- a/compiler/deSugar/Coverage.hs
+++ b/compiler/deSugar/Coverage.hs
@@ -18,7 +18,7 @@ import Data.Array
import ByteCodeTypes
import GHC.Stack.CCS
import Type
-import HsSyn
+import GHC.Hs
import Module
import Outputable
import DynFlags
diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs
index 2c0b4139a6..5df52c3df9 100644
--- a/compiler/deSugar/Desugar.hs
+++ b/compiler/deSugar/Desugar.hs
@@ -22,7 +22,7 @@ import GhcPrelude
import DsUsage
import DynFlags
import HscTypes
-import HsSyn
+import GHC.Hs
import TcRnTypes
import TcRnMonad ( finalSafeMode, fixSafeInstances )
import TcRnDriver ( runTcInteractive )
diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs
index cc12920520..ade017208d 100644
--- a/compiler/deSugar/DsArrows.hs
+++ b/compiler/deSugar/DsArrows.hs
@@ -20,11 +20,11 @@ import Match
import DsUtils
import DsMonad
-import HsSyn hiding (collectPatBinders, collectPatsBinders,
+import GHC.Hs hiding (collectPatBinders, collectPatsBinders,
collectLStmtsBinders, collectLStmtBinders,
collectStmtBinders )
import TcHsSyn
-import qualified HsUtils
+import qualified GHC.Hs.Utils as HsUtils
-- NB: The desugarer, which straddles the source and Core worlds, sometimes
-- needs to see source types (newtypes etc), and sometimes not
@@ -62,7 +62,7 @@ data DsCmdEnv = DsCmdEnv {
}
mkCmdEnv :: CmdSyntaxTable GhcTc -> DsM ([CoreBind], DsCmdEnv)
--- See Note [CmdSyntaxTable] in HsExpr
+-- See Note [CmdSyntaxTable] in GHC.Hs.Expr
mkCmdEnv tc_meths
= do { (meth_binds, prs) <- mapAndUnzipM mk_bind tc_meths
@@ -1191,10 +1191,10 @@ foldb f xs = foldb f (fold_pairs xs)
fold_pairs (x1:x2:xs) = f x1 x2:fold_pairs xs
{-
-Note [Dictionary binders in ConPatOut] See also same Note in HsUtils
+Note [Dictionary binders in ConPatOut] See also same Note in GHC.Hs.Utils
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The following functions to collect value variables from patterns are
-copied from HsUtils, with one change: we also collect the dictionary
+copied from GHC.Hs.Utils, with one change: we also collect the dictionary
bindings (pat_binds) from ConPatOut. We need them for cases like
h :: Arrow a => Int -> a (Int,Int) Int
@@ -1208,7 +1208,7 @@ The type checker turns the case into
Here p77 is a local binding for the (+) operation.
-See comments in HsUtils for why the other version does not include
+See comments in GHC.Hs.Utils for why the other version does not include
these bindings.
-}
diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index cea7f3215b..0d4c868d76 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -31,7 +31,7 @@ import DsGRHSs
import DsUtils
import Check ( needToRunPmCheck, addTyCsDs, checkGuardMatches )
-import HsSyn -- lots of things
+import GHC.Hs -- lots of things
import CoreSyn -- lots of things
import CoreOpt ( simpleOptExpr )
import OccurAnal ( occurAnalyseExpr )
@@ -618,9 +618,9 @@ We define an "unlifted bind" to be any bind that binds an unlifted id. Note that
x :: Char
(# True, x #) = blah
-is *not* an unlifted bind. Unlifted binds are detected by HsUtils.isUnliftedHsBind.
+is *not* an unlifted bind. Unlifted binds are detected by GHC.Hs.Utils.isUnliftedHsBind.
-Define a "banged bind" to have a top-level bang. Detected by HsPat.isBangedHsBind.
+Define a "banged bind" to have a top-level bang. Detected by GHC.Hs.Pat.isBangedHsBind.
Define a "strict bind" to be either an unlifted bind or a banged bind.
The restrictions are:
diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs
index 183b1e7650..1fa2dd8b99 100644
--- a/compiler/deSugar/DsExpr.hs
+++ b/compiler/deSugar/DsExpr.hs
@@ -30,7 +30,7 @@ import Name
import NameEnv
import FamInstEnv( topNormaliseType )
import DsMeta
-import HsSyn
+import GHC.Hs
-- NB: The desugarer, which straddles the source and Core worlds, sometimes
-- needs to see source types
diff --git a/compiler/deSugar/DsExpr.hs-boot b/compiler/deSugar/DsExpr.hs-boot
index 65c4f188fd..54864d5835 100644
--- a/compiler/deSugar/DsExpr.hs-boot
+++ b/compiler/deSugar/DsExpr.hs-boot
@@ -1,8 +1,8 @@
module DsExpr where
-import HsSyn ( HsExpr, LHsExpr, LHsLocalBinds, SyntaxExpr )
+import GHC.Hs ( HsExpr, LHsExpr, LHsLocalBinds, SyntaxExpr )
import DsMonad ( DsM )
import CoreSyn ( CoreExpr )
-import HsExtension ( GhcTc)
+import GHC.Hs.Extension ( GhcTc)
dsExpr :: HsExpr GhcTc -> DsM CoreExpr
dsLExpr, dsLExprNoLP :: LHsExpr GhcTc -> DsM CoreExpr
diff --git a/compiler/deSugar/DsForeign.hs b/compiler/deSugar/DsForeign.hs
index 545f26c3f6..43ef2327c5 100644
--- a/compiler/deSugar/DsForeign.hs
+++ b/compiler/deSugar/DsForeign.hs
@@ -23,7 +23,7 @@ import CoreSyn
import DsCCall
import DsMonad
-import HsSyn
+import GHC.Hs
import DataCon
import CoreUnfold
import Id
diff --git a/compiler/deSugar/DsGRHSs.hs b/compiler/deSugar/DsGRHSs.hs
index b0d35d0b2a..6b7dac41b3 100644
--- a/compiler/deSugar/DsGRHSs.hs
+++ b/compiler/deSugar/DsGRHSs.hs
@@ -18,7 +18,7 @@ import GhcPrelude
import {-# SOURCE #-} DsExpr ( dsLExpr, dsLocalBinds )
import {-# SOURCE #-} Match ( matchSinglePatVar )
-import HsSyn
+import GHC.Hs
import MkCore
import CoreSyn
import CoreUtils (bindNonRec)
diff --git a/compiler/deSugar/DsListComp.hs b/compiler/deSugar/DsListComp.hs
index 9755bf695b..e826045eb5 100644
--- a/compiler/deSugar/DsListComp.hs
+++ b/compiler/deSugar/DsListComp.hs
@@ -18,7 +18,7 @@ import GhcPrelude
import {-# SOURCE #-} DsExpr ( dsExpr, dsLExpr, dsLExprNoLP, dsLocalBinds, dsSyntaxExpr )
-import HsSyn
+import GHC.Hs
import TcHsSyn
import CoreSyn
import MkCore
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index a8d2b7de0f..c37d366d5e 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -30,7 +30,7 @@ import DsMonad
import qualified Language.Haskell.TH as TH
-import HsSyn
+import GHC.Hs
import PrelNames
-- To avoid clashes with DsMeta.varName we must make a local alias for
-- OccName.varName we do this by removing varName from the import of
diff --git a/compiler/deSugar/DsMonad.hs b/compiler/deSugar/DsMonad.hs
index 1bfa25324a..eac17bfea0 100644
--- a/compiler/deSugar/DsMonad.hs
+++ b/compiler/deSugar/DsMonad.hs
@@ -59,7 +59,7 @@ import FamInstEnv
import CoreSyn
import MkCore ( unitExpr )
import CoreUtils ( exprType, isExprLevPoly )
-import HsSyn
+import GHC.Hs
import TcIface
import TcMType ( checkForLevPolyX, formatLevPolyErr )
import PrelNames
diff --git a/compiler/deSugar/DsUtils.hs b/compiler/deSugar/DsUtils.hs
index c4abd16737..7d39b4a3c6 100644
--- a/compiler/deSugar/DsUtils.hs
+++ b/compiler/deSugar/DsUtils.hs
@@ -49,7 +49,7 @@ import GhcPrelude
import {-# SOURCE #-} Match ( matchSimply )
import {-# SOURCE #-} DsExpr ( dsLExpr )
-import HsSyn
+import GHC.Hs
import TcHsSyn
import TcType( tcSplitTyConApp )
import CoreSyn
@@ -747,7 +747,7 @@ is_triv_pat _ = False
* *
Creating big tuples and their types for full Haskell expressions.
They work over *Ids*, and create tuples replete with their types,
- which is whey they are not in HsUtils.
+ which is whey they are not in GHC.Hs.Utils.
* *
********************************************************************* -}
diff --git a/compiler/deSugar/ExtractDocs.hs b/compiler/deSugar/ExtractDocs.hs
index 4d7f115074..33bed3b3f5 100644
--- a/compiler/deSugar/ExtractDocs.hs
+++ b/compiler/deSugar/ExtractDocs.hs
@@ -8,12 +8,12 @@ module ExtractDocs (extractDocs) where
import GhcPrelude
import Bag
-import HsBinds
-import HsDoc
-import HsDecls
-import HsExtension
-import HsTypes
-import HsUtils
+import GHC.Hs.Binds
+import GHC.Hs.Doc
+import GHC.Hs.Decls
+import GHC.Hs.Extension
+import GHC.Hs.Types
+import GHC.Hs.Utils
import Name
import NameSet
import SrcLoc
diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs
index a0576494a0..0049d00613 100644
--- a/compiler/deSugar/Match.hs
+++ b/compiler/deSugar/Match.hs
@@ -21,7 +21,7 @@ import {-#SOURCE#-} DsExpr (dsLExpr, dsSyntaxExpr)
import BasicTypes ( Origin(..) )
import DynFlags
-import HsSyn
+import GHC.Hs
import TcHsSyn
import TcEvidence
import TcRnMonad
diff --git a/compiler/deSugar/Match.hs-boot b/compiler/deSugar/Match.hs-boot
index e77ad548b6..be5cd766ea 100644
--- a/compiler/deSugar/Match.hs-boot
+++ b/compiler/deSugar/Match.hs-boot
@@ -5,9 +5,9 @@ import Var ( Id )
import TcType ( Type )
import DsMonad ( DsM, EquationInfo, MatchResult )
import CoreSyn ( CoreExpr )
-import HsSyn ( LPat, HsMatchContext, MatchGroup, LHsExpr )
+import GHC.Hs ( LPat, HsMatchContext, MatchGroup, LHsExpr )
import Name ( Name )
-import HsExtension ( GhcTc )
+import GHC.Hs.Extension ( GhcTc )
match :: [Id]
-> Type
diff --git a/compiler/deSugar/MatchCon.hs b/compiler/deSugar/MatchCon.hs
index ce1f19f560..be65433c3b 100644
--- a/compiler/deSugar/MatchCon.hs
+++ b/compiler/deSugar/MatchCon.hs
@@ -18,7 +18,7 @@ import GhcPrelude
import {-# SOURCE #-} Match ( match )
-import HsSyn
+import GHC.Hs
import DsBinds
import ConLike
import BasicTypes ( Origin(..) )
diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs
index 3bab8cf000..126346b935 100644
--- a/compiler/deSugar/MatchLit.hs
+++ b/compiler/deSugar/MatchLit.hs
@@ -27,7 +27,7 @@ import {-# SOURCE #-} DsExpr ( dsExpr, dsSyntaxExpr )
import DsMonad
import DsUtils
-import HsSyn
+import GHC.Hs
import Id
import CoreSyn
diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index fc5f581a4d..037e7aa0b2 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -177,7 +177,6 @@ Library
coreSyn
deSugar
ghci
- hsSyn
iface
llvmGen
main
@@ -354,20 +353,20 @@ Library
Match
MatchCon
MatchLit
- HsBinds
- HsDecls
- HsDoc
- HsExpr
- HsImpExp
- HsLit
- PlaceHolder
- HsExtension
- HsInstances
- HsPat
- HsSyn
- HsTypes
- HsUtils
- HsDumpAst
+ GHC.Hs
+ GHC.Hs.Binds
+ GHC.Hs.Decls
+ GHC.Hs.Doc
+ GHC.Hs.Expr
+ GHC.Hs.ImpExp
+ GHC.Hs.Lit
+ GHC.Hs.PlaceHolder
+ GHC.Hs.Extension
+ GHC.Hs.Instances
+ GHC.Hs.Pat
+ GHC.Hs.Types
+ GHC.Hs.Utils
+ GHC.Hs.Dump
BinIface
BinFingerprint
BuildTyCl
@@ -663,7 +662,7 @@ Library
Dwarf
Dwarf.Types
Dwarf.Constants
- Convert
+ GHC.ThToHs
ByteCodeTypes
ByteCodeAsm
ByteCodeGen
diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs
index 47f21882c9..a1253de735 100644
--- a/compiler/hieFile/HieAst.hs
+++ b/compiler/hieFile/HieAst.hs
@@ -25,7 +25,7 @@ import CoreUtils ( exprType )
import ConLike ( conLikeName )
import Desugar ( deSugarExpr )
import FieldLabel
-import HsSyn
+import GHC.Hs
import HscTypes
import Module ( ModuleName, ml_hs_file )
import MonadUtils ( concatMapM, liftIO )
diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs
index e3be840006..7e555ed45c 100644
--- a/compiler/iface/MkIface.hs
+++ b/compiler/iface/MkIface.hs
@@ -82,7 +82,7 @@ import TcType
import InstEnv
import FamInstEnv
import TcRnMonad
-import HsSyn
+import GHC.Hs
import HscTypes
import Finder
import DynFlags
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 87f0d12667..a66daa220e 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -227,7 +227,7 @@ module GHC (
TyThing(..),
-- ** Syntax
- module HsSyn, -- ToDo: remove extraneous bits
+ module GHC.Hs, -- ToDo: remove extraneous bits
-- ** Fixities
FixityDirection(..),
@@ -314,7 +314,7 @@ import TcRnTypes
import Packages
import NameSet
import RdrName
-import HsSyn
+import GHC.Hs
import Type hiding( typeKind )
import TcType
import Id
diff --git a/compiler/main/GhcPlugins.hs b/compiler/main/GhcPlugins.hs
index 56492377d8..351f0b268a 100644
--- a/compiler/main/GhcPlugins.hs
+++ b/compiler/main/GhcPlugins.hs
@@ -90,7 +90,7 @@ import Data.Maybe
import IfaceEnv ( lookupOrigIO )
import GhcPrelude
import MonadUtils ( mapMaybeM )
-import Convert ( thRdrNameGuesses )
+import GHC.ThToHs ( thRdrNameGuesses )
import TcEnv ( lookupGlobal )
import qualified Language.Haskell.TH as TH
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index 0d7e6fd702..d534fab1d5 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -26,7 +26,7 @@ import HscTypes
import Parser ( parseHeader )
import Lexer
import FastString
-import HsSyn
+import GHC.Hs
import Module
import PrelNames
import StringBuffer
diff --git a/compiler/main/Hooks.hs b/compiler/main/Hooks.hs
index f9d420ab61..a562b3e33f 100644
--- a/compiler/main/Hooks.hs
+++ b/compiler/main/Hooks.hs
@@ -28,9 +28,9 @@ import GhcPrelude
import DynFlags
import PipelineMonad
import HscTypes
-import HsDecls
-import HsBinds
-import HsExpr
+import GHC.Hs.Decls
+import GHC.Hs.Binds
+import GHC.Hs.Expr
import OrdList
import TcRnTypes
import Bag
@@ -43,7 +43,7 @@ import SrcLoc
import Type
import System.Process
import BasicTypes
-import HsExtension
+import GHC.Hs.Extension
import Data.Maybe
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index f2fc6e98d2..a9fe3ffe18 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -104,8 +104,8 @@ import Control.Concurrent
import Module
import Packages
import RdrName
-import HsSyn
-import HsDumpAst
+import GHC.Hs
+import GHC.Hs.Dump
import CoreSyn
import StringBuffer
import Parser
diff --git a/compiler/main/HscStats.hs b/compiler/main/HscStats.hs
index df77ae41a4..27f192227f 100644
--- a/compiler/main/HscStats.hs
+++ b/compiler/main/HscStats.hs
@@ -13,7 +13,7 @@ module HscStats ( ppSourceStats ) where
import GhcPrelude
import Bag
-import HsSyn
+import GHC.Hs
import Outputable
import SrcLoc
import Util
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index a9e9bcb363..274b777eec 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -155,7 +155,7 @@ import GHCi.RemoteTypes
import GHC.ForeignSrcLang
import UniqFM
-import HsSyn
+import GHC.Hs
import RdrName
import Avail
import Module
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 88c8ecc7df..e7f3947210 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -53,7 +53,7 @@ import GHCi.Message
import GHCi.RemoteTypes
import GhcMonad
import HscMain
-import HsSyn
+import GHC.Hs
import HscTypes
import InstEnv
import IfaceEnv ( newInteractiveBinder )
diff --git a/compiler/main/Plugins.hs b/compiler/main/Plugins.hs
index c787960dd6..66eebb9f63 100644
--- a/compiler/main/Plugins.hs
+++ b/compiler/main/Plugins.hs
@@ -53,7 +53,7 @@ import {-# SOURCE #-} CoreMonad ( CoreToDo, CoreM )
import qualified TcRnTypes
import TcRnTypes ( TcGblEnv, IfM, TcM, tcg_rn_decls, tcg_rn_exports )
import TcHoleFitTypes ( HoleFitPluginR )
-import HsSyn
+import GHC.Hs
import DynFlags
import HscTypes
import GhcMonad
diff --git a/compiler/parser/HaddockUtils.hs b/compiler/parser/HaddockUtils.hs
index 7969f6e1a2..d1d41a3d29 100644
--- a/compiler/parser/HaddockUtils.hs
+++ b/compiler/parser/HaddockUtils.hs
@@ -3,7 +3,7 @@ module HaddockUtils where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import SrcLoc
import Control.Monad
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 5f79879789..bc4b7b1a74 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -44,7 +44,7 @@ import Control.Monad ( mplus )
import Control.Applicative ((<$))
-- compiler/hsSyn
-import HsSyn
+import GHC.Hs
-- compiler/main
import HscTypes ( IsBootInterface, WarningTxt(..) )
@@ -3416,7 +3416,7 @@ qconop :: { Located RdrName }
-- Type constructors
--- See Note [Unit tuples] in HsTypes for the distinction
+-- See Note [Unit tuples] in GHC.Hs.Types for the distinction
-- between gtycon and ntgtycon
gtycon :: { Located RdrName } -- A "general" qualified tycon, including unit tuples
: ntgtycon { $1 }
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index a574fbe338..538c20cc8a 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -103,7 +103,7 @@ module RdrHsSyn (
) where
import GhcPrelude
-import HsSyn -- Lots of it
+import GHC.Hs -- Lots of it
import TyCon ( TyCon, isTupleTyCon, tyConSingleDataCon_maybe )
import DataCon ( DataCon, dataConTyCon )
import ConLike ( ConLike(..) )
@@ -157,7 +157,7 @@ import Data.Data ( dataTypeOf, fromConstr, dataTypeConstrs )
-- Similarly for mkConDecl, mkClassOpSig and default-method names.
--- *** See Note [The Naming story] in HsDecls ****
+-- *** See Note [The Naming story] in GHC.Hs.Decls ****
mkTyClD :: LTyClDecl (GhcPass p) -> LHsDecl (GhcPass p)
mkTyClD (dL->L loc d) = cL loc (TyClD noExtField d)
@@ -670,7 +670,7 @@ mkGadtDecl names ty
(args, res_ty) = split_tau tau
- -- See Note [GADT abstract syntax] in HsDecls
+ -- See Note [GADT abstract syntax] in GHC.Hs.Decls
split_tau (dL->L _ (HsFunTy _ (dL->L loc (HsRecTy _ rf)) res_ty))
= (RecCon (cL loc rf), res_ty)
split_tau tau
@@ -932,7 +932,7 @@ checkTyClHdr is_cls ty
arity = length ts
tup_name | is_cls = cTupleTyConName arity
| otherwise = getName (tupleTyCon Boxed arity)
- -- See Note [Unit tuples] in HsTypes (TODO: is this still relevant?)
+ -- See Note [Unit tuples] in GHC.Hs.Types (TODO: is this still relevant?)
go l _ _ _ _
= addFatalError l (text "Malformed head of type or class declaration:"
<+> ppr ty)
@@ -1188,7 +1188,7 @@ checkFunBind strictness ann lhs_loc fun is_infix pats (dL->L rhs_span grhss)
makeFunBind :: Located RdrName -> [LMatch GhcPs (LHsExpr GhcPs)]
-> HsBind GhcPs
--- Like HsUtils.mkFunBind, but we need to be able to set the fixity too
+-- Like GHC.Hs.Utils.mkFunBind, but we need to be able to set the fixity too
makeFunBind fn ms
= FunBind { fun_ext = noExtField,
fun_id = fn,
@@ -2290,8 +2290,8 @@ rule, so this approach scales well to large parser productions.
{- Note [Resolving parsing ambiguities: non-taken alternatives]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Alternative I, extra constructors in HsExpr
--------------------------------------------
+Alternative I, extra constructors in GHC.Hs.Expr
+------------------------------------------------
We could add extra constructors to HsExpr to represent command-specific and
pattern-specific syntactic constructs. Under this scheme, we parse patterns
and commands as expressions and rejig later. This is what GHC used to do, and
@@ -2326,15 +2326,15 @@ There are several issues with this:
(f ! a b) ! c = ...
-Alternative II, extra constructors in HsExpr for GhcPs
-------------------------------------------------------
+Alternative II, extra constructors in GHC.Hs.Expr for GhcPs
+-----------------------------------------------------------
We could address some of the problems with Alternative I by using Trees That
Grow and extending HsExpr only in the GhcPs pass. However, GhcPs corresponds to
the output of parsing, not to its intermediate results, so we wouldn't want
them there either.
-Alternative III, extra constructors in HsExpr for GhcPrePs
-----------------------------------------------------------
+Alternative III, extra constructors in GHC.Hs.Expr for GhcPrePs
+---------------------------------------------------------------
We could introduce a new pass, GhcPrePs, to keep GhcPs pristine.
Unfortunately, creating a new pass would significantly bloat conversion code
and slow down the compiler by adding another linear-time pass over the entire
diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs
index 5bb76f8f0d..811a81bdb1 100644
--- a/compiler/rename/RnBinds.hs
+++ b/compiler/rename/RnBinds.hs
@@ -30,7 +30,7 @@ import GhcPrelude
import {-# SOURCE #-} RnExpr( rnLExpr, rnStmts )
-import HsSyn
+import GHC.Hs
import TcRnMonad
import RnTypes
import RnPat
@@ -248,7 +248,7 @@ rnLocalValBindsLHS fix_env binds
-- Check for duplicates and shadowing
-- Must do this *after* renaming the patterns
- -- See Note [Collect binders only after renaming] in HsUtils
+ -- See Note [Collect binders only after renaming] in GHC.Hs.Utils
-- We need to check for dups here because we
-- don't don't bind all of the variables from the ValBinds at once
diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index 91cf8f22f4..d9dbbee891 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -48,7 +48,7 @@ import GhcPrelude
import LoadIface ( loadInterfaceForName, loadSrcInterface_maybe )
import IfaceEnv
-import HsSyn
+import GHC.Hs
import RdrName
import HscTypes
import TcEnv
diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs
index eadb4bca03..6485c004a6 100644
--- a/compiler/rename/RnExpr.hs
+++ b/compiler/rename/RnExpr.hs
@@ -26,7 +26,7 @@ import GhcPrelude
import RnBinds ( rnLocalBindsAndThen, rnLocalValBindsLHS, rnLocalValBindsRHS,
rnMatchGroup, rnGRHS, makeMiniFixityEnv)
-import HsSyn
+import GHC.Hs
import TcEnv ( isBrackStage )
import TcRnMonad
import Module ( getModule )
@@ -916,7 +916,7 @@ rnStmt ctxt _ (L loc (TransStmt { trS_stmts = stmts, trS_by = by, trS_form = for
; let all_fvs = fvs1 `plusFV` fvs2 `plusFV` fvs3
`plusFV` fvs4 `plusFV` fvs5
bndr_map = used_bndrs `zip` used_bndrs
- -- See Note [TransStmt binder map] in HsExpr
+ -- See Note [TransStmt binder map] in GHC.Hs.Expr
; traceRn "rnStmt: implicitly rebound these used binders:" (ppr bndr_map)
; return (([(L loc (TransStmt { trS_ext = noExtField
diff --git a/compiler/rename/RnExpr.hs-boot b/compiler/rename/RnExpr.hs-boot
index b325eeb6f0..8a9c7818a1 100644
--- a/compiler/rename/RnExpr.hs-boot
+++ b/compiler/rename/RnExpr.hs-boot
@@ -1,6 +1,6 @@
module RnExpr where
import Name
-import HsSyn
+import GHC.Hs
import NameSet ( FreeVars )
import TcRnTypes
import SrcLoc ( Located )
diff --git a/compiler/rename/RnFixity.hs b/compiler/rename/RnFixity.hs
index 665d87747b..198a0441e5 100644
--- a/compiler/rename/RnFixity.hs
+++ b/compiler/rename/RnFixity.hs
@@ -14,7 +14,7 @@ module RnFixity ( MiniFixityEnv,
import GhcPrelude
import LoadIface
-import HsSyn
+import GHC.Hs
import RdrName
import HscTypes
import TcRnMonad
diff --git a/compiler/rename/RnHsDoc.hs b/compiler/rename/RnHsDoc.hs
index 348f87fca5..deaedb8bca 100644
--- a/compiler/rename/RnHsDoc.hs
+++ b/compiler/rename/RnHsDoc.hs
@@ -5,7 +5,7 @@ module RnHsDoc ( rnHsDoc, rnLHsDoc, rnMbLHsDoc ) where
import GhcPrelude
import TcRnTypes
-import HsSyn
+import GHC.Hs
import SrcLoc
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 5bfc1a37d8..738f4c6ab5 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -32,7 +32,7 @@ module RnNames (
import GhcPrelude
import DynFlags
-import HsSyn
+import GHC.Hs
import TcEnv
import RnEnv
import RnFixity
@@ -607,7 +607,7 @@ extendGlobalRdrEnvRn avails new_fixities
getLocalDeclBindersd@ returns the names for an HsDecl
It's used for source code.
- *** See Note [The Naming story] in HsDecls ****
+ *** See Note [The Naming story] in GHC.Hs.Decls ****
* *
********************************************************************* -}
diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs
index 150b1cd23f..61cdc140bf 100644
--- a/compiler/rename/RnPat.hs
+++ b/compiler/rename/RnPat.hs
@@ -48,7 +48,7 @@ import {-# SOURCE #-} RnSplice ( rnSplicePat )
#include "HsVersions.h"
-import HsSyn
+import GHC.Hs
import TcRnMonad
import TcHsSyn ( hsOverLitName )
import RnEnv
@@ -319,7 +319,7 @@ rnPats ctxt pats thing_inside
; unCpsRn (rnLPatsAndThen (matchNameMaker ctxt) pats) $ \ pats' -> do
{ -- Check for duplicated and shadowed names
-- Must do this *after* renaming the patterns
- -- See Note [Collect binders only after renaming] in HsUtils
+ -- See Note [Collect binders only after renaming] in GHC.Hs.Utils
-- Because we don't bind the vars all at once, we can't
-- check incrementally for duplicates;
-- Nor can we check incrementally for shadowing, else we'll
@@ -642,7 +642,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
-- due to #15884
- rn_dotdot :: Maybe (Located Int) -- See Note [DotDot fields] in HsPat
+ rn_dotdot :: Maybe (Located Int) -- See Note [DotDot fields] in GHC.Hs.Pat
-> Maybe Name -- The constructor (Nothing for an
-- out of scope constructor)
-> [LHsRecField GhcRn arg] -- Explicit fields
diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs
index 79280ee43f..229c66fda4 100644
--- a/compiler/rename/RnSource.hs
+++ b/compiler/rename/RnSource.hs
@@ -21,7 +21,7 @@ import GhcPrelude
import {-# SOURCE #-} RnExpr( rnLExpr )
import {-# SOURCE #-} RnSplice ( rnSpliceDecl, rnTopSpliceDecls )
-import HsSyn
+import GHC.Hs
import FieldLabel
import RdrName
import RnTypes
@@ -1617,7 +1617,7 @@ dataDeclHasCUSK tyvars new_or_data no_rhs_kvs has_kind_sig = do
| NewType <- new_or_data =
unlifted_newtypes && not has_kind_sig
| otherwise = False
- -- See Note [CUSKs: complete user-supplied kind signatures] in HsDecls
+ -- See Note [CUSKs: complete user-supplied kind signatures] in GHC.Hs.Decls
; cusks_enabled <- xoptM LangExt.CUSKs
; return $ cusks_enabled && hsTvbAllKinded tyvars &&
no_rhs_kvs && not non_cusk_newtype
@@ -2073,7 +2073,7 @@ rnConDecl decl@(ConDeclGADT { con_names = names
RecCon {} -> (new_args, new_res_ty)
PrefixCon as | (arg_tys, final_res_ty) <- splitHsFunType new_res_ty
-> ASSERT( null as )
- -- See Note [GADT abstract syntax] in HsDecls
+ -- See Note [GADT abstract syntax] in GHC.Hs.Decls
(PrefixCon arg_tys, final_res_ty)
new_qtvs = HsQTvs { hsq_ext = implicit_tkvs
diff --git a/compiler/rename/RnSplice.hs b/compiler/rename/RnSplice.hs
index 9c3e317958..3e6d64751d 100644
--- a/compiler/rename/RnSplice.hs
+++ b/compiler/rename/RnSplice.hs
@@ -16,7 +16,7 @@ import GhcPrelude
import Name
import NameSet
-import HsSyn
+import GHC.Hs
import RdrName
import TcRnMonad
diff --git a/compiler/rename/RnSplice.hs-boot b/compiler/rename/RnSplice.hs-boot
index 7844acd2c9..cd6021027e 100644
--- a/compiler/rename/RnSplice.hs-boot
+++ b/compiler/rename/RnSplice.hs-boot
@@ -1,7 +1,7 @@
module RnSplice where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcRnMonad
import NameSet
diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs
index 80b03d3f25..e982e72f82 100644
--- a/compiler/rename/RnTypes.hs
+++ b/compiler/rename/RnTypes.hs
@@ -38,7 +38,7 @@ import GhcPrelude
import {-# SOURCE #-} RnSplice( rnSpliceType )
import DynFlags
-import HsSyn
+import GHC.Hs
import RnHsDoc ( rnLHsDoc, rnMbLHsDoc )
import RnEnv
import RnUtils ( HsDocContext(..), withHsDocContext, mapFvRn
@@ -280,7 +280,7 @@ partition_nwcs free_vars
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Identifiers starting with an underscore are always parsed as type variables.
It is only here in the renamer that we give the special treatment.
-See Note [The wildcard story for types] in HsTypes.
+See Note [The wildcard story for types] in GHC.Hs.Types.
It's easy! When we collect the implicitly bound type variables, ready
to bring them into scope, and NamedWildCards is on, we partition the
@@ -803,7 +803,7 @@ bindHsQTyVars :: forall a b.
-- The Bool is True <=> all kind variables used in the
-- kind signature are bound on the left. Reason:
-- the last clause of Note [CUSKs: Complete user-supplied
- -- kind signatures] in HsDecls
+ -- kind signatures] in GHC.Hs.Decls
-> RnM (b, FreeVars)
-- See Note [bindHsQTyVars examples]
diff --git a/compiler/rename/RnUtils.hs b/compiler/rename/RnUtils.hs
index a4715a23f6..6678ad6dbf 100644
--- a/compiler/rename/RnUtils.hs
+++ b/compiler/rename/RnUtils.hs
@@ -33,7 +33,7 @@ where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import RdrName
import HscTypes
import TcEnv
diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs
index a00e8ad2ba..052ef2b6c7 100644
--- a/compiler/stgSyn/StgSyn.hs
+++ b/compiler/stgSyn/StgSyn.hs
@@ -435,7 +435,7 @@ data StgPass
| LiftLams
| CodeGen
--- | Like 'HsExtension.NoExtField', but with an 'Outputable' instance that
+-- | Like 'GHC.Hs.Extension.NoExtField', but with an 'Outputable' instance that
-- returns 'empty'.
data NoExtFieldSilent = NoExtFieldSilent
deriving (Data, Eq, Ord)
@@ -447,8 +447,8 @@ instance Outputable NoExtFieldSilent where
-- not appear in pretty-printed output at all.
noExtFieldSilent :: NoExtFieldSilent
noExtFieldSilent = NoExtFieldSilent
--- TODO: Maybe move this to HsExtension? I'm not sure about the implications
--- on build time...
+-- TODO: Maybe move this to GHC.Hs.Extension? I'm not sure about the
+-- implications on build time...
-- TODO: Do we really want to the extension point type families to have a closed
-- domain?
diff --git a/compiler/typecheck/Inst.hs b/compiler/typecheck/Inst.hs
index 1ec85b22d1..8e180b4cf4 100644
--- a/compiler/typecheck/Inst.hs
+++ b/compiler/typecheck/Inst.hs
@@ -39,7 +39,7 @@ import {-# SOURCE #-} TcUnify( unifyType, unifyKind )
import BasicTypes ( IntegralLit(..), SourceText(..) )
import FastString
-import HsSyn
+import GHC.Hs
import TcHsSyn
import TcRnMonad
import TcEnv
@@ -608,7 +608,7 @@ tcSyntaxName :: CtOrigin
-> TcM (Name, HsExpr GhcTcId)
-- ^ (Standard name, suitable expression)
-- USED ONLY FOR CmdTop (sigh) ***
--- See Note [CmdSyntaxTable] in HsExpr
+-- See Note [CmdSyntaxTable] in GHC.Hs.Expr
tcSyntaxName orig ty (std_nm, HsVar _ (L _ user_nm))
| std_nm == user_nm
diff --git a/compiler/typecheck/TcAnnotations.hs b/compiler/typecheck/TcAnnotations.hs
index 00c1958106..b3736ed7bb 100644
--- a/compiler/typecheck/TcAnnotations.hs
+++ b/compiler/typecheck/TcAnnotations.hs
@@ -18,7 +18,7 @@ import Module
import DynFlags
import Control.Monad ( when )
-import HsSyn
+import GHC.Hs
import Name
import Annotations
import TcRnMonad
diff --git a/compiler/typecheck/TcArrows.hs b/compiler/typecheck/TcArrows.hs
index c5e3ca99b2..d9c2136aca 100644
--- a/compiler/typecheck/TcArrows.hs
+++ b/compiler/typecheck/TcArrows.hs
@@ -14,7 +14,7 @@ import GhcPrelude
import {-# SOURCE #-} TcExpr( tcMonoExpr, tcInferRho, tcSyntaxOp, tcCheckId, tcPolyExpr )
-import HsSyn
+import GHC.Hs
import TcMatches
import TcHsSyn( hsLPatType )
import TcType
@@ -388,7 +388,7 @@ tcArrDoStmt env ctxt (RecStmt { recS_stmts = stmts, recS_later_ids = later_names
-- NB: The rec_ids for the recursive things
-- already scope over this part. This binding may shadow
-- some of them with polymorphic things with the same Name
- -- (see note [RecStmt] in HsExpr)
+ -- (see note [RecStmt] in GHC.Hs.Expr)
; let rec_ids = takeList rec_names tup_ids
; later_ids <- tcLookupLocalIds later_names
diff --git a/compiler/typecheck/TcBackpack.hs b/compiler/typecheck/TcBackpack.hs
index 7fffcd1d18..1e9a1ea691 100644
--- a/compiler/typecheck/TcBackpack.hs
+++ b/compiler/typecheck/TcBackpack.hs
@@ -23,7 +23,7 @@ import BasicTypes (defaultFixity)
import Packages
import TcRnExports
import DynFlags
-import HsSyn
+import GHC.Hs
import RdrName
import TcRnMonad
import TcTyDecls
diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index fcf871f75f..8f14abe32f 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -25,7 +25,7 @@ import CoreSyn (Tickish (..))
import CostCentre (mkUserCC, CCFlavour(DeclCC))
import DynFlags
import FastString
-import HsSyn
+import GHC.Hs
import HscTypes( isHsBootOrSig )
import TcSigs
import TcRnMonad
diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs
index 31c9ad9a89..e779c6794f 100644
--- a/compiler/typecheck/TcCanonical.hs
+++ b/compiler/typecheck/TcCanonical.hs
@@ -36,7 +36,7 @@ import Outputable
import DynFlags( DynFlags )
import NameSet
import RdrName
-import HsTypes( HsIPName(..) )
+import GHC.Hs.Types( HsIPName(..) )
import Pair
import Util
diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs
index 0239793a51..6f2ef4c292 100644
--- a/compiler/typecheck/TcClassDcl.hs
+++ b/compiler/typecheck/TcClassDcl.hs
@@ -22,7 +22,7 @@ module TcClassDcl ( tcClassSigs, tcClassDecl2,
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcEnv
import TcSigs
import TcEvidence ( idHsWrapper )
diff --git a/compiler/typecheck/TcDefaults.hs b/compiler/typecheck/TcDefaults.hs
index 926eca1ac0..a204486147 100644
--- a/compiler/typecheck/TcDefaults.hs
+++ b/compiler/typecheck/TcDefaults.hs
@@ -10,7 +10,7 @@ module TcDefaults ( tcDefaults ) where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import Class
import TcRnMonad
import TcEnv
diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs
index 0863e22cb9..0b78b8e2ed 100644
--- a/compiler/typecheck/TcDeriv.hs
+++ b/compiler/typecheck/TcDeriv.hs
@@ -15,7 +15,7 @@ module TcDeriv ( tcDeriving, DerivInfo(..) ) where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import DynFlags
import TcRnMonad
diff --git a/compiler/typecheck/TcDerivUtils.hs b/compiler/typecheck/TcDerivUtils.hs
index e7c2451246..ae191f937b 100644
--- a/compiler/typecheck/TcDerivUtils.hs
+++ b/compiler/typecheck/TcDerivUtils.hs
@@ -32,7 +32,7 @@ import DataCon
import DynFlags
import ErrUtils
import HscTypes (lookupFixity, mi_fix)
-import HsSyn
+import GHC.Hs
import Inst
import InstEnv
import LoadIface (loadInterfaceForName)
diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs
index 0ec0601521..3cc1994f5b 100644
--- a/compiler/typecheck/TcEnv.hs
+++ b/compiler/typecheck/TcEnv.hs
@@ -4,7 +4,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-} -- instance MonadThings is necessarily an
-- orphan
{-# LANGUAGE UndecidableInstances #-} -- Note [Pass sensitive types]
- -- in module PlaceHolder
+ -- in module GHC.Hs.PlaceHolder
{-# LANGUAGE TypeFamilies #-}
module TcEnv(
@@ -71,7 +71,7 @@ module TcEnv(
import GhcPrelude
-import HsSyn
+import GHC.Hs
import IfaceEnv
import TcRnMonad
import TcMType
diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 02b888703d..832f859c8a 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -33,8 +33,8 @@ import Class
import DataCon
import TcEvidence
import TcEvTerm
-import HsExpr ( UnboundVar(..) )
-import HsBinds ( PatSynBind(..) )
+import GHC.Hs.Expr ( UnboundVar(..) )
+import GHC.Hs.Binds ( PatSynBind(..) )
import Name
import RdrName ( lookupGlobalRdrEnv, lookupGRE_Name, GlobalRdrEnv
, mkRdrUnqual, isLocalGRE, greSrcSpan )
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 1387e89089..c195576c39 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -24,7 +24,7 @@ import GhcPrelude
import {-# SOURCE #-} TcSplice( tcSpliceExpr, tcTypedBracket, tcUntypedBracket )
import THNames( liftStringName, liftName )
-import HsSyn
+import GHC.Hs
import TcHsSyn
import TcRnMonad
import TcUnify
@@ -1088,7 +1088,7 @@ arithSeqEltType (Just fl) res_ty
************************************************************************
-}
--- HsArg is defined in HsTypes.hs
+-- HsArg is defined in GHC.Hs.Types
wrapHsArgs :: (NoGhcTc (GhcPass id) ~ GhcRn)
=> LHsExpr (GhcPass id)
@@ -2237,7 +2237,7 @@ particular update is sufficiently obvious for the signature to be
omitted. Moreover, this might change the behaviour of typechecker in
non-obvious ways.
-See also Note [HsRecField and HsRecUpdField] in HsPat.
+See also Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat.
-}
-- Given a RdrName that refers to multiple record fields, and the type
diff --git a/compiler/typecheck/TcExpr.hs-boot b/compiler/typecheck/TcExpr.hs-boot
index bb6b5d181c..25650e34fc 100644
--- a/compiler/typecheck/TcExpr.hs-boot
+++ b/compiler/typecheck/TcExpr.hs-boot
@@ -1,9 +1,9 @@
module TcExpr where
import Name
-import HsSyn ( HsExpr, LHsExpr, SyntaxExpr )
+import GHC.Hs ( HsExpr, LHsExpr, SyntaxExpr )
import TcType ( TcRhoType, TcSigmaType, SyntaxOpType, ExpType, ExpRhoType )
import TcRnTypes( TcM, CtOrigin )
-import HsExtension ( GhcRn, GhcTcId )
+import GHC.Hs.Extension ( GhcRn, GhcTcId )
tcPolyExpr ::
LHsExpr GhcRn
diff --git a/compiler/typecheck/TcForeign.hs b/compiler/typecheck/TcForeign.hs
index ace0cddb66..3684061642 100644
--- a/compiler/typecheck/TcForeign.hs
+++ b/compiler/typecheck/TcForeign.hs
@@ -35,7 +35,7 @@ module TcForeign
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcRnMonad
import TcHsType
diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs
index 4a7032cedf..a7f8f79530 100644
--- a/compiler/typecheck/TcGenDeriv.hs
+++ b/compiler/typecheck/TcGenDeriv.hs
@@ -40,7 +40,7 @@ module TcGenDeriv (
import GhcPrelude
import TcRnMonad
-import HsSyn
+import GHC.Hs
import RdrName
import BasicTypes
import DataCon
diff --git a/compiler/typecheck/TcGenFunctor.hs b/compiler/typecheck/TcGenFunctor.hs
index c2cdef412a..19cd9d903a 100644
--- a/compiler/typecheck/TcGenFunctor.hs
+++ b/compiler/typecheck/TcGenFunctor.hs
@@ -23,7 +23,7 @@ import GhcPrelude
import Bag
import DataCon
import FastString
-import HsSyn
+import GHC.Hs
import Panic
import PrelNames
import RdrName
diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs
index ecf0d8b76d..087bd938f0 100644
--- a/compiler/typecheck/TcGenGenerics.hs
+++ b/compiler/typecheck/TcGenGenerics.hs
@@ -16,7 +16,7 @@ module TcGenGenerics (canDoGenerics, canDoGenerics1,
import GhcPrelude
-import HsSyn
+import GHC.Hs
import Type
import TcType
import TcGenDeriv
diff --git a/compiler/typecheck/TcHoleErrors.hs b/compiler/typecheck/TcHoleErrors.hs
index 8c9cf0285b..bf3253188b 100644
--- a/compiler/typecheck/TcHoleErrors.hs
+++ b/compiler/typecheck/TcHoleErrors.hs
@@ -50,7 +50,7 @@ import TcUnify ( tcSubType_NC )
import ExtractDocs ( extractDocs )
import qualified Data.Map as Map
-import HsDoc ( unpackHDS, DeclDocMap(..) )
+import GHC.Hs.Doc ( unpackHDS, DeclDocMap(..) )
import HscTypes ( ModIface(..) )
import LoadIface ( loadInterfaceForNameMaybe )
diff --git a/compiler/typecheck/TcHoleFitTypes.hs b/compiler/typecheck/TcHoleFitTypes.hs
index 8700cc1399..fccf47eb54 100644
--- a/compiler/typecheck/TcHoleFitTypes.hs
+++ b/compiler/typecheck/TcHoleFitTypes.hs
@@ -12,7 +12,7 @@ import TcType
import RdrName
-import HsDoc
+import GHC.Hs.Doc
import Id
import Outputable
diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs
index d80505ea63..cd15db5bfd 100644
--- a/compiler/typecheck/TcHsSyn.hs
+++ b/compiler/typecheck/TcHsSyn.hs
@@ -48,7 +48,7 @@ module TcHsSyn (
import GhcPrelude
-import HsSyn
+import GHC.Hs
import Id
import IdInfo
import TcRnMonad
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 328290a2f8..37cc83e4ca 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -64,7 +64,7 @@ module TcHsType (
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcRnMonad
import TcEvidence
import TcEnv
@@ -403,7 +403,7 @@ argument, which we do not want because users should be able to write
solution is to switch the PartialTypeSignatures flags here to let the
typechecker know that it's checking a '@_' and do not emit hole
constraints on it. See related Note [Wildcards in visible kind
-application] and Note [The wildcard story for types] in HsTypes.hs
+application] and Note [The wildcard story for types] in GHC.Hs.Types
Ugh!
@@ -734,7 +734,7 @@ tc_hs_type mode rn_ty@(HsListTy _ elt_ty) exp_kind
; checkWiredInTyCon listTyCon
; checkExpectedKind rn_ty (mkListTy tau_ty) liftedTypeKind exp_kind }
--- See Note [Distinguishing tuple kinds] in HsTypes
+-- See Note [Distinguishing tuple kinds] in GHC.Hs.Types
-- See Note [Inferring tuple kinds]
tc_hs_type mode rn_ty@(HsTupleTy _ HsBoxedOrConstraintTuple hs_tys) exp_kind
-- (NB: not zonking before looking at exp_k, to avoid left-right bias)
@@ -892,7 +892,7 @@ And whenever we see a '@', we automatically turn on PartialTypeSignatures and
turn off hole constraint warnings, and do not call emitAnonWildCardHoleConstraint
under these conditions.
See related Note [Wildcards in visible type application] here and
-Note [The wildcard story for types] in HsTypes.hs
+Note [The wildcard story for types] in GHC.Hs.Types
-}
@@ -1752,7 +1752,7 @@ tcNamedWildCardBinders :: [Name]
-> TcM a
-- Bring into scope the /named/ wildcard binders. Remember that
-- plain wildcards _ are anonymous and dealt with by HsWildCardTy
--- Soe Note [The wildcard story for types] in HsTypes
+-- Soe Note [The wildcard story for types] in GHC.Hs.Types
tcNamedWildCardBinders wc_names thing_inside
= do { wcs <- mapM (const newWildTyVar) wc_names
; let wc_prs = wc_names `zip` wcs
@@ -1802,7 +1802,7 @@ It has two cases:
-- Used in 'getInitialKind' (for tycon kinds and other kinds)
-- and in kind-checking (but not for tycon kinds, which are checked with
-- tcTyClDecls). See Note [CUSKs: complete user-supplied kind signatures]
--- in HsDecls.
+-- in GHC.Hs.Decls.
--
-- This function does not do telescope checking.
kcLHsQTyVars :: Name -- ^ of the thing being checked
@@ -2002,7 +2002,7 @@ kcLHsQTyVarBndrs:
* The tcLookupLocal_maybe code in kc_hs_tv
See Note [Associated type tyvar names] in Class and
- Note [TyVar binders for associated decls] in HsDecls
+ Note [TyVar binders for associated decls] in GHC.Hs.Decls
We must do the same for family instance decls, where the in-scope
variables may be bound by the enclosing class instance decl.
diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs
index bc5e9ae244..e9d75fb17f 100644
--- a/compiler/typecheck/TcInstDcls.hs
+++ b/compiler/typecheck/TcInstDcls.hs
@@ -16,7 +16,7 @@ module TcInstDcls ( tcInstDecls1, tcInstDeclsDeriv, tcInstDecls2 ) where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcBinds
import TcTyClsDecls
import TcTyDecls ( addTyConsToGblEnv )
diff --git a/compiler/typecheck/TcInstDcls.hs-boot b/compiler/typecheck/TcInstDcls.hs-boot
index ea0f50fd36..c65016efa0 100644
--- a/compiler/typecheck/TcInstDcls.hs-boot
+++ b/compiler/typecheck/TcInstDcls.hs-boot
@@ -5,7 +5,7 @@
module TcInstDcls ( tcInstDecls1 ) where
-import HsSyn
+import GHC.Hs
import TcRnTypes
import TcEnv( InstInfo )
import TcDeriv
diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs
index b2233b4964..3f56fc8e45 100644
--- a/compiler/typecheck/TcMatches.hs
+++ b/compiler/typecheck/TcMatches.hs
@@ -25,7 +25,7 @@ import {-# SOURCE #-} TcExpr( tcSyntaxOp, tcInferSigmaNC, tcInferSigma
, tcCheckId, tcMonoExpr, tcMonoExprNC, tcPolyExpr )
import BasicTypes (LexicalFixity(..))
-import HsSyn
+import GHC.Hs
import TcRnMonad
import TcEnv
import TcPat
@@ -516,7 +516,7 @@ tcLcStmt m_tc ctxt (TransStmt { trS_form = form, trS_stmts = stmts
-- Ensure that every old binder of type `b` is linked up with its
-- new binder which should have type `n b`
- -- See Note [GroupStmt binder map] in HsExpr
+ -- See Note [GroupStmt binder map] in GHC.Hs.Expr
n_bndr_ids = zipWith mk_n_bndr n_bndr_names bndr_ids
bindersMap' = bndr_ids `zip` n_bndr_ids
@@ -696,7 +696,7 @@ tcMcStmt ctxt (TransStmt { trS_stmts = stmts, trS_bndrs = bindersMap
-- Ensure that every old binder of type `b` is linked up with its
-- new binder which should have type `n b`
- -- See Note [GroupStmt binder map] in HsExpr
+ -- See Note [GroupStmt binder map] in GHC.Hs.Expr
n_bndr_ids = zipWith mk_n_bndr n_bndr_names bndr_ids
bindersMap' = bndr_ids `zip` n_bndr_ids
diff --git a/compiler/typecheck/TcMatches.hs-boot b/compiler/typecheck/TcMatches.hs-boot
index 42640151ce..9c6b914422 100644
--- a/compiler/typecheck/TcMatches.hs-boot
+++ b/compiler/typecheck/TcMatches.hs-boot
@@ -1,11 +1,11 @@
module TcMatches where
-import HsSyn ( GRHSs, MatchGroup, LHsExpr )
+import GHC.Hs ( GRHSs, MatchGroup, LHsExpr )
import TcEvidence( HsWrapper )
import Name ( Name )
import TcType ( ExpSigmaType, TcRhoType )
import TcRnTypes( TcM )
import SrcLoc ( Located )
-import HsExtension ( GhcRn, GhcTcId )
+import GHC.Hs.Extension ( GhcRn, GhcTcId )
tcGRHSsPat :: GRHSs GhcRn (LHsExpr GhcRn)
-> TcRhoType
diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs
index fae16723fa..7ecfb61d7d 100644
--- a/compiler/typecheck/TcPat.hs
+++ b/compiler/typecheck/TcPat.hs
@@ -21,7 +21,7 @@ import GhcPrelude
import {-# SOURCE #-} TcExpr( tcSyntaxOp, tcSyntaxOpGen, tcInferSigma )
-import HsSyn
+import GHC.Hs
import TcHsSyn
import TcSigs( TcPragEnv, lookupPragEnv, addInlinePrags )
import TcRnMonad
diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs
index b2b552725f..28ec8471ff 100644
--- a/compiler/typecheck/TcPatSyn.hs
+++ b/compiler/typecheck/TcPatSyn.hs
@@ -16,7 +16,7 @@ module TcPatSyn ( tcPatSynDecl, tcPatSynBuilderBind
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcPat
import Type( tidyTyCoVarBinders, tidyTypes, tidyType )
import TcRnMonad
diff --git a/compiler/typecheck/TcPatSyn.hs-boot b/compiler/typecheck/TcPatSyn.hs-boot
index 3538682f69..950d03811a 100644
--- a/compiler/typecheck/TcPatSyn.hs-boot
+++ b/compiler/typecheck/TcPatSyn.hs-boot
@@ -1,10 +1,10 @@
module TcPatSyn where
-import HsSyn ( PatSynBind, LHsBinds )
+import GHC.Hs ( PatSynBind, LHsBinds )
import TcRnTypes ( TcM, TcSigInfo )
import TcRnMonad ( TcGblEnv)
import Outputable ( Outputable )
-import HsExtension ( GhcRn, GhcTc )
+import GHC.Hs.Extension ( GhcRn, GhcTc )
import Data.Maybe ( Maybe )
tcPatSynDecl :: PatSynBind GhcRn GhcRn
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 2fd8359477..6c61487152 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -64,7 +64,7 @@ import MkId
import TysWiredIn ( unitTy, mkListTy )
import Plugins
import DynFlags
-import HsSyn
+import GHC.Hs
import IfaceSyn ( ShowSub(..), showToHeader )
import IfaceType( ShowForAllFlag(..) )
import PatSyn( pprPatSynType )
@@ -134,7 +134,7 @@ import Bag
import Inst (tcGetInsts)
import qualified GHC.LanguageExtensions as LangExt
import Data.Data ( Data )
-import HsDumpAst
+import GHC.Hs.Dump
import qualified Data.Set as S
import Control.DeepSeq
diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs
index 4ac969ffcf..0b405d3c9e 100644
--- a/compiler/typecheck/TcRnExports.hs
+++ b/compiler/typecheck/TcRnExports.hs
@@ -9,7 +9,7 @@ module TcRnExports (tcRnExports, exports_from_avail) where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import PrelNames
import RdrName
import TcRnMonad
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index dfc80ed764..f788b3e001 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -148,7 +148,7 @@ import TcRnTypes -- Re-export all
import IOEnv -- Re-export all
import TcEvidence
-import HsSyn hiding (LIE)
+import GHC.Hs hiding (LIE)
import HscTypes
import Module
import RdrName
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index fe7db11404..8f301a0391 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -149,7 +149,7 @@ module TcRnTypes(
import GhcPrelude
-import HsSyn
+import GHC.Hs
import CoreSyn
import HscTypes
import TcEvidence
diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs
index 4146c8900c..41a7be18b7 100644
--- a/compiler/typecheck/TcRules.hs
+++ b/compiler/typecheck/TcRules.hs
@@ -13,7 +13,7 @@ module TcRules ( tcRules ) where
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcRnTypes
import TcRnMonad
import TcSimplify
diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs
index f6505152f8..3aa16a83f5 100644
--- a/compiler/typecheck/TcSigs.hs
+++ b/compiler/typecheck/TcSigs.hs
@@ -27,7 +27,7 @@ module TcSigs(
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TcHsType
import TcRnTypes
import TcRnMonad
diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 3534757af1..2c930cbd30 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -31,7 +31,7 @@ import GhcPrelude
import Bag
import Class ( Class, classKey, classTyCon )
import DynFlags
-import HsExpr ( UnboundVar(..) )
+import GHC.Hs.Expr ( UnboundVar(..) )
import Id ( idType, mkLocalId )
import Inst
import ListSetOps
diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs
index 242028f578..05c2b0fd10 100644
--- a/compiler/typecheck/TcSplice.hs
+++ b/compiler/typecheck/TcSplice.hs
@@ -33,7 +33,7 @@ module TcSplice(
import GhcPrelude
-import HsSyn
+import GHC.Hs
import Annotations
import Finder
import Name
@@ -60,7 +60,7 @@ import HscMain
import RnSplice( traceSplice, SpliceInfo(..))
import RdrName
import HscTypes
-import Convert
+import GHC.ThToHs
import RnExpr
import RnEnv
import RnUtils ( HsDocContext(..) )
@@ -256,7 +256,7 @@ very straightforwardly:
1. tcTopSpliceExpr: typecheck the body e of the splice $(e)
2. runMetaT: desugar, compile, run it, and convert result back to
- HsSyn RdrName (of the appropriate flavour, eg HsType RdrName,
+ GHC.Hs syntax RdrName (of the appropriate flavour, eg HsType RdrName,
HsExpr RdrName etc)
3. treat the result as if that's what you saw in the first place
diff --git a/compiler/typecheck/TcSplice.hs-boot b/compiler/typecheck/TcSplice.hs-boot
index 8fb294bfc6..8cab536a01 100644
--- a/compiler/typecheck/TcSplice.hs-boot
+++ b/compiler/typecheck/TcSplice.hs-boot
@@ -5,13 +5,13 @@ module TcSplice where
import GhcPrelude
import Name
-import HsExpr ( PendingRnSplice, DelayedSplice )
+import GHC.Hs.Expr ( PendingRnSplice, DelayedSplice )
import TcRnTypes( TcM , SpliceType )
import TcType ( ExpRhoType )
import Annotations ( Annotation, CoreAnnTarget )
-import HsExtension ( GhcTcId, GhcRn, GhcPs, GhcTc )
+import GHC.Hs.Extension ( GhcTcId, GhcRn, GhcPs, GhcTc )
-import HsSyn ( HsSplice, HsBracket, HsExpr, LHsExpr, LHsType, LPat,
+import GHC.Hs ( HsSplice, HsBracket, HsExpr, LHsExpr, LHsType, LPat,
LHsDecl, ThModFinalizers )
import qualified Language.Haskell.TH as TH
diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs
index 36d5807495..69c909f4a1 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -26,7 +26,7 @@ module TcTyClsDecls (
import GhcPrelude
-import HsSyn
+import GHC.Hs
import HscTypes
import BuildTyCl
import TcRnMonad
@@ -151,7 +151,7 @@ tcTyAndClassDecls tyclds_s
tcTyClGroup :: TyClGroup GhcRn
-> TcM (TcGblEnv, [InstInfo GhcRn], [DerivInfo])
-- Typecheck one strongly-connected component of type, class, and instance decls
--- See Note [TyClGroups and dependency analysis] in HsDecls
+-- See Note [TyClGroups and dependency analysis] in GHC.Hs.Decls
tcTyClGroup (TyClGroup { group_tyclds = tyclds
, group_roles = roles
, group_instds = instds })
diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs
index 94658c2413..132ced5fae 100644
--- a/compiler/typecheck/TcTyDecls.hs
+++ b/compiler/typecheck/TcTyDecls.hs
@@ -38,7 +38,7 @@ import TyCoRep( Type(..), Coercion(..), MCoercion(..), UnivCoProvenance(..) )
import TcType
import TysWiredIn( unitTy )
import MkCore( rEC_SEL_ERROR_ID )
-import HsSyn
+import GHC.Hs
import Class
import Type
import HscTypes
diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs
index e2a0e66cd8..f85f647632 100644
--- a/compiler/typecheck/TcTypeable.hs
+++ b/compiler/typecheck/TcTypeable.hs
@@ -34,7 +34,7 @@ import Type
import TyCon
import DataCon
import Module
-import HsSyn
+import GHC.Hs
import DynFlags
import Bag
import Var ( VarBndr(..) )
diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs
index 45cc3f9168..e1fed8d2b3 100644
--- a/compiler/typecheck/TcUnify.hs
+++ b/compiler/typecheck/TcUnify.hs
@@ -40,7 +40,7 @@ module TcUnify (
import GhcPrelude
-import HsSyn
+import GHC.Hs
import TyCoRep
import TcMType
import TcRnMonad
diff --git a/compiler/typecheck/TcUnify.hs-boot b/compiler/typecheck/TcUnify.hs-boot
index 295c85eb73..3b12153704 100644
--- a/compiler/typecheck/TcUnify.hs-boot
+++ b/compiler/typecheck/TcUnify.hs-boot
@@ -1,12 +1,12 @@
module TcUnify where
import GhcPrelude
-import TcType ( TcTauType )
-import TcRnTypes ( TcM )
-import TcEvidence ( TcCoercion )
-import HsExpr ( HsExpr )
-import HsTypes ( HsType )
-import HsExtension ( GhcRn )
+import TcType ( TcTauType )
+import TcRnTypes ( TcM )
+import TcEvidence ( TcCoercion )
+import GHC.Hs.Expr ( HsExpr )
+import GHC.Hs.Types ( HsType )
+import GHC.Hs.Extension ( GhcRn )
-- This boot file exists only to tie the knot between
-- TcUnify and Inst
diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index 045f3c9f18..eaec2dbd2f 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -42,7 +42,7 @@ import TyCon
-- others:
import IfaceType( pprIfaceType, pprIfaceTypeApp )
import ToIface ( toIfaceTyCon, toIfaceTcArgs, toIfaceType )
-import HsSyn -- HsType
+import GHC.Hs -- HsType
import TcRnMonad -- TcType, amongst others
import TcEnv ( tcInitTidyEnv, tcInitOpenTidyEnv )
import FunDeps
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 45fdb411ab..19f3f0ee56 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -398,7 +398,7 @@ invariant that if `famTcInj` is a Just then at least one element in the list
must be True.
See also:
- * [Injectivity annotation] in HsDecls
+ * [Injectivity annotation] in GHC.Hs.Decls
* [Renaming injectivity annotation] in RnSource
* [Verifying injectivity annotation] in FamInstEnv
* [Type inference for type families with injectivity] in TcInteract
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index f574132c4f..39a07c2fed 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -3131,7 +3131,7 @@ There are a couple of places in GHC where we convert Core Types into forms that
more closely resemble user-written syntax. These include:
1. Template Haskell Type reification (see, for instance, TcSplice.reify_tc_app)
-2. Converting Types to LHsTypes (in HsUtils.typeToLHsType, or in Haddock)
+2. Converting Types to LHsTypes (in GHC.Hs.Utils.typeToLHsType, or in Haddock)
This conversion presents a challenge: how do we ensure that the resulting type
has enough kind information so as not to be ambiguous? To better motivate this
@@ -3171,7 +3171,7 @@ require a kind signature? It might require it when we need to fill in any of
T's omitted arguments. By "omitted argument", we mean one that is dropped when
reifying ty_1 ... ty_n. Sometimes, the omitted arguments are inferred and
specified arguments (e.g., TH reification in TcSplice), and sometimes the
-omitted arguments are only the inferred ones (e.g., in HsUtils.typeToLHsType,
+omitted arguments are only the inferred ones (e.g., in GHC.Hs.Utils.typeToLHsType,
which reifies specified arguments through visible kind application).
Regardless, the key idea is that _some_ arguments are going to be omitted after
reification, and the only mechanism we have at our disposal for filling them in
@@ -3269,7 +3269,7 @@ each form of tycon binder:
injective_vars_of_binder(forall a. ...) = {a}.)
There are some situations where using visible kind application is appropriate
- (e.g., HsUtils.typeToLHsType) and others where it is not (e.g., TH
+ (e.g., GHC.Hs.Utils.typeToLHsType) and others where it is not (e.g., TH
reification), so the `injective_vars_of_binder` function is parametrized by
a Bool which decides if specified binders should be counted towards
injective positions or not.
diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst
index 6b6a1ed3cb..7035e02465 100644
--- a/docs/users_guide/extending_ghc.rst
+++ b/docs/users_guide/extending_ghc.rst
@@ -752,13 +752,13 @@ displayed.
import Plugins
import HscTypes
import TcRnTypes
- import HsExtension
- import HsDecls
- import HsExpr
- import HsImpExp
+ import GHC.Hs.Extension
+ import GHC.Hs.Decls
+ import GHC.Hs.Expr
+ import GHC.Hs.ImpExp
import Avail
import Outputable
- import HsDoc
+ import GHC.Hs.Doc
plugin :: Plugin
plugin = defaultPlugin
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index f5cae41578..87204824d1 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -52,8 +52,8 @@ import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..),
GetDocsFailure(..),
getModuleGraph, handleSourceError )
import HscMain (hscParseDeclsWithLocation, hscParseStmtWithLocation)
-import HsImpExp
-import HsSyn
+import GHC.Hs.ImpExp
+import GHC.Hs
import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC,
setInteractivePrintName, hsc_dflags, msObjFilePath, runInteractiveHsc,
hsc_dynLinker )
diff --git a/ghc/GHCi/UI/Monad.hs b/ghc/GHCi/UI/Monad.hs
index 8bdeb04834..aa09af2f15 100644
--- a/ghc/GHCi/UI/Monad.hs
+++ b/ghc/GHCi/UI/Monad.hs
@@ -51,8 +51,8 @@ import RdrName (mkOrig)
import PrelNames (gHC_GHCI_HELPERS)
import GHCi
import GHCi.RemoteTypes
-import HsSyn (ImportDecl, GhcPs, GhciLStmt, LHsDecl)
-import HsUtils
+import GHC.Hs (ImportDecl, GhcPs, GhciLStmt, LHsDecl)
+import GHC.Hs.Utils
import Util
import Exception
diff --git a/nofib b/nofib
-Subproject 52e761b9bc05e4b90f0a9d780a0f2cae9cbbb67
+Subproject a6cbac8fd8c69d85fddfde0a2686607e1ae2294
diff --git a/testsuite/tests/ghc-api/annotations/stringSource.hs b/testsuite/tests/ghc-api/annotations/stringSource.hs
index 1b5803b817..8bae838672 100644
--- a/testsuite/tests/ghc-api/annotations/stringSource.hs
+++ b/testsuite/tests/ghc-api/annotations/stringSource.hs
@@ -17,7 +17,7 @@ import FastString
import ForeignCall
import MonadUtils
import Outputable
-import HsDecls
+import GHC.Hs.Decls
import Bag (filterBag,isEmptyBag)
import System.Directory (removeFile)
import System.Environment( getArgs )
diff --git a/testsuite/tests/ghc-api/annotations/t11430.hs b/testsuite/tests/ghc-api/annotations/t11430.hs
index 232d47ff98..f161e601ce 100644
--- a/testsuite/tests/ghc-api/annotations/t11430.hs
+++ b/testsuite/tests/ghc-api/annotations/t11430.hs
@@ -17,7 +17,7 @@ import FastString
import ForeignCall
import MonadUtils
import Outputable
-import HsDecls
+import GHC.Hs.Decls
import Bag (filterBag,isEmptyBag)
import System.Directory (removeFile)
import System.Environment( getArgs )
diff --git a/testsuite/tests/package/all.T b/testsuite/tests/package/all.T
index 869abb1a7a..8fe654fb7d 100644
--- a/testsuite/tests/package/all.T
+++ b/testsuite/tests/package/all.T
@@ -1,7 +1,7 @@
hide_all = '-hide-all-packages -XNoImplicitPrelude '
incr_containers = '-package "containers (Data.Map as Map, Data.Set)" '
inc_containers = '-package containers '
-incr_ghc = '-package "ghc (HsTypes as MyHsTypes, HsUtils)" '
+incr_ghc = '-package "ghc (GHC.Hs.Types as GHC.Hs.MyTypes, GHC.Hs.Utils)" '
inc_ghc = '-package ghc '
hide_ghc = '-hide-package ghc '
diff --git a/testsuite/tests/package/package05.hs b/testsuite/tests/package/package05.hs
index 3b0069c5d5..e2c1125321 100644
--- a/testsuite/tests/package/package05.hs
+++ b/testsuite/tests/package/package05.hs
@@ -1,4 +1,4 @@
module Package05 where
-import HsTypes
-import MyHsTypes
-import HsUtils
+import GHC.Hs.Types
+import GHC.Hs.MyTypes
+import GHC.Hs.Utils
diff --git a/testsuite/tests/package/package06.hs b/testsuite/tests/package/package06.hs
index 096b81b7ba..ce9ce6fb84 100644
--- a/testsuite/tests/package/package06.hs
+++ b/testsuite/tests/package/package06.hs
@@ -1,3 +1,3 @@
module Package06 where
-import MyHsTypes
-import HsUtils
+import GHC.Hs.MyTypes
+import GHC.Hs.Utils
diff --git a/testsuite/tests/package/package06e.hs b/testsuite/tests/package/package06e.hs
index 6feaebda62..35b6ceaa76 100644
--- a/testsuite/tests/package/package06e.hs
+++ b/testsuite/tests/package/package06e.hs
@@ -1,3 +1,3 @@
module Package06e where
-import HsTypes
+import GHC.Hs.Types
import UniqFM
diff --git a/testsuite/tests/package/package06e.stderr b/testsuite/tests/package/package06e.stderr
index 12d721223c..98f048c107 100644
--- a/testsuite/tests/package/package06e.stderr
+++ b/testsuite/tests/package/package06e.stderr
@@ -1,6 +1,6 @@
package06e.hs:2:1: error:
- Could not load module ‘HsTypes’
+ Could not load module ‘GHC.Hs.Types’
It is a member of the hidden package ‘ghc-8.7’.
You can run ‘:set -package ghc’ to expose it.
(Note: this unloads all the modules in the current scope.)
diff --git a/testsuite/tests/package/package07e.hs b/testsuite/tests/package/package07e.hs
index 85bb723989..df13ed734e 100644
--- a/testsuite/tests/package/package07e.hs
+++ b/testsuite/tests/package/package07e.hs
@@ -1,5 +1,5 @@
module Package07e where
-import MyHsTypes
-import HsTypes
-import HsUtils
+import GHC.Hs.MyTypes
+import GHC.Hs.Types
+import GHC.Hs.Utils
import UniqFM
diff --git a/testsuite/tests/package/package07e.stderr b/testsuite/tests/package/package07e.stderr
index 2678972a78..5f5f0b9885 100644
--- a/testsuite/tests/package/package07e.stderr
+++ b/testsuite/tests/package/package07e.stderr
@@ -1,18 +1,18 @@
package07e.hs:2:1: error:
- Could not find module ‘MyHsTypes’
- Perhaps you meant HsTypes (needs flag -package-key ghc-8.7)
+ Could not find module ‘GHC.Hs.MyTypes’
+ Perhaps you meant GHC.Hs.Types (needs flag -package-key ghc-8.7)
Use -v (or `:set -v` in ghci) to see a list of the files searched for.
package07e.hs:3:1: error:
- Could not load module ‘HsTypes’
+ Could not load module ‘GHC.Hs.Types’
It is a member of the hidden package ‘ghc-8.7’.
You can run ‘:set -package ghc’ to expose it.
(Note: this unloads all the modules in the current scope.)
Use -v (or `:set -v` in ghci) to see a list of the files searched for.
package07e.hs:4:1: error:
- Could not load module ‘HsUtils’
+ Could not load module ‘GHC.Hs.Utils’
It is a member of the hidden package ‘ghc-8.7’.
You can run ‘:set -package ghc’ to expose it.
(Note: this unloads all the modules in the current scope.)
diff --git a/testsuite/tests/package/package08e.hs b/testsuite/tests/package/package08e.hs
index 40f814449a..aba05de9ca 100644
--- a/testsuite/tests/package/package08e.hs
+++ b/testsuite/tests/package/package08e.hs
@@ -1,5 +1,5 @@
module Package08e where
-import MyHsTypes
-import HsTypes
-import HsUtils
+import GHC.Hs.MyTypes
+import GHC.Hs.Types
+import GHC.Hs.Utils
import UniqFM
diff --git a/testsuite/tests/package/package08e.stderr b/testsuite/tests/package/package08e.stderr
index f02e9d6da3..46d665bceb 100644
--- a/testsuite/tests/package/package08e.stderr
+++ b/testsuite/tests/package/package08e.stderr
@@ -1,18 +1,18 @@
package08e.hs:2:1: error:
- Could not find module ‘MyHsTypes’
- Perhaps you meant HsTypes (needs flag -package-key ghc-8.7)
+ Could not find module ‘GHC.Hs.MyTypes’
+ Perhaps you meant GHC.Hs.Types (needs flag -package-key ghc-8.7)
Use -v (or `:set -v` in ghci) to see a list of the files searched for.
package08e.hs:3:1: error:
- Could not load module ‘HsTypes’
+ Could not load module ‘GHC.Hs.Types’
It is a member of the hidden package ‘ghc-8.7’.
You can run ‘:set -package ghc’ to expose it.
(Note: this unloads all the modules in the current scope.)
Use -v (or `:set -v` in ghci) to see a list of the files searched for.
package08e.hs:4:1: error:
- Could not load module ‘HsUtils’
+ Could not load module ‘GHC.Hs.Utils’
It is a member of the hidden package ‘ghc-8.7’.
You can run ‘:set -package ghc’ to expose it.
(Note: this unloads all the modules in the current scope.)
diff --git a/testsuite/tests/parser/should_fail/readFail001.hs b/testsuite/tests/parser/should_fail/readFail001.hs
index 6b186922f3..a3faa1b5e5 100644
--- a/testsuite/tests/parser/should_fail/readFail001.hs
+++ b/testsuite/tests/parser/should_fail/readFail001.hs
@@ -51,7 +51,7 @@ instance (Eq a) => EqClass (Tree a) where
default (Integer, Rational)
--- HsBinds stuff
+-- GHC.Hs.Binds stuff
singlebind x = x
diff --git a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs
index 2d14eeaf85..fce8b7d136 100644
--- a/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs
+++ b/testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs
@@ -7,12 +7,12 @@ import Plugins
import Bag
import HscTypes
import TcRnTypes
-import HsExtension
-import HsExpr
+import GHC.Hs.Extension
+import GHC.Hs.Expr
import Outputable
import SrcLoc
-import HsSyn
-import HsBinds
+import GHC.Hs
+import GHC.Hs.Binds
import OccName
import RdrName
import Name
diff --git a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs
index b9bdaeb37a..cb5fc70550 100644
--- a/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs
+++ b/testsuite/tests/plugins/simple-plugin/Simple/SourcePlugin.hs
@@ -6,13 +6,13 @@ import Data.Maybe (isJust)
import Plugins
import HscTypes
import TcRnTypes
-import HsExtension
+import GHC.Hs.Extension
import Avail
-import HsExpr
+import GHC.Hs.Expr
import Outputable
-import HsImpExp
-import HsDecls
-import HsDoc
+import GHC.Hs.ImpExp
+import GHC.Hs.Decls
+import GHC.Hs.Doc
plugin :: Plugin
plugin = defaultPlugin { parsedResultAction = parsedPlugin
diff --git a/testsuite/tests/plugins/static-plugins.hs b/testsuite/tests/plugins/static-plugins.hs
index 36e18b86b5..3dd6aa2e6d 100644
--- a/testsuite/tests/plugins/static-plugins.hs
+++ b/testsuite/tests/plugins/static-plugins.hs
@@ -6,11 +6,11 @@ import DynFlags
(getDynFlags, parseDynamicFlagsCmdLine, defaultFatalMessager, defaultFlushOut)
import GHC
import GHC.Fingerprint.Type
-import HsDecls
-import HsDoc
-import HsExpr
-import HsExtension
-import HsImpExp
+import GHC.Hs.Decls
+import GHC.Hs.Doc
+import GHC.Hs.Expr
+import GHC.Hs.Extension
+import GHC.Hs.ImpExp
import HscTypes
import Outputable
import Plugins
diff --git a/testsuite/tests/pmcheck/should_compile/pmc009.hs b/testsuite/tests/pmcheck/should_compile/pmc009.hs
index ac8f5c2dd5..08f130de33 100644
--- a/testsuite/tests/pmcheck/should_compile/pmc009.hs
+++ b/testsuite/tests/pmcheck/should_compile/pmc009.hs
@@ -1,5 +1,5 @@
module HsUtils where
-import HsBinds
+import GHC.Hs.Binds
import SrcLoc
diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs
index a5aeee2f1d..8a86d02e7c 100644
--- a/utils/check-ppr/Main.hs
+++ b/utils/check-ppr/Main.hs
@@ -3,7 +3,7 @@
import Data.List
import SrcLoc
import GHC hiding (moduleName)
-import HsDumpAst
+import GHC.Hs.Dump
import DynFlags
import Outputable hiding (space)
import System.Environment( getArgs )
diff --git a/utils/haddock b/utils/haddock
-Subproject 75f71980dfcd9a009e2eeb3a8690a473f47fcdf
+Subproject 58933236f116a26a2827b0cb5c46947e4f056c7