diff options
Diffstat (limited to 'compiler/GHC/Hs')
-rw-r--r-- | compiler/GHC/Hs/Binds.hs | 26 | ||||
-rw-r--r-- | compiler/GHC/Hs/Decls.hs | 54 | ||||
-rw-r--r-- | compiler/GHC/Hs/Expr.hs | 82 | ||||
-rw-r--r-- | compiler/GHC/Hs/ImpExp.hs | 18 | ||||
-rw-r--r-- | compiler/GHC/Hs/Pat.hs | 26 | ||||
-rw-r--r-- | compiler/GHC/Hs/Types.hs | 54 | ||||
-rw-r--r-- | compiler/GHC/Hs/Utils.hs | 6 |
7 files changed, 133 insertions, 133 deletions
diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs index 54718d289f..5068f082ce 100644 --- a/compiler/GHC/Hs/Binds.hs +++ b/compiler/GHC/Hs/Binds.hs @@ -218,7 +218,7 @@ data HsBindLR idL idR -- - 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere', -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation FunBind { fun_ext :: XFunBind idL idR, @@ -259,7 +259,7 @@ data HsBindLR idL idR -- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere', -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | PatBind { pat_ext :: XPatBind idL idR, -- ^ See Note [Bind free vars] pat_lhs :: LPat idL, @@ -310,7 +310,7 @@ data HsBindLR idL idR -- 'ApiAnnotation.AnnWhere' -- 'ApiAnnotation.AnnOpen' @'{'@,'ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XHsBindsLR !(XXHsBindsLR idL idR) @@ -365,7 +365,7 @@ type instance XXABExport (GhcPass p) = NoExtCon -- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@, --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Pattern Synonym binding data PatSynBind idL idR @@ -824,7 +824,7 @@ type LIPBind id = Located (IPBind id) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when in a -- list --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Implicit parameter bindings. -- @@ -835,7 +835,7 @@ type LIPBind id = Located (IPBind id) -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data IPBind id = IPBind (XCIPBind id) @@ -890,7 +890,7 @@ data Sig pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon', -- 'ApiAnnotation.AnnComma' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation TypeSig (XTypeSig pass) [Located (IdP pass)] -- LHS of the signature; e.g. f,g,h :: blah @@ -904,7 +904,7 @@ data Sig pass -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnForall' -- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass) -- P :: forall a b. Req => Prov => ty @@ -935,7 +935,7 @@ data Sig pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInfix', -- 'ApiAnnotation.AnnVal' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | FixSig (XFixSig pass) (FixitySig pass) -- | An inline pragma @@ -948,7 +948,7 @@ data Sig pass -- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnTilde', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | InlineSig (XInlineSig pass) (Located (IdP pass)) -- Function name InlinePragma -- Never defaultInlinePragma @@ -964,7 +964,7 @@ data Sig pass -- 'ApiAnnotation.AnnClose' @']'@ and @'\#-}'@, -- 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | SpecSig (XSpecSig pass) (Located (IdP pass)) -- Specialise a function or datatype ... [LHsSigType pass] -- ... to these types @@ -982,7 +982,7 @@ data Sig pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnInstance','ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass) -- Note [Pragma source text] in GHC.Types.Basic @@ -994,7 +994,7 @@ data Sig pass -- 'ApiAnnotation.AnnVbar','ApiAnnotation.AnnComma', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | MinimalSig (XMinimalSig pass) SourceText (LBooleanFormula (Located (IdP pass))) -- Note [Pragma source text] in GHC.Types.Basic diff --git a/compiler/GHC/Hs/Decls.hs b/compiler/GHC/Hs/Decls.hs index c3388b6362..0be89127a5 100644 --- a/compiler/GHC/Hs/Decls.hs +++ b/compiler/GHC/Hs/Decls.hs @@ -135,7 +135,7 @@ type LHsDecl p = Located (HsDecl p) -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' -- --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | A Haskell Declaration data HsDecl p @@ -452,7 +452,7 @@ have (Just binds) in the tcdMeths field, whereas interface decls have Nothing. In *source-code* class declarations: - When parsing, every ClassOpSig gets a DefMeth with a suitable RdrName - This is done by RdrHsSyn.mkClassOpSigDM + This is done by GHC.Parser.PostProcess.mkClassOpSigDM - The renamer renames it to a Name @@ -546,7 +546,7 @@ data TyClDecl pass -- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnRarrow', -- 'ApiAnnotation.AnnVbar' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation FamDecl { tcdFExt :: XFamDecl pass, tcdFam :: FamilyDecl pass } | -- | @type@ declaration @@ -554,7 +554,7 @@ data TyClDecl pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType', -- 'ApiAnnotation.AnnEqual', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation SynDecl { tcdSExt :: XSynDecl pass -- ^ Post renameer, FVs , tcdLName :: Located (IdP pass) -- ^ Type constructor , tcdTyVars :: LHsQTyVars pass -- ^ Type variables; for an @@ -571,7 +571,7 @@ data TyClDecl pass -- 'ApiAnnotation.AnnNewType','ApiAnnotation.AnnDcolon' -- 'ApiAnnotation.AnnWhere', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation DataDecl { tcdDExt :: XDataDecl pass -- ^ Post renamer, CUSK flag, FVs , tcdLName :: Located (IdP pass) -- ^ Type constructor , tcdTyVars :: LHsQTyVars pass -- ^ Type variables @@ -598,7 +598,7 @@ data TyClDecl pass -- 'ApiAnnotation.AnnComma' -- 'ApiAnnotation.AnnRarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XTyClDecl !(XXTyClDecl pass) type LHsFunDep pass = Located (FunDep (Located (IdP pass))) @@ -1047,14 +1047,14 @@ data FamilyResultSig pass = -- see Note [FamilyResultSig] NoSig (XNoSig pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | KindSig (XCKindSig pass) (LHsKind pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : -- 'ApiAnnotation.AnnOpenP','ApiAnnotation.AnnDcolon', -- 'ApiAnnotation.AnnCloseP' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | TyVarSig (XTyVarSig pass) (LHsTyVarBndr pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : @@ -1062,7 +1062,7 @@ data FamilyResultSig pass = -- see Note [FamilyResultSig] -- 'ApiAnnotation.AnnCloseP', 'ApiAnnotation.AnnEqual' | XFamilyResultSig !(XXFamilyResultSig pass) - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation type instance XNoSig (GhcPass _) = NoExtField type instance XCKindSig (GhcPass _) = NoExtField @@ -1093,7 +1093,7 @@ data FamilyDecl pass = FamilyDecl -- 'ApiAnnotation.AnnEqual', 'ApiAnnotation.AnnRarrow', -- 'ApiAnnotation.AnnVbar' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation type instance XCFamilyDecl (GhcPass _) = NoExtField type instance XXFamilyDecl (GhcPass _) = NoExtCon @@ -1115,7 +1115,7 @@ data InjectivityAnn pass -- ^ - 'ApiAnnotation.AnnKeywordId' : -- 'ApiAnnotation.AnnRarrow', 'ApiAnnotation.AnnVbar' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation data FamilyInfo pass = DataFamily @@ -1231,7 +1231,7 @@ data HsDataDefn pass -- The payload of a data type defn dd_derivs :: HsDeriving pass -- ^ Optional 'deriving' clause - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation } | XHsDataDefn !(XXHsDataDefn pass) @@ -1348,7 +1348,7 @@ type LConDecl pass = Located (ConDecl pass) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when -- in a GADT constructor list - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | -- @@ -1372,7 +1372,7 @@ type LConDecl pass = Located (ConDecl pass) -- 'ApiAnnotation.AnnDarrow','ApiAnnotation.AnnDarrow', -- 'ApiAnnotation.AnnForall','ApiAnnotation.AnnDot' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | data Constructor Declaration data ConDecl pass @@ -1444,7 +1444,7 @@ There's a wrinkle in ConDeclGADT so it's hard to split up the arguments until we've done the precedence resolution (in the renamer). - So: - In the parser (RdrHsSyn.mkGadtDecl), we put the whole constr + So: - In the parser (GHC.Parser.PostProcess.mkGadtDecl), we put the whole constr type into the res_ty for a ConDeclGADT for now, and use PrefixCon [] con_args = PrefixCon [] @@ -1593,7 +1593,7 @@ type LTyFamInstEqn pass = Located (TyFamInstEqn pass) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' -- when in a list --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Haskell Type Patterns type HsTyPats pass = [LHsTypeArg pass] @@ -1652,7 +1652,7 @@ newtype TyFamInstDecl pass = TyFamInstDecl { tfid_eqn :: TyFamInstEqn pass } -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType', -- 'ApiAnnotation.AnnInstance', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ----------------- Data family instances ------------- @@ -1669,7 +1669,7 @@ newtype DataFamInstDecl pass -- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ----------------- Family instances (common types) ------------- @@ -1700,7 +1700,7 @@ data FamEqn pass rhs -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual' | XFamEqn !(XXFamEqn pass rhs) - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation type instance XCFamEqn (GhcPass _) r = NoExtField type instance XXFamEqn (GhcPass _) r = NoExtCon @@ -1725,14 +1725,14 @@ data ClsInstDecl pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation } -- ^ -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInstance', -- 'ApiAnnotation.AnnWhere', -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XClsInstDecl !(XXClsInstDecl pass) type instance XCClsInstDecl (GhcPass _) = NoExtField @@ -1922,7 +1922,7 @@ data DerivDecl pass = DerivDecl -- 'ApiAnnotation.AnnAnyClass', 'Api.AnnNewtype', -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation } | XDerivDecl !(XXDerivDecl pass) @@ -2023,7 +2023,7 @@ data DefaultDecl pass -- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnDefault', -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XDefaultDecl !(XXDefaultDecl pass) type instance XCDefaultDecl (GhcPass _) = NoExtField @@ -2069,7 +2069,7 @@ data ForeignDecl pass -- 'ApiAnnotation.AnnImport','ApiAnnotation.AnnExport', -- 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XForeignDecl !(XXForeignDecl pass) {- @@ -2250,7 +2250,7 @@ data RuleBndr pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation type instance XCRuleBndr (GhcPass _) = NoExtField type instance XRuleBndrSig (GhcPass _) = NoExtField @@ -2386,7 +2386,7 @@ data AnnDecl pass = HsAnnotation -- 'ApiAnnotation.AnnModule' -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XAnnDecl !(XXAnnDecl pass) type instance XHsAnnotation (GhcPass _) = NoExtField @@ -2438,7 +2438,7 @@ data RoleAnnotDecl pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType', -- 'ApiAnnotation.AnnRole' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XRoleAnnotDecl !(XXRoleAnnotDecl pass) type instance XCRoleAnnotDecl (GhcPass _) = NoExtField diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs index 050ba91d6b..d52f9cac65 100644 --- a/compiler/GHC/Hs/Expr.hs +++ b/compiler/GHC/Hs/Expr.hs @@ -47,7 +47,7 @@ import Util import Outputable import FastString import GHC.Core.Type -import TysWiredIn (mkTupleStr) +import GHC.Builtin.Types (mkTupleStr) import GHC.Tc.Utils.TcType (TcType) import {-# SOURCE #-} GHC.Tc.Types (TcLclEnv) @@ -75,7 +75,7 @@ type LHsExpr p = Located (HsExpr p) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when -- in a list - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ------------------------- -- | Post-Type checking Expression @@ -281,7 +281,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam', -- 'ApiAnnotation.AnnRarrow', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p)) -- ^ Lambda-case -- @@ -289,7 +289,7 @@ data HsExpr p -- 'ApiAnnotation.AnnCase','ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsApp (XApp p) (LHsExpr p) (LHsExpr p) -- ^ Application @@ -316,7 +316,7 @@ data HsExpr p -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnMinus' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | NegApp (XNegApp p) (LHsExpr p) (SyntaxExpr p) @@ -324,7 +324,7 @@ data HsExpr p -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsPar (XPar p) (LHsExpr p) -- ^ Parenthesised expr; see Note [Parens in HsSyn] @@ -340,7 +340,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- Note [ExplicitTuple] | ExplicitTuple (XExplicitTuple p) @@ -364,7 +364,7 @@ data HsExpr p -- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCase (XCase p) (LHsExpr p) (MatchGroup p (LHsExpr p)) @@ -374,7 +374,7 @@ data HsExpr p -- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi', -- 'ApiAnnotation.AnnElse', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsIf (XIf p) -- GhcPs: this is a Bool; False <=> do not use -- rebindable syntax (SyntaxExpr p) -- cond function @@ -389,7 +389,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnIf' -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)] -- | let(rec) @@ -398,7 +398,7 @@ data HsExpr p -- 'ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsLet (XLet p) (LHsLocalBinds p) (LHsExpr p) @@ -408,7 +408,7 @@ data HsExpr p -- 'ApiAnnotation.AnnVbar', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsDo (XDo p) -- Type of the whole expression (HsStmtContext GhcRn) -- The parameterisation is unimportant -- because in this context we never use @@ -420,7 +420,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@, -- 'ApiAnnotation.AnnClose' @']'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- See Note [Empty lists] | ExplicitList (XExplicitList p) -- Gives type of components of list @@ -433,7 +433,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | RecordCon { rcon_ext :: XRecordCon p , rcon_con_name :: Located (IdP p) -- The constructor name; @@ -445,7 +445,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | RecordUpd { rupd_ext :: XRecordUpd p , rupd_expr :: LHsExpr p @@ -458,7 +458,7 @@ data HsExpr p -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | ExprWithTySig (XExprWithTySig p) @@ -471,14 +471,14 @@ data HsExpr p -- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnDotdot', -- 'ApiAnnotation.AnnClose' @']'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | ArithSeq (XArithSeq p) (Maybe (SyntaxExpr p)) -- For OverloadedLists, the fromList witness (ArithSeqInfo p) - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ----------------------------------------------------------- -- MetaHaskell Extensions @@ -487,7 +487,7 @@ data HsExpr p -- 'ApiAnnotation.AnnOpenE','ApiAnnotation.AnnOpenEQ', -- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnCloseQ' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsBracket (XBracket p) (HsBracket p) -- See Note [Pending Splices] @@ -509,7 +509,7 @@ data HsExpr p -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsSpliceE (XSpliceE p) (HsSplice p) ----------------------------------------------------------- @@ -520,7 +520,7 @@ data HsExpr p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnProc', -- 'ApiAnnotation.AnnRarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsProc (XProc p) (LPat p) -- arrow abstraction, proc (LHsCmdTop p) -- body of the abstraction @@ -530,7 +530,7 @@ data HsExpr p -- static pointers extension -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnStatic', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsStatic (XStatic p) -- Free variables of the body (LHsExpr p) -- Body @@ -681,7 +681,7 @@ data HsPragE p -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CORE'@, -- 'ApiAnnotation.AnnVal', 'ApiAnnotation.AnnClose' @'\#-}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsPragCore (XCoreAnn p) SourceText -- Note [Pragma source text] in GHC.Types.Basic StringLiteral -- hdaume: core annotation @@ -695,7 +695,7 @@ data HsPragE p -- 'ApiAnnotation.AnnVal', -- 'ApiAnnotation.AnnClose' @'\#-}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsPragTick -- A pragma introduced tick (XTickPragma p) SourceText -- Note [Pragma source text] in GHC.Types.Basic @@ -721,7 +721,7 @@ type instance XXPragE (GhcPass _) = NoExtCon type LHsTupArg id = Located (HsTupArg id) -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Haskell Tuple Argument data HsTupArg id @@ -841,7 +841,7 @@ A tuple data constructor like () or (,,,) is parsed as an `HsVar`, not an Sadly, the grammar for this is actually ambiguous, and it's only thanks to the preference of a shift in a shift/reduce conflict that the parser works as this -Note details. Search for a reference to this Note in Parser.y for further +Note details. Search for a reference to this Note in GHC.Parser for further explanation. Note [Empty lists] @@ -853,7 +853,7 @@ various phases and why. Parsing ------- An empty list is parsed by the sysdcon nonterminal. It thus comes to life via -HsVar nilDataCon (defined in TysWiredIn). A freshly-parsed (HsExpr GhcPs) empty list +HsVar nilDataCon (defined in GHC.Builtin.Types). A freshly-parsed (HsExpr GhcPs) empty list is never a ExplicitList. Renaming @@ -1270,7 +1270,7 @@ data HsCmd id -- 'ApiAnnotation.Annrarrowtail','ApiAnnotation.AnnLarrowtail', -- 'ApiAnnotation.AnnRarrowtail' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation = HsCmdArrApp -- Arrow tail, or arrow application (f -< arg) (XCmdArrApp id) -- type of the arrow expressions f, -- of the form a t t', where arg :: t @@ -1283,7 +1283,7 @@ data HsCmd id -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpenB' @'(|'@, -- 'ApiAnnotation.AnnCloseB' @'|)'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdArrForm -- Command formation, (| e cmd1 .. cmdn |) (XCmdArrForm id) (LHsExpr id) -- The operator. @@ -1304,14 +1304,14 @@ data HsCmd id -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam', -- 'ApiAnnotation.AnnRarrow', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdPar (XCmdPar id) (LHsCmd id) -- parenthesised command -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdCase (XCmdCase id) (LHsExpr id) @@ -1320,7 +1320,7 @@ data HsCmd id -- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdIf (XCmdIf id) (SyntaxExpr id) -- cond function @@ -1332,7 +1332,7 @@ data HsCmd id -- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi', -- 'ApiAnnotation.AnnElse', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdLet (XCmdLet id) (LHsLocalBinds id) -- let(rec) @@ -1341,7 +1341,7 @@ data HsCmd id -- 'ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsCmdDo (XCmdDo id) -- Type of the whole expression (Located [CmdLStmt id]) @@ -1350,7 +1350,7 @@ data HsCmd id -- 'ApiAnnotation.AnnVbar', -- 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XCmd !(XXCmd id) -- Note [Trees that Grow] extension point @@ -1567,7 +1567,7 @@ type LMatch id body = Located (Match id body) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when in a -- list --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data Match p body = Match { m_ext :: XCMatch p body, @@ -1659,7 +1659,7 @@ hsLMatchPats (L _ (Match { m_pats = pats })) = pats -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose' -- 'ApiAnnotation.AnnRarrow','ApiAnnotation.AnnSemi' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data GRHSs p body = GRHSs { grhssExt :: XCGRHSs p body, @@ -1809,7 +1809,7 @@ type GhciStmt id = Stmt id (LHsExpr id) -- 'ApiAnnotation.AnnBy','ApiAnnotation.AnnBy', -- 'ApiAnnotation.AnnGroup','ApiAnnotation.AnnUsing' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data StmtLR idL idR body -- body should always be (LHs**** idR) = LastStmt -- Always the last Stmt in ListComp, MonadComp, -- and (after the renamer, see GHC.Rename.Expr.checkLastStmt) DoExpr, MDoExpr @@ -1827,7 +1827,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- See Note [Monad Comprehensions] -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | BindStmt (XBindStmt idL idR body) -- ^ Post renaming has optional fail and bind / (>>=) operator. -- Post typechecking, also has result type of the @@ -1861,7 +1861,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet' -- 'ApiAnnotation.AnnOpen' @'{'@,'ApiAnnotation.AnnClose' @'}'@, - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR) -- ParStmts only occur in a list/monad comprehension @@ -1899,7 +1899,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR) -- Recursive statement (see Note [How RecStmt works] below) -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRec' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | RecStmt { recS_ext :: XRecStmt idL idR body , recS_stmts :: [LStmtLR idL idR body] diff --git a/compiler/GHC/Hs/ImpExp.hs b/compiler/GHC/Hs/ImpExp.hs index f0f62b9fb6..d4ed3e64a0 100644 --- a/compiler/GHC/Hs/ImpExp.hs +++ b/compiler/GHC/Hs/ImpExp.hs @@ -48,7 +48,7 @@ type LImportDecl pass = Located (ImportDecl pass) -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | If/how an import is 'qualified'. data ImportDeclQualifiedStyle @@ -59,7 +59,7 @@ data ImportDeclQualifiedStyle -- | Given two possible located 'qualified' tokens, compute a style -- (in a conforming Haskell program only one of the two can be not --- 'Nothing'). This is called from 'Parser.y'. +-- 'Nothing'). This is called from 'GHC.Parser'. importDeclQualifiedStyle :: Maybe (Located a) -> Maybe (Located a) -> ImportDeclQualifiedStyle @@ -107,7 +107,7 @@ data ImportDecl pass -- 'ApiAnnotation.AnnClose' attached -- to location in ideclHiding - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation type instance XCImportDecl (GhcPass _) = NoExtField type instance XXImportDecl (GhcPass _) = NoExtCon @@ -189,7 +189,7 @@ data IEWrappedName name -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnType', -- 'ApiAnnotation.AnnPattern' type LIEWrappedName name = Located (IEWrappedName name) --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Located Import or Export @@ -198,7 +198,7 @@ type LIE pass = Located (IE pass) -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Imported or exported entity. data IE pass @@ -212,7 +212,7 @@ data IE pass -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern', -- 'ApiAnnotation.AnnType','ApiAnnotation.AnnVal' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- See Note [Located RdrNames] in GHC.Hs.Expr | IEThingAll (XIEThingAll pass) (LIEWrappedName (IdP pass)) -- ^ Imported or exported Thing with All imported or exported @@ -223,7 +223,7 @@ data IE pass -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose', -- 'ApiAnnotation.AnnType' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- See Note [Located RdrNames] in GHC.Hs.Expr | IEThingWith (XIEThingWith pass) @@ -240,7 +240,7 @@ data IE pass -- 'ApiAnnotation.AnnComma', -- 'ApiAnnotation.AnnType' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | IEModuleContents (XIEModuleContents pass) (Located ModuleName) -- ^ Imported or exported module contents -- @@ -248,7 +248,7 @@ data IE pass -- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnModule' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | IEGroup (XIEGroup pass) Int HsDocString -- ^ Doc section heading | IEDoc (XIEDoc pass) HsDocString -- ^ Some documentation | IEDocNamed (XIEDocNamed pass) String -- ^ Reference to named doc diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs index bfa8bb9ed0..2b5c871ab1 100644 --- a/compiler/GHC/Hs/Pat.hs +++ b/compiler/GHC/Hs/Pat.hs @@ -60,7 +60,7 @@ import GHC.Types.Basic -- others: import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} ) import GHC.Driver.Session ( gopt, GeneralFlag(Opt_PrintTypecheckerElaboration) ) -import TysWiredIn +import GHC.Builtin.Types import GHC.Types.Var import GHC.Types.Name.Reader ( RdrName ) import GHC.Core.ConLike @@ -83,7 +83,7 @@ type LPat p = XRec p Pat -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang' --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data Pat p = ------------ Simple patterns --------------- WildPat (XWildPat p) -- ^ Wildcard Pattern @@ -99,13 +99,13 @@ data Pat p (LPat p) -- ^ Lazy Pattern -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | AsPat (XAsPat p) (Located (IdP p)) (LPat p) -- ^ As pattern -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnAt' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | ParPat (XParPat p) (LPat p) -- ^ Parenthesised pattern @@ -113,12 +113,12 @@ data Pat p -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | BangPat (XBangPat p) (LPat p) -- ^ Bang pattern -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) @@ -132,7 +132,7 @@ data Pat p -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@, -- 'ApiAnnotation.AnnClose' @']'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | TuplePat (XTuplePat p) -- after typechecking, holds the types of the tuple components @@ -170,7 +170,7 @@ data Pat p -- 'ApiAnnotation.AnnOpen' @'(#'@, -- 'ApiAnnotation.AnnClose' @'#)'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation ------------ Constructor patterns --------------- | ConPatIn (Located (IdP p)) @@ -201,7 +201,7 @@ data Pat p ------------ View patterns --------------- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | ViewPat (XViewPat p) -- The overall type of the pattern -- (= the argument type of the view function) -- for hsPatType. @@ -213,7 +213,7 @@ data Pat p -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@ -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) (HsSplice p) -- ^ Splice Pattern (Includes quasi-quotes) @@ -239,7 +239,7 @@ data Pat p -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnVal' @'+'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | NPlusKPat (XNPlusKPat p) -- Type of overall pattern (Located (IdP p)) -- n+k pattern (Located (HsOverLit p)) -- It'll always be an HsIntegral @@ -254,7 +254,7 @@ data Pat p ------------ Pattern type signatures --------------- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (LHsSigWcType (NoGhcTc p)) -- Signature can bind both @@ -389,7 +389,7 @@ type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual', -- --- For details on above see note [Api annotations] in ApiAnnotation +-- For details on above see note [Api annotations] in GHC.Parser.Annotation data HsRecField' id arg = HsRecField { hsRecFieldLbl :: Located id, hsRecFieldArg :: arg, -- ^ Filled in by renamer when punning diff --git a/compiler/GHC/Hs/Types.hs b/compiler/GHC/Hs/Types.hs index d9a8ae3066..38a0300a8f 100644 --- a/compiler/GHC/Hs/Types.hs +++ b/compiler/GHC/Hs/Types.hs @@ -83,7 +83,7 @@ import GHC.Types.Name( Name, NamedThing(getName) ) import GHC.Types.Name.Reader ( RdrName ) import GHC.Core.DataCon( HsSrcBang(..), HsImplBang(..), SrcStrictness(..), SrcUnpackedness(..) ) -import TysWiredIn( mkTupleStr ) +import GHC.Builtin.Types( mkTupleStr ) import GHC.Core.Type import GHC.Hs.Doc import GHC.Types.Basic @@ -284,7 +284,7 @@ quantified in left-to-right order in kind signatures is nice since: -- | Located Haskell Context type LHsContext pass = Located (HsContext pass) -- ^ 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnUnit' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation noLHsContext :: LHsContext pass -- Use this when there is no context in the original program @@ -302,7 +302,7 @@ type LHsType pass = Located (HsType pass) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when -- in a list - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Haskell Kind type HsKind pass = HsType pass @@ -311,7 +311,7 @@ type HsKind pass = HsType pass type LHsKind pass = Located (HsKind pass) -- ^ 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -------------------------------------------------- -- LHsQTyVars @@ -495,7 +495,7 @@ data HsTyVarBndr pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen', -- 'ApiAnnotation.AnnDcolon', 'ApiAnnotation.AnnClose' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XTyVarBndr !(XXTyVarBndr pass) @@ -531,7 +531,7 @@ data HsType pass } -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnForall', -- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsQualTy -- See Note [HsType binders] { hst_xqual :: XQualTy pass @@ -547,14 +547,14 @@ data HsType pass -- See Note [Located RdrNames] in GHC.Hs.Expr -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsAppKindTy (XAppKindTy pass) -- type level type app (LHsType pass) @@ -565,14 +565,14 @@ data HsType pass (LHsType pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow', - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsListTy (XListTy pass) (LHsType pass) -- Element type -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@, -- 'ApiAnnotation.AnnClose' @']'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsTupleTy (XTupleTy pass) HsTupleSort @@ -580,20 +580,20 @@ data HsType pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(' or '(#'@, -- 'ApiAnnotation.AnnClose' @')' or '#)'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsSumTy (XSumTy pass) [LHsType pass] -- Element types (length gives arity) -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(#'@, -- 'ApiAnnotation.AnnClose' '#)'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsOpTy (XOpTy pass) (LHsType pass) (Located (IdP pass)) (LHsType pass) -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsParTy (XParTy pass) (LHsType pass) -- See Note [Parens in HsSyn] in GHC.Hs.Expr @@ -603,7 +603,7 @@ data HsType pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsIParamTy (XIParamTy pass) (Located HsIPName) -- (?x :: ty) @@ -614,7 +614,7 @@ data HsType pass -- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsStarTy (XStarTy pass) Bool -- Is this the Unicode variant? @@ -630,20 +630,20 @@ data HsType pass -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@, -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsSpliceTy (XSpliceTy pass) (HsSplice pass) -- Includes quasi-quotes -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsDocTy (XDocTy pass) (LHsType pass) LHsDocString -- A documented type -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsBangTy (XBangTy pass) HsSrcBang (LHsType pass) -- Bang-style type annotations @@ -652,20 +652,20 @@ data HsType pass -- 'ApiAnnotation.AnnClose' @'#-}'@ -- 'ApiAnnotation.AnnBang' @\'!\'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsRecTy (XRecTy pass) [LConDeclField pass] -- Only in data type declarations -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@, -- 'ApiAnnotation.AnnClose' @'}'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | HsCoreTy (XCoreTy pass) Type -- An escape hatch for tunnelling a *closed* -- -- Core Type through HsSyn. -- -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsExplicitListTy -- A promoted explicit list (XExplicitListTy pass) @@ -674,7 +674,7 @@ data HsType pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'["@, -- 'ApiAnnotation.AnnClose' @']'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsExplicitTupleTy -- A promoted explicit tuple (XExplicitTupleTy pass) @@ -682,18 +682,18 @@ data HsType pass -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'("@, -- 'ApiAnnotation.AnnClose' @')'@ - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsTyLit (XTyLit pass) HsTyLit -- A promoted numeric literal. -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | HsWildCardTy (XWildCardTy pass) -- A type wildcard -- See Note [The wildcard story for types] -- ^ - 'ApiAnnotation.AnnKeywordId' : None - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- For adding new constructors via Trees that Grow | XHsType @@ -857,7 +857,7 @@ type LConDeclField pass = Located (ConDeclField pass) -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when -- in a list - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation -- | Constructor Declaration Field data ConDeclField pass -- Record fields have Haddock docs on them @@ -868,7 +868,7 @@ data ConDeclField pass -- Record fields have Haddock docs on them cd_fld_doc :: Maybe LHsDocString } -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon' - -- For details on above see note [Api annotations] in ApiAnnotation + -- For details on above see note [Api annotations] in GHC.Parser.Annotation | XConDeclField !(XXConDeclField pass) type instance XConDeclField (GhcPass _) = NoExtField diff --git a/compiler/GHC/Hs/Utils.hs b/compiler/GHC/Hs/Utils.hs index 0a6c2a66a6..5daa380819 100644 --- a/compiler/GHC/Hs/Utils.hs +++ b/compiler/GHC/Hs/Utils.hs @@ -9,7 +9,7 @@ which deal with the instantiated versions are located elsewhere: Parameterised by Module ---------------- ------------- - GhcPs/RdrName parser/RdrHsSyn + GhcPs/RdrName GHC.Parser.PostProcess GhcRn/Name GHC.Rename.* GhcTc/Id GHC.Tc.Utils.Zonk @@ -116,7 +116,7 @@ import GHC.Types.Var import GHC.Core.TyCo.Rep import GHC.Core.TyCon import GHC.Core.Type ( appTyArgFlags, splitAppTys, tyConArgFlags, tyConAppNeedsKindSig ) -import TysWiredIn ( unitTy ) +import GHC.Builtin.Types ( unitTy ) import GHC.Tc.Utils.TcType import GHC.Core.DataCon import GHC.Core.ConLike @@ -130,7 +130,7 @@ import FastString import Util import Bag import Outputable -import Constants +import GHC.Settings.Constants import Data.Either import Data.Function |