summaryrefslogtreecommitdiff
path: root/compiler/hsSyn
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/hsSyn')
-rw-r--r--compiler/hsSyn/HsBinds.hs28
-rw-r--r--compiler/hsSyn/HsDecls.hs51
-rw-r--r--compiler/hsSyn/HsExpr.hs90
-rw-r--r--compiler/hsSyn/HsImpExp.hs17
-rw-r--r--compiler/hsSyn/HsLit.hs4
-rw-r--r--compiler/hsSyn/HsPat.hs24
-rw-r--r--compiler/hsSyn/HsSyn.hs11
-rw-r--r--compiler/hsSyn/HsTypes.hs60
8 files changed, 275 insertions, 10 deletions
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs
index ecd94c4d3c..429881ba12 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/hsSyn/HsBinds.hs
@@ -136,6 +136,8 @@ data HsBindLR idL idR
--
-- - 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
FunBind {
fun_id :: Located idL, -- Note [fun_id in Match] in HsExpr
@@ -173,6 +175,8 @@ data HsBindLR idL idR
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang',
-- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| PatBind {
pat_lhs :: LPat idL,
pat_rhs :: GRHSs idR (LHsExpr idR),
@@ -211,6 +215,8 @@ data HsBindLR idL idR
-- 'ApiAnnotation.AnnWhere'
-- 'ApiAnnotation.AnnOpen' @'{'@,'ApiAnnotation.AnnClose' @'}'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
deriving (Typeable)
deriving instance (DataId idL, DataId idR)
=> Data (HsBindLR idL idR)
@@ -239,6 +245,8 @@ data ABExport id
-- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnLarrow'
-- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@,
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data PatSynBind idL idR
= PSB { psb_id :: Located idL, -- ^ Name of the pattern synonym
psb_fvs :: PostRn idR NameSet, -- ^ See Note [Bind free vars]
@@ -554,6 +562,8 @@ 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
+
-- | Implicit parameter bindings.
--
-- These bindings start off as (Left "x") in the parser and stay
@@ -562,6 +572,8 @@ type LIPBind id = Located (IPBind id)
-- evidence for the implicit parameter.
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data IPBind id
= IPBind (Either (Located HsIPName) id) (LHsExpr id)
deriving (Typeable)
@@ -608,6 +620,8 @@ data Sig name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon',
-- 'ApiAnnotation.AnnComma'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
TypeSig [Located name] (LHsType name) (PostRn name [Name])
-- | A pattern synonym type signature
@@ -617,6 +631,8 @@ data Sig name
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnPattern',
-- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnForall'
-- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| PatSynSig (Located name)
(HsExplicitFlag, LHsTyVarBndrs name)
(LHsContext name) -- Provided context
@@ -629,6 +645,8 @@ data Sig name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDefault',
-- 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| GenericSig [Located name] (LHsType name)
-- | A type signature in generated code, notably the code
@@ -645,6 +663,8 @@ data Sig name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInfix',
-- 'ApiAnnotation.AnnVal'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| FixSig (FixitySig name)
-- | An inline pragma
@@ -656,6 +676,8 @@ data Sig name
-- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnTilde',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| InlineSig (Located name) -- Function name
InlinePragma -- Never defaultInlinePragma
@@ -669,6 +691,8 @@ data Sig name
-- 'ApiAnnotation.AnnVal',
-- 'ApiAnnotation.AnnClose' @']'@ and @'\#-}'@,
-- 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| SpecSig (Located name) -- Specialise a function or datatype ...
[LHsType name] -- ... to these types
InlinePragma -- The pragma on SPECIALISE_INLINE form.
@@ -684,6 +708,8 @@ data Sig name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnInstance','ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| SpecInstSig SourceText (LHsType name)
-- Note [Pragma source text] in BasicTypes
@@ -694,6 +720,8 @@ data Sig name
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnVbar','ApiAnnotation.AnnComma',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| MinimalSig SourceText (BooleanFormula (Located name))
-- Note [Pragma source text] in BasicTypes
diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs
index 3f37b52190..afd6e1e44b 100644
--- a/compiler/hsSyn/HsDecls.hs
+++ b/compiler/hsSyn/HsDecls.hs
@@ -124,6 +124,8 @@ type LHsDecl id = Located (HsDecl id)
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
--
+-- For details on above see note [Api annotations] in ApiAnnotation
+
-- | A Haskell Declaration
data HsDecl id
= TyClD (TyClDecl id) -- ^ A type or class declaration.
@@ -468,12 +470,15 @@ data TyClDecl name
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnDcolon',
-- 'ApiAnnotation.AnnClose'
+ -- For details on above see note [Api annotations] in ApiAnnotation
FamDecl { tcdFam :: FamilyDecl name }
| -- | @type@ declaration
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
-- 'ApiAnnotation.AnnEqual',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
SynDecl { tcdLName :: Located name -- ^ Type constructor
, tcdTyVars :: LHsTyVarBndrs name -- ^ Type variables; for an associated type
-- these include outer binders
@@ -486,6 +491,8 @@ data TyClDecl name
-- 'ApiAnnotation.AnnFamily',
-- 'ApiAnnotation.AnnNewType',
-- 'ApiAnnotation.AnnNewType','ApiAnnotation.AnnWhere'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
DataDecl { tcdLName :: Located name -- ^ Type constructor
, tcdTyVars :: LHsTyVarBndrs name -- ^ Type variables; for an assoicated type
-- these include outer binders
@@ -516,6 +523,8 @@ data TyClDecl name
-- 'ApiAnnotation.AnnComma'
-- 'ApiAnnotation.AnnRarrow'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
deriving (Typeable)
deriving instance (DataId id) => Data (TyClDecl id)
@@ -820,6 +829,8 @@ data HsDataDefn name -- The payload of a data type defn
-- - 'ApiAnnotation.AnnKeywordId' :
-- 'ApiAnnotation.AnnDeriving',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
}
deriving( Typeable )
deriving instance (DataId id) => Data (HsDataDefn id)
@@ -833,6 +844,8 @@ type LConDecl name = Located (ConDecl name)
-- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when
-- in a GADT constructor list
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
-- |
--
-- @
@@ -854,6 +867,8 @@ type LConDecl name = Located (ConDecl name)
-- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnVbar',
-- 'ApiAnnotation.AnnDarrow','ApiAnnotation.AnnDarrow',
-- 'ApiAnnotation.AnnForall','ApiAnnotation.AnnDot'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data ConDecl name
= ConDecl
{ con_names :: [Located name]
@@ -1027,6 +1042,9 @@ It is parameterised over its tfe_pats field:
type LTyFamInstEqn name = Located (TyFamInstEqn name)
-- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
-- when in a list
+
+-- For details on above see note [Api annotations] in ApiAnnotation
+
type LTyFamDefltEqn name = Located (TyFamDefltEqn name)
type HsTyPats name = HsWithBndrs name [LHsType name]
@@ -1046,6 +1064,8 @@ data TyFamEqn name pats
, tfe_rhs :: LHsType name }
-- ^
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving( Typeable )
deriving instance (DataId name, Data pats) => Data (TyFamEqn name pats)
@@ -1057,6 +1077,8 @@ data TyFamInstDecl name
-- ^
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
-- 'ApiAnnotation.AnnInstance',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving( Typeable )
deriving instance (DataId name) => Data (TyFamInstDecl name)
@@ -1075,6 +1097,8 @@ data DataFamInstDecl name
-- 'ApiAnnotation.AnnNewType','ApiAnnotation.AnnInstance',
-- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving( Typeable )
deriving instance (DataId name) => Data (DataFamInstDecl name)
@@ -1095,12 +1119,14 @@ data ClsInstDecl name
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose',
+ -- For details on above see note [Api annotations] in ApiAnnotation
}
-- ^
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInstance',
-- 'ApiAnnotation.AnnWhere',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId id) => Data (ClsInstDecl id)
@@ -1240,7 +1266,9 @@ data DerivDecl name = DerivDecl
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnDeriving',
- -- 'ApiAnnotation.AnnInstance',
+ -- 'ApiAnnotation.AnnInstance'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
}
deriving (Typeable)
deriving instance (DataId name) => Data (DerivDecl name)
@@ -1268,6 +1296,7 @@ data DefaultDecl name
-- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnDefault',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (DefaultDecl name)
@@ -1306,6 +1335,8 @@ data ForeignDecl name
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnForeign',
-- 'ApiAnnotation.AnnImport','ApiAnnotation.AnnExport',
-- 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (ForeignDecl name)
{-
@@ -1435,6 +1466,8 @@ data RuleDecl name
-- 'ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnForall','ApiAnnotation.AnnDot',
-- 'ApiAnnotation.AnnEqual',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (RuleDecl name)
@@ -1448,6 +1481,8 @@ data RuleBndr name
-- ^
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (RuleBndr name)
@@ -1497,11 +1532,15 @@ data VectDecl name
(LHsExpr name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsNoVect
SourceText -- Note [Pragma source text] in BasicTypes
(Located name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsVectTypeIn -- pre type-checking
SourceText -- Note [Pragma source text] in BasicTypes
Bool -- 'TRUE' => SCALAR declaration
@@ -1510,6 +1549,8 @@ data VectDecl name
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnType','ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnEqual'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsVectTypeOut -- post type-checking
Bool -- 'TRUE' => SCALAR declaration
TyCon
@@ -1519,6 +1560,8 @@ data VectDecl name
(Located name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClass','ApiAnnotation.AnnClose',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsVectClassOut -- post type-checking
Class
| HsVectInstIn -- pre type-checking (always SCALAR) !!!FIXME: should be superfluous now
@@ -1653,6 +1696,8 @@ data AnnDecl name = HsAnnotation
-- 'ApiAnnotation.AnnType'
-- 'ApiAnnotation.AnnModule'
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (AnnDecl name)
@@ -1696,6 +1741,8 @@ data RoleAnnotDecl name
[Located (Maybe Role)] -- optional annotations
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
-- 'ApiAnnotation.AnnRole'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Data, Typeable)
instance OutputableBndr name => Outputable (RoleAnnotDecl name) where
diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index c46c5948c3..7a66a50d46 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -55,6 +55,8 @@ type LHsExpr id = Located (HsExpr id)
-- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
-- in a list
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
-------------------------
-- | PostTcExpr is an evidence expression attached to the syntax tree by the
-- type checker (c.f. postTcType).
@@ -136,12 +138,16 @@ data HsExpr id
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
-- 'ApiAnnotation.AnnRarrow',
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsLamCase (PostTc id Type) (MatchGroup id (LHsExpr id)) -- ^ Lambda-case
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
-- 'ApiAnnotation.AnnCase','ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsApp (LHsExpr id) (LHsExpr id) -- ^ Application
-- | Operator applications:
@@ -159,11 +165,15 @@ data HsExpr id
-- of 'negate'
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnMinus'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| NegApp (LHsExpr id)
(SyntaxExpr id)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
-- 'ApiAnnotation.AnnClose' @')'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsPar (LHsExpr id) -- ^ Parenthesised expr; see Note [Parens in HsSyn]
| SectionL (LHsExpr id) -- operand; see Note [Sections in HsSyn]
@@ -175,6 +185,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ExplicitTuple
[LHsTupArg id]
Boxity
@@ -182,6 +194,8 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnCase',
-- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsCase (LHsExpr id)
(MatchGroup id (LHsExpr id))
@@ -189,6 +203,8 @@ data HsExpr id
-- 'ApiAnnotation.AnnSemi',
-- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi',
-- 'ApiAnnotation.AnnElse',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsIf (Maybe (SyntaxExpr id)) -- cond function
-- Nothing => use the built-in 'if'
-- See Note [Rebindable if]
@@ -200,6 +216,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnIf'
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsMultiIf (PostTc id Type) [LGRHS id (LHsExpr id)]
-- | let(rec)
@@ -207,6 +225,8 @@ data HsExpr id
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet',
-- 'ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsLet (HsLocalBinds id)
(LHsExpr id)
@@ -214,6 +234,8 @@ data HsExpr id
-- 'ApiAnnotation.AnnOpen', 'ApiAnnotation.AnnSemi',
-- 'ApiAnnotation.AnnVbar',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsDo (HsStmtContext Name) -- The parameterisation is unimportant
-- because in this context we never use
-- the PatGuard or ParStmt variant
@@ -224,6 +246,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
-- 'ApiAnnotation.AnnClose' @']'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ExplicitList
(PostTc id Type) -- Gives type of components of list
(Maybe (SyntaxExpr id)) -- For OverloadedLists, the fromListN witness
@@ -235,6 +259,8 @@ data HsExpr id
-- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnComma',
-- 'ApiAnnotation.AnnVbar'
-- 'ApiAnnotation.AnnClose' @':]'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ExplicitPArr
(PostTc id Type) -- type of elements of the parallel array
[LHsExpr id]
@@ -243,6 +269,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| RecordCon (Located id) -- The constructor. After type checking
-- it's the dataConWrapId of the constructor
PostTcExpr -- Data con Id applied to type args
@@ -252,6 +280,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| RecordUpd (LHsExpr id)
(HsRecordBinds id)
-- (HsMatchGroup Id) -- Filled in by the type checker to be
@@ -267,6 +297,8 @@ data HsExpr id
-- | Expression with an explicit type signature. @e :: type@
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ExprWithTySig
(LHsExpr id)
(LHsType id)
@@ -285,6 +317,8 @@ data HsExpr id
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
-- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnDotdot',
-- 'ApiAnnotation.AnnClose' @']'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ArithSeq
PostTcExpr
(Maybe (SyntaxExpr id)) -- For OverloadedLists, the fromList witness
@@ -298,6 +332,8 @@ data HsExpr id
-- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnDotdot',
-- 'ApiAnnotation.AnnVbar',
-- 'ApiAnnotation.AnnClose' @':]'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| PArrSeq
PostTcExpr
(ArithSeqInfo id)
@@ -305,12 +341,16 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# SCC'@,
-- 'ApiAnnotation.AnnVal' or 'ApiAnnotation.AnnValStr',
-- 'ApiAnnotation.AnnClose' @'\#-}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsSCC SourceText -- Note [Pragma source text] in BasicTypes
FastString -- "set cost centre" SCC pragma
(LHsExpr id) -- expr whose cost is to be measured
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CORE'@,
-- 'ApiAnnotation.AnnVal', 'ApiAnnotation.AnnClose' @'\#-}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsCoreAnn SourceText -- Note [Pragma source text] in BasicTypes
FastString -- hdaume: core annotation
(LHsExpr id)
@@ -321,6 +361,8 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsBracket (HsBracket id)
-- See Note [Pending Splices]
@@ -337,6 +379,8 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsSpliceE Bool -- True <=> typed splice
(HsSplice id) -- False <=> untyped
@@ -350,6 +394,8 @@ data HsExpr id
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnProc',
-- 'ApiAnnotation.AnnRarrow'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsProc (LPat id) -- arrow abstraction, proc
(LHsCmdTop id) -- body of the abstraction
-- always has an empty stack
@@ -357,6 +403,8 @@ data HsExpr id
---------------------------------------
-- static pointers extension
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnStatic',
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsStatic (LHsExpr id)
---------------------------------------
@@ -367,6 +415,8 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.Annlarrowtail',
-- 'ApiAnnotation.Annrarrowtail','ApiAnnotation.AnnLarrowtail',
-- 'ApiAnnotation.AnnRarrowtail'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsArrApp -- Arrow tail, or arrow application (f -< arg)
(LHsExpr id) -- arrow expression, f
(LHsExpr id) -- input expression, arg
@@ -378,6 +428,8 @@ data HsExpr id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(|'@,
-- 'ApiAnnotation.AnnClose' @'|)'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsArrForm -- Command formation, (| e cmd1 .. cmdn |)
(LHsExpr id) -- the operator
-- after type-checking, a type abstraction to be
@@ -406,6 +458,8 @@ data HsExpr id
-- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnColon',
-- 'ApiAnnotation.AnnVal',
-- 'ApiAnnotation.AnnClose' @'\#-}'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsTickPragma -- A pragma introduced tick
SourceText -- Note [Pragma source text] in BasicTypes
(FastString,(Int,Int),(Int,Int)) -- external span for this tick
@@ -418,14 +472,20 @@ data HsExpr id
| EWildPat -- wildcard
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnAt'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| EAsPat (Located id) -- as pattern
(LHsExpr id)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| EViewPat (LHsExpr id) -- view pattern
(LHsExpr id)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ELazyPat (LHsExpr id) -- ~ pattern
| HsType (LHsType id) -- Explicit type argument; e.g f {| Int |} x y
@@ -444,6 +504,8 @@ deriving instance (DataId id) => Data (HsExpr id)
-- Which in turn stands for (\x:ty1 \y:ty2. (x,a,y))
type LHsTupArg id = Located (HsTupArg id)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data HsTupArg id
= Present (LHsExpr id) -- ^ The argument
| Missing (PostTc id Type) -- ^ The argument is missing, but this is its type
@@ -782,6 +844,8 @@ data HsCmd id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.Annlarrowtail',
-- 'ApiAnnotation.Annrarrowtail','ApiAnnotation.AnnLarrowtail',
-- 'ApiAnnotation.AnnRarrowtail'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
= HsCmdArrApp -- Arrow tail, or arrow application (f -< arg)
(LHsExpr id) -- arrow expression, f
(LHsExpr id) -- input expression, arg
@@ -793,6 +857,8 @@ data HsCmd id
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(|'@,
-- 'ApiAnnotation.AnnClose' @'|)'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| HsCmdArrForm -- Command formation, (| e cmd1 .. cmdn |)
(LHsExpr id) -- the operator
-- after type-checking, a type abstraction to be
@@ -808,16 +874,22 @@ data HsCmd id
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
-- 'ApiAnnotation.AnnRarrow',
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdPar (LHsCmd id) -- parenthesised command
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
-- 'ApiAnnotation.AnnClose' @')'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdCase (LHsExpr id)
(MatchGroup id (LHsCmd id)) -- bodies are HsCmd's
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnCase',
-- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdIf (Maybe (SyntaxExpr id)) -- cond function
(LHsExpr id) -- predicate
(LHsCmd id) -- then part
@@ -827,12 +899,16 @@ data HsCmd id
-- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi',
-- 'ApiAnnotation.AnnElse',
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdLet (HsLocalBinds id) -- let(rec)
(LHsCmd id)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet',
-- 'ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdDo [CmdLStmt id]
(PostTc id Type) -- Type of the whole expression
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDo',
@@ -840,6 +916,8 @@ data HsCmd id
-- 'ApiAnnotation.AnnVbar',
-- 'ApiAnnotation.AnnClose'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCmdCast TcCoercion -- A simpler version of HsWrap in HsExpr
(HsCmd id) -- If cmd :: arg1 --> res
-- co :: arg1 ~ arg2
@@ -999,6 +1077,8 @@ deriving instance (Data body,DataId id) => Data (MatchGroup id body)
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
data Match id body
= Match {
m_fun_id_infix :: (Maybe (Located id,Bool)),
@@ -1057,6 +1137,8 @@ hsLMatchPats (L _ (Match _ pats _ _)) = pats
-- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
-- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
-- 'ApiAnnotation.AnnRarrow','ApiAnnotation.AnnSemi'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data GRHSs id body
= GRHSs {
grhssGRHSs :: [LGRHS id body], -- ^ Guarded RHSs
@@ -1174,6 +1256,8 @@ type GhciStmt id = Stmt id (LHsExpr id)
-- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnThen',
-- 'ApiAnnotation.AnnBy','ApiAnnotation.AnnBy',
-- 'ApiAnnotation.AnnGroup','ApiAnnotation.AnnUsing'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data StmtLR idL idR body -- body should always be (LHs**** idR)
= LastStmt -- Always the last Stmt in ListComp, MonadComp, PArrComp,
-- and (after the renamer) DoExpr, MDoExpr
@@ -1184,6 +1268,8 @@ data StmtLR idL idR body -- body should always be (LHs**** idR)
-- For DoExpr, MDoExpr, we don't appply a 'return' at all
-- See Note [Monad Comprehensions]
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLarrow'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| BindStmt (LPat idL)
body
(SyntaxExpr idR) -- The (>>=) operator; see Note [The type of bind]
@@ -1199,6 +1285,8 @@ 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
| LetStmt (HsLocalBindsLR idL idR)
-- ParStmts only occur in a list/monad comprehension
@@ -1229,6 +1317,8 @@ 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
| RecStmt
{ recS_stmts :: [LStmtLR idL idR body]
diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs
index 892202ffe2..42b374abfc 100644
--- a/compiler/hsSyn/HsImpExp.hs
+++ b/compiler/hsSyn/HsImpExp.hs
@@ -35,7 +35,8 @@ type LImportDecl name = Located (ImportDecl name)
-- ^ When in a list this may have
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
-- | A single Haskell @import@ declaration.
data ImportDecl name
@@ -67,6 +68,7 @@ data ImportDecl name
-- 'ApiAnnotation.AnnClose' attached
-- to location in ideclHiding
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Data, Typeable)
simpleImportDecl :: ModuleName -> ImportDecl name
@@ -128,31 +130,42 @@ type LIE name = Located (IE name)
-- ^ When in a list this may have
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma'
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
-- | Imported or exported entity.
data IE name
= IEVar (Located name)
-- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
-- 'ApiAnnotation.AnnType'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| IEThingAbs (Located name) -- ^ Class/Type (can't tell)
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
-- 'ApiAnnotation.AnnType','ApiAnnotation.AnnVal'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| IEThingAll (Located name) -- ^ Class/Type plus all methods/constructors
--
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnType'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| IEThingWith (Located name) [Located name]
-- ^ Class/Type plus some methods/constructors
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose',
-- 'ApiAnnotation.AnnComma',
-- 'ApiAnnotation.AnnType'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| IEModuleContents (Located ModuleName) -- ^ (Export Only)
--
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnModule'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| IEGroup Int HsDocString -- ^ Doc section heading
| IEDoc HsDocString -- ^ Some documentation
| IEDocNamed String -- ^ Reference to named doc
diff --git a/compiler/hsSyn/HsLit.hs b/compiler/hsSyn/HsLit.hs
index 90e79d13c3..2a910ad86b 100644
--- a/compiler/hsSyn/HsLit.hs
+++ b/compiler/hsSyn/HsLit.hs
@@ -36,7 +36,7 @@ import Data.Data hiding ( Fixity )
************************************************************************
-}
--- Note [literal source text] in BasicTypes for SourceText fields in
+-- Note [Literal source text] in BasicTypes for SourceText fields in
-- the following
data HsLit
= HsChar SourceText Char -- Character
@@ -84,7 +84,7 @@ data HsOverLit id -- An overloaded literal
deriving (Typeable)
deriving instance (DataId id) => Data (HsOverLit id)
--- Note [literal source text] in BasicTypes for SourceText fields in
+-- Note [Literal source text] in BasicTypes for SourceText fields in
-- the following
data OverLitVal
= HsIntegral !SourceText !Integer -- Integer-looking literals;
diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs
index ea8f62500b..1d8da13b5a 100644
--- a/compiler/hsSyn/HsPat.hs
+++ b/compiler/hsSyn/HsPat.hs
@@ -59,6 +59,8 @@ type OutPat id = LPat id -- No 'In' constructors
type LPat id = Located (Pat id)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data Pat id
= ------------ Simple patterns ---------------
WildPat (PostTc id Type) -- Wild card
@@ -69,16 +71,24 @@ data Pat id
| LazyPat (LPat id) -- Lazy pattern
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| AsPat (Located id) (LPat id) -- As pattern
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnAt'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| ParPat (LPat id) -- Parenthesised pattern
-- See Note [Parens in HsSyn] in HsExpr
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
-- 'ApiAnnotation.AnnClose' @')'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| BangPat (LPat id) -- Bang pattern
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
------------ Lists, tuples, arrays ---------------
| ListPat [LPat id] -- Syntactic list
(PostTc id Type) -- The type of the elements
@@ -89,6 +99,8 @@ data Pat id
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
-- 'ApiAnnotation.AnnClose' @']'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| TuplePat [LPat id] -- Tuple sub-patterns
Boxity -- UnitPat is TuplePat []
[PostTc id Type] -- [] before typechecker, filled in afterwards
@@ -112,11 +124,13 @@ data Pat id
-- 'ApiAnnotation.AnnOpen' @'('@ or @'(#'@,
-- 'ApiAnnotation.AnnClose' @')'@ or @'#)'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
| PArrPat [LPat id] -- Syntactic parallel array
(PostTc id Type) -- The type of the elements
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'[:'@,
-- 'ApiAnnotation.AnnClose' @':]'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
------------ Constructor patterns ---------------
| ConPatIn (Located id)
(HsConPatDetails id)
@@ -139,6 +153,8 @@ data Pat id
------------ View patterns ---------------
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| ViewPat (LHsExpr id)
(LPat id)
(PostTc id Type) -- The overall type of the pattern
@@ -148,6 +164,8 @@ data Pat id
------------ Pattern splices ---------------
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@
-- 'ApiAnnotation.AnnClose' @')'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| SplicePat (HsSplice id)
------------ Quasiquoted patterns ---------------
@@ -166,6 +184,8 @@ data Pat id
(SyntaxExpr id) -- Equality checker, of type t->t->Bool
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnVal' @'+'@
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| NPlusKPat (Located id) -- n+k pattern
(Located (HsOverLit id)) -- It'll always be an HsIntegral
(SyntaxExpr id) -- (>=) function, of type t->t->Bool
@@ -173,6 +193,8 @@ data Pat id
------------ Pattern type signatures ---------------
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
| SigPatIn (LPat id) -- Pattern with a type signature
(HsWithBndrs id (LHsType id)) -- Signature can bind both
-- kind and type vars
@@ -233,6 +255,8 @@ data HsRecFields id arg -- A bunch of record fields
type LHsRecField id arg = Located (HsRecField id arg)
-- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual',
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data HsRecField id arg = HsRecField {
hsRecFieldId :: Located id,
hsRecFieldArg :: arg, -- Filled in by renamer
diff --git a/compiler/hsSyn/HsSyn.hs b/compiler/hsSyn/HsSyn.hs
index e75939ea2f..72525b2519 100644
--- a/compiler/hsSyn/HsSyn.hs
+++ b/compiler/hsSyn/HsSyn.hs
@@ -73,7 +73,8 @@ data HsModule name
--
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
-- ,'ApiAnnotation.AnnClose'
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
hsmodImports :: [LImportDecl name],
-- ^ We snaffle interesting stuff out of the imported interfaces early
-- on, adding that info to TyDecls/etc; so this list is often empty,
@@ -86,12 +87,15 @@ data HsModule name
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
-- ,'ApiAnnotation.AnnClose'
--
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
hsmodHaddockModHeader :: Maybe LHsDocString
-- ^ Haddock module info and description, unparsed
--
-- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
-- ,'ApiAnnotation.AnnClose'
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
}
-- ^ 'ApiAnnotation.AnnKeywordId's
--
@@ -100,7 +104,8 @@ data HsModule name
-- - 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnSemi',
-- 'ApiAnnotation.AnnClose' for explicit braces and semi around
-- hsmodImports,hsmodDecls if this style is used.
- --
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (HsModule name)
diff --git a/compiler/hsSyn/HsTypes.hs b/compiler/hsSyn/HsTypes.hs
index c1b440d007..b5a3f9af88 100644
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@ -134,11 +134,15 @@ See also Note [Kind and type-variable binders] in RnTypes
type LHsContext name = Located (HsContext name)
-- ^ 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnUnit'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
type HsContext name = [LHsType name]
type LHsType name = Located (HsType name)
-- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
-- in a list
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
type HsKind name = HsType name
type LHsKind name = Located (HsKind name)
@@ -207,6 +211,8 @@ data HsTyVarBndr name
-- ^
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnDcolon', 'ApiAnnotation.AnnClose'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (HsTyVarBndr name)
@@ -235,40 +241,58 @@ data HsType name
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnForall',
-- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsTyVar name -- Type variable, type constructor, or data constructor
-- see Note [Promotions (HsTyVar)]
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsAppTy (LHsType name)
(LHsType name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsFunTy (LHsType name) -- function type
(LHsType name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow',
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsListTy (LHsType name) -- Element type
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
-- 'ApiAnnotation.AnnClose' @']'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsPArrTy (LHsType name) -- Elem. type of parallel array: [:t:]
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'[:'@,
-- 'ApiAnnotation.AnnClose' @':]'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsTupleTy HsTupleSort
[LHsType name] -- Element types (length gives arity)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(' or '(#'@,
-- 'ApiAnnotation.AnnClose' @')' or '#)'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsOpTy (LHsType name) (LHsTyOp name) (LHsType name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsParTy (LHsType name) -- See Note [Parens in HsSyn] in HsExpr
-- 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' @'('@,
-- 'ApiAnnotation.AnnClose' @')'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsIParamTy HsIPName -- (?x :: ty)
(LHsType name) -- Implicit parameters as they occur in contexts
-- ^
@@ -276,6 +300,8 @@ data HsType name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsEqTy (LHsType name) -- ty1 ~ ty2
(LHsType name) -- Always allowed even without TypeOperators, and has special kinding rule
-- ^
@@ -283,6 +309,8 @@ data HsType name
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsKindSig (LHsType name) -- (ty :: kind)
(LHsKind name) -- A type with a kind signature
-- ^
@@ -291,58 +319,84 @@ data HsType name
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
-- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose' @')'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsQuasiQuoteTy (HsQuasiQuote name)
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsSpliceTy (HsSplice name)
(PostTc name Kind)
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@,
-- 'ApiAnnotation.AnnClose' @')'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsDocTy (LHsType name) LHsDocString -- A documented type
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsBangTy HsSrcBang (LHsType name) -- Bang-style type annotations
-- ^ - 'ApiAnnotation.AnnKeywordId' :
-- 'ApiAnnotation.AnnOpen' @'{-\# UNPACK' or '{-\# NOUNPACK'@,
-- 'ApiAnnotation.AnnClose' @'#-}'@
-- 'ApiAnnotation.AnnBang' @\'!\'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsRecTy [LConDeclField name] -- Only in data type declarations
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
-- 'ApiAnnotation.AnnClose' @'}'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsCoreTy 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
+
| HsExplicitListTy -- A promoted explicit list
(PostTc name Kind) -- See Note [Promoted lists and tuples]
[LHsType name]
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'["@,
-- 'ApiAnnotation.AnnClose' @']'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsExplicitTupleTy -- A promoted explicit tuple
[PostTc name Kind] -- See Note [Promoted lists and tuples]
[LHsType name]
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'("@,
-- 'ApiAnnotation.AnnClose' @')'@
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsTyLit HsTyLit -- A promoted numeric literal.
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsWrapTy HsTyWrapper (HsType name) -- only in typechecker output
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsWildcardTy -- A type wildcard
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- For details on above see note [Api annotations] in ApiAnnotation
+
| HsNamedWildcardTy name -- A named wildcard
-- ^ - 'ApiAnnotation.AnnKeywordId' : None
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (HsType name)
--- Note [literal source text] in BasicTypes for SourceText fields in
+-- Note [Literal source text] in BasicTypes for SourceText fields in
-- the following
data HsTyLit
= HsNumTy SourceText Integer
@@ -467,11 +521,15 @@ data HsExplicitFlag = Qualified | Implicit | Explicit deriving (Data, Typeable)
type LConDeclField name = Located (ConDeclField name)
-- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
-- in a list
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
data ConDeclField name -- Record fields have Haddoc docs on them
= ConDeclField { cd_fld_names :: [Located name],
cd_fld_type :: LBangType name,
cd_fld_doc :: Maybe LHsDocString }
-- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+
+ -- For details on above see note [Api annotations] in ApiAnnotation
deriving (Typeable)
deriving instance (DataId name) => Data (ConDeclField name)