summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2015-01-19 08:15:18 -0600
committerAustin Seipp <aseipp@pobox.com>2015-01-23 07:18:04 -0600
commit5b7a79780b709f4a9d1c110bb786bae1031d1614 (patch)
tree77608fe69623b484118b7a67db2661511b84ab1c
parent3a7a30d765d272f10b150c28dcc28726b513b091 (diff)
downloadhaskell-wip/api-annot-tweaks-7.10.tar.gz
API Annotations documentation update, parsing issue, add example testwip/api-annot-tweaks-7.10
Summary: Add a reference note to each AnnKeywordId haddock comment so GHC developers will have an idea why they are there. Add a new test to ghc-api/annotations to serve as a template for other GHC developers when they need to update the parser. It provides output which checks that each SrcSpan that an annotation is attached to actually appears in the `ParsedSource`, and lists the individual annotations. The idea is that a developer writes a version of this which parses a sample file using whatever syntax is changed in Parser.y, and can then check that all the annotations come through. Depends on D538 Test Plan: ./validate Reviewers: simonpj, hvr, austin Reviewed By: austin Subscribers: thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D620 (cherry picked from commit 851ed7211fb18fea938be84c99b6389f6762b30d)
-rw-r--r--compiler/basicTypes/BasicTypes.hs30
-rw-r--r--compiler/basicTypes/DataCon.hs2
-rw-r--r--compiler/basicTypes/RdrName.hs2
-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
-rw-r--r--compiler/parser/ApiAnnotation.hs16
-rw-r--r--compiler/parser/Lexer.x14
-rw-r--r--compiler/parser/Parser.y5
-rw-r--r--compiler/prelude/ForeignCall.hs2
-rw-r--r--compiler/types/Class.hs2
-rw-r--r--testsuite/tests/ghc-api/annotations/.gitignore1
-rw-r--r--testsuite/tests/ghc-api/annotations/Makefile6
-rw-r--r--testsuite/tests/ghc-api/annotations/all.T1
-rw-r--r--testsuite/tests/ghc-api/annotations/exampleTest.hs112
-rw-r--r--testsuite/tests/ghc-api/annotations/exampleTest.stdout124
21 files changed, 563 insertions, 39 deletions
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index 8dbdfc3fa5..ee34b215cb 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -456,6 +456,8 @@ instance Outputable Origin where
-- @'\{-\# OVERLAPS'@ or
-- @'\{-\# INCOHERENT'@,
-- 'ApiAnnotation.AnnClose' @`\#-\}`@,
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data OverlapFlag = OverlapFlag
{ overlapMode :: OverlapMode
, isSafeOverlap :: Bool
@@ -788,7 +790,6 @@ Keeping Source Text for source to source conversions
Note [Pragma source text]
~~~~~~~~~~~~~~~~~~~~~~~~~
-
The lexer does a case-insensitive match for pragmas, as well as
accepting both UK and US spelling variants.
@@ -814,9 +815,8 @@ for the cases above.
[without the space between '{' and '-', otherwise this comment won't parse]
-Note [literal source text]
+Note [Literal source text]
~~~~~~~~~~~~~~~~~~~~~~~~~~
-
The lexer/parser converts literals from their original source text
versions to an appropriate internal representation. This is a problem
for tools doing source to source conversions, so the original source
@@ -824,24 +824,24 @@ text is stored in literals where this can occur.
Motivating examples for HsLit
- HsChar '\n', '\x20`
- HsCharPrim '\x41`#
+ HsChar '\n' == '\x20`
+ HsCharPrim '\x41`# == `A`
HsString "\x20\x41" == " A"
- HsStringPrim "\x20"#
- HsInt 001
- HsIntPrim 002#
- HsWordPrim 003##
- HsInt64Prim 004##
- HsWord64Prim 005##
- HsInteger 006
+ HsStringPrim "\x20"# == " "#
+ HsInt 001 == 1
+ HsIntPrim 002# == 2#
+ HsWordPrim 003## == 3##
+ HsInt64Prim 004## == 4##
+ HsWord64Prim 005## == 5##
+ HsInteger 006 == 6
For OverLitVal
- HsIntegral 003,0x001
- HsIsString "\x41nd"
+ HsIntegral 003 == 0x003
+ HsIsString "\x41nd" == "And"
-}
-type SourceText = String -- Note [literal source text],[Pragma source text]
+type SourceText = String -- Note [Literal source text],[Pragma source text]
{-
diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs
index cd4fe71993..b635aaf4a1 100644
--- a/compiler/basicTypes/DataCon.hs
+++ b/compiler/basicTypes/DataCon.hs
@@ -250,6 +250,8 @@ Note that (Foo a) might not be an instance of Ord.
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
-- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma'
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data DataCon
= MkData {
dcName :: Name, -- This is the name of the *source data con*
diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs
index 5db0a9d7b3..094347a4fa 100644
--- a/compiler/basicTypes/RdrName.hs
+++ b/compiler/basicTypes/RdrName.hs
@@ -100,6 +100,8 @@ import Data.Data
-- 'ApiAnnotation.AnnBackquote' @'`'@,
-- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnTildehsh',
-- 'ApiAnnotation.AnnTilde',
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data RdrName
= Unqual OccName
-- ^ Used for ordinary, unqualified occurrences, e.g. @x@, @y@ or @Foo@.
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)
diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs
index 60f917222f..e8ad8ea879 100644
--- a/compiler/parser/ApiAnnotation.hs
+++ b/compiler/parser/ApiAnnotation.hs
@@ -17,9 +17,9 @@ import qualified Data.Map as Map
import Data.Data
-{- Note [Api annotations]
- ~~~~~~~~~~~~~~~~~~~~~~
-
+{-
+Note [Api annotations]
+~~~~~~~~~~~~~~~~~~~~~~
In order to do source to source conversions using the GHC API, the
locations of all elements of the original source needs to be tracked.
The includes keywords such as 'let' / 'in' / 'do' etc as well as
@@ -66,8 +66,8 @@ This is done in the lexer / parser as follows.
The PState variable in the lexer has the following variables added
-> annotations :: [(ApiAnnKey,SrcSpan)],
-> comment_q :: [Located Token],
+> annotations :: [(ApiAnnKey,[SrcSpan])],
+> comment_q :: [Located AnnotationComment],
> annotations_comments :: [(SrcSpan,[Located AnnotationComment])]
The first and last store the values that end up in the ApiAnns value
@@ -115,6 +115,9 @@ This adds an AnnLet annotation for 'let', an AnnIn for 'in', as well
as any annotations that may arise in the binds. This will include open
and closing braces if they are used to delimit the let expressions.
+The wiki page describing this feature is
+https://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations
+
-}
-- ---------------------------------------------------------------------
@@ -173,6 +176,9 @@ getAndRemoveAnnotationComments (anns,canns) span =
-- Comments are only retained if @'Opt_KeepRawTokenStream'@ is set in
-- @'DynFlags.DynFlags'@ before parsing.
--
+-- The wiki page describing this feature is
+-- https://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations
+--
-- Note: in general the names of these are taken from the
-- corresponding token, unless otherwise noted
-- See note [Api annotations] above for details of the usage
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 495605e70c..abb2477783 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -639,15 +639,15 @@ data Token
| ITdupipvarid FastString -- GHC extension: implicit param: ?x
- | ITchar SourceText Char -- Note [literal source text] in BasicTypes
- | ITstring SourceText FastString -- Note [literal source text] in BasicTypes
- | ITinteger SourceText Integer -- Note [literal source text] in BasicTypes
+ | ITchar SourceText Char -- Note [Literal source text] in BasicTypes
+ | ITstring SourceText FastString -- Note [Literal source text] in BasicTypes
+ | ITinteger SourceText Integer -- Note [Literal source text] in BasicTypes
| ITrational FractionalLit
- | ITprimchar SourceText Char -- Note [literal source text] in BasicTypes
- | ITprimstring SourceText ByteString -- Note [literal source text] @BasicTypes
- | ITprimint SourceText Integer -- Note [literal source text] in BasicTypes
- | ITprimword SourceText Integer -- Note [literal source text] in BasicTypes
+ | ITprimchar SourceText Char -- Note [Literal source text] in BasicTypes
+ | ITprimstring SourceText ByteString -- Note [Literal source text] @BasicTypes
+ | ITprimint SourceText Integer -- Note [Literal source text] in BasicTypes
+ | ITprimword SourceText Integer -- Note [Literal source text] in BasicTypes
| ITprimfloat FractionalLit
| ITprimdouble FractionalLit
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 9e3d5ff14e..e3760906dd 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -253,7 +253,10 @@ structured editors.
The helper functions are defined at the bottom of this file.
-See https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations for some background.
+See
+ https://ghc.haskell.org/trac/ghc/wiki/ApiAnnotations and
+ https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations
+for some background.
-- -----------------------------------------------------------------------------
diff --git a/compiler/prelude/ForeignCall.hs b/compiler/prelude/ForeignCall.hs
index 915a0f6945..907640b462 100644
--- a/compiler/prelude/ForeignCall.hs
+++ b/compiler/prelude/ForeignCall.hs
@@ -233,6 +233,8 @@ instance Outputable Header where
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CTYPE'@,
-- 'ApiAnnotation.AnnHeader','ApiAnnotation.AnnVal',
-- 'ApiAnnotation.AnnClose' @'\#-}'@,
+
+-- For details on above see note [Api annotations] in ApiAnnotation
data CType = CType SourceText -- Note [Pragma source text] in BasicTypes
(Maybe Header) -- header to include for this type
FastString -- the type itself
diff --git a/compiler/types/Class.hs b/compiler/types/Class.hs
index 9ccece9802..d51da7e054 100644
--- a/compiler/types/Class.hs
+++ b/compiler/types/Class.hs
@@ -85,6 +85,8 @@ data Class
-- Here fun-deps are [([a,b],[c]), ([a,c],[b])]
--
-- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow'',
+
+-- For details on above see note [Api annotations] in ApiAnnotation
type FunDep a = ([a],[a])
type ClassOpItem = (Id, DefMeth)
diff --git a/testsuite/tests/ghc-api/annotations/.gitignore b/testsuite/tests/ghc-api/annotations/.gitignore
index 61d9b24b9e..fe31fad9b9 100644
--- a/testsuite/tests/ghc-api/annotations/.gitignore
+++ b/testsuite/tests/ghc-api/annotations/.gitignore
@@ -1,6 +1,7 @@
annotations
parseTree
comments
+exampleTest
*.hi
*.o
*.run.*
diff --git a/testsuite/tests/ghc-api/annotations/Makefile b/testsuite/tests/ghc-api/annotations/Makefile
index 421154ea25..61474e9b0e 100644
--- a/testsuite/tests/ghc-api/annotations/Makefile
+++ b/testsuite/tests/ghc-api/annotations/Makefile
@@ -4,7 +4,7 @@ include $(TOP)/mk/test.mk
clean:
rm -f *.o *.hi
- rm -f annotations comments parseTree
+ rm -f annotations comments parseTree exampleTest
annotations:
rm -f annotations.o annotations.hi
@@ -21,5 +21,9 @@ comments:
'$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc comments
./comments "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
+exampleTest:
+ rm -f exampleTest.o exampleTest.hi
+ '$(TEST_HC)' $(TEST_HC_OPTS) --make -v0 -package ghc exampleTest
+ ./exampleTest "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`"
.PHONY: clean
diff --git a/testsuite/tests/ghc-api/annotations/all.T b/testsuite/tests/ghc-api/annotations/all.T
index 54da2efda4..cb075cb185 100644
--- a/testsuite/tests/ghc-api/annotations/all.T
+++ b/testsuite/tests/ghc-api/annotations/all.T
@@ -1,4 +1,5 @@
test('annotations', normal, run_command, ['$MAKE -s --no-print-directory annotations'])
test('parseTree', normal, run_command, ['$MAKE -s --no-print-directory parseTree'])
test('comments', normal, run_command, ['$MAKE -s --no-print-directory comments'])
+test('exampleTest', normal, run_command, ['$MAKE -s --no-print-directory exampleTest'])
diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.hs b/testsuite/tests/ghc-api/annotations/exampleTest.hs
new file mode 100644
index 0000000000..0b6c22464c
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/exampleTest.hs
@@ -0,0 +1,112 @@
+{-# LANGUAGE RankNTypes #-}
+
+-- This program must be called with GHC's libdir as the single command line
+-- argument.
+module Main where
+
+-- import Data.Generics
+import Data.Data
+import Data.List
+import System.IO
+import GHC
+import BasicTypes
+import DynFlags
+import MonadUtils
+import Outputable
+import ApiAnnotation
+import Bag (filterBag,isEmptyBag)
+import System.Directory (removeFile)
+import System.Environment( getArgs )
+import qualified Data.Map as Map
+import qualified Data.Set as Set
+import Data.Dynamic ( fromDynamic,Dynamic )
+
+main::IO()
+main = do
+ [libdir] <- getArgs
+ testOneFile libdir "AnnotationTuple"
+
+testOneFile libdir fileName = do
+ ((anns,cs),p) <- runGhc (Just libdir) $ do
+ dflags <- getSessionDynFlags
+ setSessionDynFlags dflags
+ let mn =mkModuleName fileName
+ addTarget Target { targetId = TargetModule mn
+ , targetAllowObjCode = True
+ , targetContents = Nothing }
+ load LoadAllTargets
+ modSum <- getModSummary mn
+ p <- parseModule modSum
+ t <- typecheckModule p
+ d <- desugarModule t
+ l <- loadModule d
+ let ts=typecheckedSource l
+ r =renamedSource l
+ return (pm_annotations p,p)
+
+ let spans = Set.fromList $ getAllSrcSpans (pm_parsed_source p)
+
+ -- putStrLn (pp spans)
+ problems = filter (\(s,a) -> not (Set.member s spans))
+ $ getAnnSrcSpans (anns,cs)
+ putStrLn "---Problems---------------------"
+ putStrLn (intercalate "\n" [showAnns $ Map.fromList $ map snd problems])
+ putStrLn "--------------------------------"
+ putStrLn (intercalate "\n" [showAnns anns])
+
+ where
+ getAnnSrcSpans :: ApiAnns -> [(SrcSpan,(ApiAnnKey,[SrcSpan]))]
+ getAnnSrcSpans (anns,_) = map (\a@((ss,_),_) -> (ss,a)) $ Map.toList anns
+
+ getAllSrcSpans :: (Data t) => t -> [SrcSpan]
+ getAllSrcSpans ast = everything (++) ([] `mkQ` getSrcSpan) ast
+ where
+ getSrcSpan :: SrcSpan -> [SrcSpan]
+ getSrcSpan ss = [ss]
+
+
+showAnns anns = "[\n" ++ (intercalate "\n"
+ $ map (\((s,k),v)
+ -> ("(AK " ++ pp s ++ " " ++ show k ++" = " ++ pp v ++ ")\n"))
+ $ Map.toList anns)
+ ++ "]\n"
+
+pp a = showPpr unsafeGlobalDynFlags a
+
+
+-- ---------------------------------------------------------------------
+
+-- Copied from syb for the test
+
+
+-- | Generic queries of type \"r\",
+-- i.e., take any \"a\" and return an \"r\"
+--
+type GenericQ r = forall a. Data a => a -> r
+
+
+-- | Make a generic query;
+-- start from a type-specific case;
+-- return a constant otherwise
+--
+mkQ :: ( Typeable a
+ , Typeable b
+ )
+ => r
+ -> (b -> r)
+ -> a
+ -> r
+(r `mkQ` br) a = case cast a of
+ Just b -> br b
+ Nothing -> r
+
+
+
+-- | Summarise all nodes in top-down, left-to-right order
+everything :: (r -> r -> r) -> GenericQ r -> GenericQ r
+
+-- Apply f to x to summarise top-level node;
+-- use gmapQ to recurse into immediate subterms;
+-- use ordinary foldl to reduce list of intermediate results
+
+everything k f x = foldl k (f x) (gmapQ (everything k f) x)
diff --git a/testsuite/tests/ghc-api/annotations/exampleTest.stdout b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
new file mode 100644
index 0000000000..42da538cc7
--- /dev/null
+++ b/testsuite/tests/ghc-api/annotations/exampleTest.stdout
@@ -0,0 +1,124 @@
+---Problems---------------------
+[
+(AK AnnotationTuple.hs:13:39 AnnComma = [AnnotationTuple.hs:13:39])
+
+(AK <no location info> AnnEofPos = [AnnotationTuple.hs:21:1])
+]
+
+--------------------------------
+[
+(AK AnnotationTuple.hs:1:1 AnnCloseC = [AnnotationTuple.hs:16:1])
+
+(AK AnnotationTuple.hs:1:1 AnnModule = [AnnotationTuple.hs:2:1-6])
+
+(AK AnnotationTuple.hs:1:1 AnnOpenC = [AnnotationTuple.hs:4:1])
+
+(AK AnnotationTuple.hs:1:1 AnnWhere = [AnnotationTuple.hs:2:30-34])
+
+(AK AnnotationTuple.hs:2:24-28 AnnCloseP = [AnnotationTuple.hs:2:28])
+
+(AK AnnotationTuple.hs:2:24-28 AnnOpenP = [AnnotationTuple.hs:2:24])
+
+(AK AnnotationTuple.hs:5:1-32 AnnAs = [AnnotationTuple.hs:5:28-29])
+
+(AK AnnotationTuple.hs:5:1-32 AnnImport = [AnnotationTuple.hs:5:1-6])
+
+(AK AnnotationTuple.hs:5:1-32 AnnQualified = [AnnotationTuple.hs:5:8-16])
+
+(AK AnnotationTuple.hs:5:1-32 AnnSemi = [AnnotationTuple.hs:6:1])
+
+(AK AnnotationTuple.hs:5:1-32 AnnVal = [AnnotationTuple.hs:5:31-32])
+
+(AK AnnotationTuple.hs:(7,1)-(10,14) AnnEqual = [AnnotationTuple.hs:7:5])
+
+(AK AnnotationTuple.hs:(7,1)-(10,14) AnnFunId = [AnnotationTuple.hs:7:1-3])
+
+(AK AnnotationTuple.hs:(7,1)-(10,14) AnnSemi = [AnnotationTuple.hs:12:1])
+
+(AK AnnotationTuple.hs:(7,7)-(10,14) AnnIn = [AnnotationTuple.hs:10:7-8])
+
+(AK AnnotationTuple.hs:(7,7)-(10,14) AnnLet = [AnnotationTuple.hs:7:7-9])
+
+(AK AnnotationTuple.hs:8:9-13 AnnEqual = [AnnotationTuple.hs:8:11])
+
+(AK AnnotationTuple.hs:8:9-13 AnnFunId = [AnnotationTuple.hs:8:9])
+
+(AK AnnotationTuple.hs:8:9-13 AnnSemi = [AnnotationTuple.hs:9:9])
+
+(AK AnnotationTuple.hs:9:9-13 AnnEqual = [AnnotationTuple.hs:9:11])
+
+(AK AnnotationTuple.hs:9:9-13 AnnFunId = [AnnotationTuple.hs:9:9])
+
+(AK AnnotationTuple.hs:10:10-14 AnnVal = [AnnotationTuple.hs:10:12])
+
+(AK AnnotationTuple.hs:13:1-72 AnnEqual = [AnnotationTuple.hs:13:5])
+
+(AK AnnotationTuple.hs:13:1-72 AnnFunId = [AnnotationTuple.hs:13:1-3])
+
+(AK AnnotationTuple.hs:13:1-72 AnnSemi = [AnnotationTuple.hs:14:1])
+
+(AK AnnotationTuple.hs:13:7-72 AnnVal = [AnnotationTuple.hs:13:13])
+
+(AK AnnotationTuple.hs:13:19-53 AnnCloseP = [AnnotationTuple.hs:13:53])
+
+(AK AnnotationTuple.hs:13:19-53 AnnOpenP = [AnnotationTuple.hs:13:19])
+
+(AK AnnotationTuple.hs:13:20 AnnComma = [AnnotationTuple.hs:13:21])
+
+(AK AnnotationTuple.hs:13:23-29 AnnComma = [AnnotationTuple.hs:13:33])
+
+(AK AnnotationTuple.hs:13:35-37 AnnComma = [AnnotationTuple.hs:13:38])
+
+(AK AnnotationTuple.hs:13:39 AnnComma = [AnnotationTuple.hs:13:39])
+
+(AK AnnotationTuple.hs:13:41-52 AnnCloseS = [AnnotationTuple.hs:13:52])
+
+(AK AnnotationTuple.hs:13:41-52 AnnOpenS = [AnnotationTuple.hs:13:41])
+
+(AK AnnotationTuple.hs:13:42 AnnComma = [AnnotationTuple.hs:13:43])
+
+(AK AnnotationTuple.hs:13:45 AnnComma = [AnnotationTuple.hs:13:46])
+
+(AK AnnotationTuple.hs:13:48 AnnComma = [AnnotationTuple.hs:13:49])
+
+(AK AnnotationTuple.hs:13:55-72 AnnCloseS = [AnnotationTuple.hs:13:72])
+
+(AK AnnotationTuple.hs:13:55-72 AnnOpenS = [AnnotationTuple.hs:13:55])
+
+(AK AnnotationTuple.hs:13:56-62 AnnComma = [AnnotationTuple.hs:13:63])
+
+(AK AnnotationTuple.hs:13:61-62 AnnCloseP = [AnnotationTuple.hs:13:62])
+
+(AK AnnotationTuple.hs:13:61-62 AnnOpenP = [AnnotationTuple.hs:13:61])
+
+(AK AnnotationTuple.hs:15:1-41 AnnEqual = [AnnotationTuple.hs:15:5])
+
+(AK AnnotationTuple.hs:15:1-41 AnnFunId = [AnnotationTuple.hs:15:1-3])
+
+(AK AnnotationTuple.hs:15:7-27 AnnCloseP = [AnnotationTuple.hs:15:27])
+
+(AK AnnotationTuple.hs:15:7-27 AnnOpenP = [AnnotationTuple.hs:15:7])
+
+(AK AnnotationTuple.hs:15:8 AnnComma = [AnnotationTuple.hs:15:9])
+
+(AK AnnotationTuple.hs:15:11-17 AnnComma = [AnnotationTuple.hs:15:18])
+
+(AK AnnotationTuple.hs:15:20-22 AnnComma = [AnnotationTuple.hs:15:23])
+
+(AK AnnotationTuple.hs:15:24 AnnComma = [AnnotationTuple.hs:15:24])
+
+(AK AnnotationTuple.hs:15:25 AnnComma = [AnnotationTuple.hs:15:25])
+
+(AK AnnotationTuple.hs:15:26 AnnComma = [AnnotationTuple.hs:15:26])
+
+(AK AnnotationTuple.hs:15:33-41 AnnCloseP = [AnnotationTuple.hs:15:41])
+
+(AK AnnotationTuple.hs:15:33-41 AnnOpenP = [AnnotationTuple.hs:15:33])
+
+(AK AnnotationTuple.hs:15:39-40 AnnCloseP = [AnnotationTuple.hs:15:40])
+
+(AK AnnotationTuple.hs:15:39-40 AnnOpenP = [AnnotationTuple.hs:15:39])
+
+(AK <no location info> AnnEofPos = [AnnotationTuple.hs:21:1])
+]
+