Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
fbc0b92a by Vladislav Zavialov at 2025-06-22T04:25:16+03:00
Visible forall in GADTs (#25127)
Add support for visible dependent quantification `forall a -> t` in
types of data constructors, e.g.
data KindVal a where
K :: forall k.
forall (a::k) -> -- now allowed!
k ->
KindVal a
For details, see docs/users_guide/exts/required_type_arguments.rst,
which has gained a new subsection.
DataCon in compiler/GHC/Core/DataCon.hs
---------------------------------------
The main change in this patch is that DataCon, the Core representation
of a data constructor, now uses a different type to store user-written
type variable binders:
- dcUserTyVarBinders :: [InvisTVBinder]
+ dcUserTyVarBinders :: [TyVarBinder]
where
type TyVarBinder = VarBndr TyVar ForAllTyFlag
type InvisTVBinder = VarBndr TyVar Specificity
and
data Specificity = InferredSpec | SpecifiedSpec
data ForAllTyFlag = Invisible Specificity | Required
This change necessitates some boring, mechanical changes scattered
throughout the diff:
... is now used in place of ...
-----------------+---------------
TyVarBinder | InvisTVBinder
IfaceForAllBndr | IfaceForAllSpecBndr
Specified | SpecifiedSpec
Inferred | InferredSpec
mkForAllTys | mkInvisForAllTys
additionally,
tyVarSpecToBinders -- added or removed calls
ifaceForAllSpecToBndrs -- removed calls
Visibility casts in mkDataConRep
--------------------------------
Type abstractions in Core (/\a. e) always have type (forall a. t)
because coreTyLamForAllTyFlag = Specified. This is also true of data
constructor workers. So we may be faced with the following:
data con worker: (forall a. blah)
data con wrapper: (forall a -> blah)
In this case the wrapper must use a visibility cast (e |> ForAllCo ...)
with appropriately set fco_vis{L,R}. Relevant functions:
mkDataConRep in compiler/GHC/Types/Id/Make.hs
dataConUserTyVarBindersNeedWrapper in compiler/GHC/Core/DataCon.hs
mkForAllVisCos in compiler/GHC/Core/Coercion.hs
mkCoreTyLams in compiler/GHC/Core/Make.hs
mkWpForAllCast in compiler/GHC/Tc/Types/Evidence.hs
More specifically:
- dataConUserTyVarBindersNeedWrapper has been updated to answer "yes"
if there are visible foralls in the type of the data constructor.
- mkDataConRep now uses mkCoreTyLams to generate the big lambda
abstractions (/\a b c. e) in the data con wrapper.
- mkCoreTyLams is a variant of mkCoreLams that applies visibility casts
as needed. It similar in purpose to the pre-existing mkWpForAllCast,
so the common bits have been factored out into mkForAllVisCos.
ConDecl in compiler/Language/Haskell/Syntax/Decls.hs
----------------------------------------------------
The surface syntax representation of a data constructor declaration is
ConDecl. In accordance with the proposal, only GADT syntax is extended
with support for visible forall, so we are interested in ConDeclGADT.
ConDeclGADT's field con_bndrs has been renamed to con_outer_bndrs
and is now accompanied by con_inner_bndrs:
con_outer_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
con_inner_bndrs :: [HsForAllTelescope pass]
Visible foralls always end up in con_inner_bndrs. The outer binders are
stored and processed separately to support implicit quantification and
the forall-or-nothing rule, a design established by HsSigType.
A side effect of this change is that even in absence of visible foralls,
GHC now permits multiple invisible foralls, e.g.
data T a where { MkT :: forall a b. forall c d. ... -> T a }
But of course, this is done in service of making at least some of these
foralls visible. The entire compiler front-end has been updated to deal
with con_inner_bndrs. See the following modified or added functions:
Parser:
mkGadtDecl in compiler/GHC/Parser/PostProcess.hs
splitLHsGadtTy in compiler/GHC/Hs/Type.hs
Pretty-printer:
pprConDecl in compiler/GHC/Hs/Decls.hs
pprHsForAllTelescope in compiler/GHC/Hs/Type.hs
Renamer:
rnConDecl in compiler/GHC/Rename/Module.hs
bindHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
extractHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
Type checker:
tcConDecl in compiler/GHC/Tc/TyCl.hs
tcGadtConTyVarBndrs in compiler/GHC/Tc/Gen/HsType.hs
Template Haskell
----------------
The TH AST is left unchanged for the moment to avoid breakage. An
attempt to quote or reify a data constructor declaration with visible
forall in its type will result an error:
data ThRejectionReason -- in GHC/HsToCore/Errors/Types.hs
= ...
| ThDataConVisibleForall -- new error constructor
However, as noted in the previous section, GHC now permits multiple
invisible foralls, and TH was updated accordingly. Updated code:
repC in compiler/GHC/HsToCore/Quote.hs
reifyDataCon in compiler/GHC/Tc/Gen/Splice.hs
ppr @Con in libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
Pattern matching
----------------
Everything described above concerns data constructor declarations, but
what about their use sites? Now it is trickier to type check a pattern
match fn(Con a b c)=... because we can no longer assume that a,b,c are
all value arguments. Indeed, some or all of them may very well turn out
to be required type arguments.
To that end, see the changes to:
tcDataConPat in compiler/GHC/Tc/Gen/Pat.hs
splitConTyArgs in compiler/GHC/Tc/Gen/Pat.hs
and the new helpers split_con_ty_args, zip_pats_bndrs.
This is also the reason the TcRnTooManyTyArgsInConPattern error
constructor has been removed. The new code emits TcRnArityMismatch
or TcRnIllegalInvisibleTypePattern.
Summary
-------
DataCon, ConDecl, as well as all related functions have been updated to
support required type arguments in data constructors.
Test cases:
HieGadtConSigs GadtConSigs_th_dump1 GadtConSigs_th_pprint1
T25127_data T25127_data_inst T25127_infix
T25127_newtype T25127_fail_th_quote T25127_fail_arity
TyAppPat_Tricky
Co-authored-by: mniip
- - - - -
ae003a3a by Teo Camarasu at 2025-06-23T05:21:48-04:00
linters: lint-whitespace: bump upper-bound for containers
The version of containers was bumped in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13989
- - - - -
9625de2b by Alan Zimmerman at 2025-06-23T18:33:24+01:00
GHC-CPP: first rough proof of concept
Processes
#define FOO
#ifdef FOO
x = 1
#endif
Into
[ITcppIgnored [L loc ITcppDefine]
,ITcppIgnored [L loc ITcppIfdef]
,ITvarid "x"
,ITequal
,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1})
,ITcppIgnored [L loc ITcppEndif]
,ITeof]
In time, ITcppIgnored will be pushed into a comment
- - - - -
0c228b61 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Tidy up before re-visiting the continuation mechanic
- - - - -
7220c603 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Switch preprocessor to continuation passing style
Proof of concept, needs tidying up
- - - - -
55dcc836 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Small cleanup
- - - - -
da13d8b9 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Get rid of some cruft
- - - - -
d24ebdcd by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Starting to integrate.
Need to get the pragma recognised and set
- - - - -
7cccb4fe by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Make cppTokens extend to end of line, and process CPP comments
- - - - -
0cb0145d by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Remove unused ITcppDefined
- - - - -
0e2c22e9 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Allow spaces between # and keyword for preprocessor directive
- - - - -
67dfc5f8 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Process CPP continuation lines
They are emited as separate ITcppContinue tokens.
Perhaps the processing should be more like a comment, and keep on
going to the end.
BUT, the last line needs to be slurped as a whole.
- - - - -
78c58755 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Accumulate CPP continuations, process when ready
Can be simplified further, we only need one CPP token
- - - - -
c6165a99 by Alan Zimmerman at 2025-06-23T18:33:24+01:00
Simplify Lexer interface. Only ITcpp
We transfer directive lines through it, then parse them from scratch
in the preprocessor.
- - - - -
5225dec2 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Deal with directive on last line, with no trailing \n
- - - - -
44717e01 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Start parsing and processing the directives
- - - - -
0696fe99 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Prepare for processing include files
- - - - -
e8486efd by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Move PpState into PreProcess
And initParserState, initPragState too
- - - - -
239ec200 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Process nested include files
Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci
session, loading utils/check-cpp/Main.hs
- - - - -
b036abde by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Split into separate files
- - - - -
35d20b58 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Starting on expression parser.
But it hangs. Time for Text.Parsec.Expr
- - - - -
1316ac0f by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Start integrating the ghc-cpp work
From https://github.com/alanz/ghc-cpp
- - - - -
90a72c90 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
WIP
- - - - -
16ae009f by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Fixup after rebase
- - - - -
ad48088b by Alan Zimmerman at 2025-06-23T18:33:25+01:00
WIP
- - - - -
fd4ca39b by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Fixup after rebase, including all tests pass
- - - - -
17a746b4 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Change pragma usage to GHC_CPP from GhcCPP
- - - - -
023790f3 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Some comments
- - - - -
082a2f08 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Reformat
- - - - -
eb6ac737 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Delete unused file
- - - - -
8759e56f by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Rename module Parse to ParsePP
- - - - -
42490e4f by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Clarify naming in the parser
- - - - -
60891959 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
WIP. Switching to alex/happy to be able to work in-tree
Since Parsec is not available
- - - - -
efb9029e by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Layering is now correct
- GHC lexer, emits CPP tokens
- accumulated in Preprocessor state
- Lexed by CPP lexer, CPP command extracted, tokens concated with
spaces (to get rid of token pasting via comments)
- if directive lexed and parsed by CPP lexer/parser, and evaluated
- - - - -
f9040df6 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
First example working
Loading Example1.hs into ghci, getting the right results
```
{-# LANGUAGE GHC_CPP #-}
module Example1 where
y = 3
x =
"hello"
"bye now"
foo = putStrLn x
```
- - - - -
a452cf9b by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Rebase, and all tests pass except whitespace for generated parser
- - - - -
8ec90c01 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
More plumbing. Ready for testing tomorrow.
- - - - -
02e48d73 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Proress. Renamed module State from Types
And at first blush it seems to handle preprocessor scopes properly.
- - - - -
3ddf8eb7 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Insert basic GHC version macros into parser
__GLASGOW_HASKELL__
__GLASGOW_HASKELL_FULL_VERSION__
__GLASGOW_HASKELL_PATCHLEVEL1__
__GLASGOW_HASKELL_PATCHLEVEL2__
- - - - -
e5caf95c by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Re-sync check-cpp for easy ghci work
- - - - -
5864aad5 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Get rid of warnings
- - - - -
62a8a050 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Rework macro processing, in check-cpp
Macros kept at the top level, looked up via name, multiple arity
versions per name can be stored
- - - - -
48a4bc6c by Alan Zimmerman at 2025-06-23T18:33:25+01:00
WIP. Can crack arguments for #define
Next step it to crack out args in an expansion
- - - - -
02a00453 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
WIP on arg parsing.
- - - - -
11be8320 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Progress. Still screwing up nested parens.
- - - - -
a8bfb2a9 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Seems to work, but has redundant code
- - - - -
623c5911 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Remove redundant code
- - - - -
8239ea99 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Reformat
- - - - -
7240e358 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Expand args, single pass
Still need to repeat until fixpoint
- - - - -
debfc2e8 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Fixed point expansion
- - - - -
cbfc797a by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Sync the playground to compiler
- - - - -
56245469 by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Working on dumping the GHC_CPP result
But We need to keep the BufSpan in a comment
- - - - -
35c012ff by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Keep BufSpan in queued comments in GHC.Parser.Lexer
- - - - -
53cf2a2e by Alan Zimmerman at 2025-06-23T18:33:25+01:00
Getting close to being able to print the combined tokens
showing what is in and what is out
- - - - -
d148263f by Alan Zimmerman at 2025-06-23T18:33:26+01:00
First implementation of dumpGhcCpp.
Example output
First dumps all macros in the state, then the source, showing which
lines are in and which are out
------------------------------
- |#define FOO(A,B) A + B
- |#define FOO(A,B,C) A + B + C
- |#if FOO(1,FOO(3,4)) == 8
- |-- a comment
|x = 1
- |#else
- |x = 5
- |#endif
- - - - -
1a44cc0e by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Clean up a bit
- - - - -
70d1268c by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Add -ddump-ghc-cpp option and a test based on it
- - - - -
e5a07fa3 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Restore Lexer.x rules, we need them for continuation lines
- - - - -
29f7484d by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Lexer.x: trying to sort out the span for continuations
- We need to match on \n at the end of the line
- We cannot simply back up for it
- - - - -
9e634da4 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Inserts predefined macros. But does not dump properly
Because the cpp tokens have a trailing newline
- - - - -
a438631a by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Remove unnecessary LExer rules
We *need* the ones that explicitly match to the end of the line.
- - - - -
881cca4a by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Generate correct span for ITcpp
Dump now works, except we do not render trailing `\` for continuation
lines. This is good enough for use in test output.
- - - - -
89947b39 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Reduce duplication in lexer
- - - - -
06ace60c by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Tweaks
- - - - -
2c75ecc2 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Insert min_version predefined macros into state
The mechanism now works. Still need to flesh out the full set.
- - - - -
556589c8 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Trying my alternative pragma syntax.
It works, but dumpGhcCpp is broken, I suspect from the ITcpp token
span update.
- - - - -
1cf0c5fa by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Pragma extraction now works, with both CPP and GHC_CPP
For the following
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 913
{-# LANGUAGE GHC_CPP #-}
#endif
We will enable GHC_CPP only
- - - - -
ee84e1ba by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Remove some tracing
- - - - -
a5ecb924 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Fix test exes for changes
- - - - -
b9f9e561 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
For GHC_CPP tests, normalise config-time-based macros
- - - - -
3b4bb7d0 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
WIP
- - - - -
51359193 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
WIP again. What is wrong?
- - - - -
e25013ec by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Revert to dynflags for normal not pragma lexing
- - - - -
edf5276b by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Working on getting check-exact to work properly
- - - - -
f403c72e by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Passes CppCommentPlacement test
- - - - -
fce7f837 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Starting on exact printing with GHC_CPP
While overriding normal CPP
- - - - -
1b7c033c by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Correctly store CPP ignored tokens as comments
By populating the lexeme string in it, based on the bufpos
- - - - -
5e43cdea by Alan Zimmerman at 2025-06-23T18:33:26+01:00
WIP
- - - - -
c5c0b37f by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Simplifying
- - - - -
679d4083 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Update the active state logic
- - - - -
a739e6dc by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Work the new logic into the mainline code
- - - - -
4e329814 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Process `defined` operator
- - - - -
274e12ae by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Manage lexer state while skipping tokens
There is very intricate layout-related state used when lexing. If a
CPP directive blanks out some tokens, store this state when the
blanking starts, and restore it when they are no longer being blanked.
- - - - -
104b8f1d by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Track the last token buffer index, for ITCppIgnored
We need to attach the source being skipped in an ITCppIgnored token.
We cannot simply use its BufSpan as an index into the underlying
StringBuffer as it counts unicode chars, not bytes.
So we update the lexer state to store the starting StringBuffer
location for the last token, and use the already-stored length to
extract the correct portion of the StringBuffer being parsed.
- - - - -
b87d1014 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Process the ! operator in GHC_CPP expressions
- - - - -
9083f901 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Predefine a constant when GHC_CPP is being used.
- - - - -
b91f355f by Alan Zimmerman at 2025-06-23T18:33:26+01:00
WIP
- - - - -
de0b5aa2 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Skip lines directly in the lexer when required
- - - - -
e4fe6880 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Properly manage location when accepting tokens again
- - - - -
598371e3 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Seems to be working now, for Example9
- - - - -
19fe751b by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Remove tracing
- - - - -
00ccbc1d by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Fix parsing '*' in block comments
Instead of replacing them with '-'
- - - - -
f960dcec by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Keep the trailing backslash in a ITcpp token
- - - - -
a490bd63 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Deal with only enabling one section of a group.
A group is an instance of a conditional introduced by
#if/#ifdef/#ifndef,
and ending at the final #endif, including intermediate #elsif sections
- - - - -
c99ff814 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Replace remaining identifiers with 0 when evaluating
As per the spec
- - - - -
a10efe09 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Snapshot before rebase
- - - - -
3d1a1b1b by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Skip non-processed lines starting with #
- - - - -
d4fc27a9 by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Export generateMacros so we can use it in ghc-exactprint
- - - - -
0f972a8a by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Fix rebase
- - - - -
5287d2bd by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Expose initParserStateWithMacrosString
- - - - -
a3f0e23c by Alan Zimmerman at 2025-06-23T18:33:26+01:00
Fix buggy lexer cppSkip
It was skipping all lines, not just ones prefixed by #
- - - - -
5f85b0e7 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Fix evaluation of && to use the correct operator
- - - - -
92ea7869 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Deal with closing #-} at the start of a line
- - - - -
9ad5ae59 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Add the MIN_VERSION_GLASGOW_HASKELL predefined macro
- - - - -
8d92338e by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Include MIN_VERSION_GLASGOW_HASKELL in GhcCpp01.stderr
- - - - -
9e6d46a7 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Use a strict map for macro defines
- - - - -
e698e9ea by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Process TIdentifierLParen
Which only matters at the start of #define
- - - - -
00facc82 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Do not provide TIdentifierLParen paren twice
- - - - -
e351fbed by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Handle whitespace between identifier and '(' for directive only
- - - - -
30256b62 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Expose some Lexer bitmap manipulation helpers
- - - - -
63fdb781 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Deal with line pragmas as tokens
Blows up for dumpGhcCpp though
- - - - -
96b69aa1 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Allow strings delimited by a single quote too
- - - - -
6e62f419 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Allow leading whitespace on cpp directives
As per https://timsong-cpp.github.io/cppwp/n4140/cpp#1
- - - - -
97bf05e4 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Implement GHC_CPP undef
- - - - -
5c823128 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Sort out expansion of no-arg macros, in a context with args
And make the expansion bottom out, in the case of recursion
- - - - -
28c73f21 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Fix GhcCpp01 test
The LINE pragma stuff works in ghc-exactprint when specifically
setting flag to emit ITline_pragma tokens
- - - - -
16e291d6 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Process comments in CPP directives
- - - - -
5c31a66a by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Correctly lex pragmas with finel #-} on a newline
- - - - -
af6c89b3 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Do not process CPP-style comments
- - - - -
ac6a6f2b by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Allow cpp-style comments when GHC_CPP enabled
- - - - -
67266cd5 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Return other pragmas as cpp ignored when GHC_CPP active
- - - - -
162d77fd by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Fix exactprinting default decl
- - - - -
17689987 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Reorganise getOptionsFromFile for use in ghc-exactprint
We want to be able to inject predefined macro definitions into the
parser preprocessor state for when we do a hackage roundtrip.
- - - - -
8ed49e2d by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Tweak testing
- - - - -
54a3bd41 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Only allow unknown cpp pragmas with # in left margin
- - - - -
56c93232 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Require # against left margin for all GHC_CPP directives
- - - - -
eb6fd328 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Fix CPP directives appearing in pragmas
And add a test for error reporting for missing `#if`
- - - - -
94f2eca9 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Starting to report GHC_CPP errors using GHC machinery
- - - - -
04d4acfb by Alan Zimmerman at 2025-06-23T18:33:27+01:00
More GHC_CPP diagnostic results
- - - - -
c2e86d5d by Alan Zimmerman at 2025-06-23T18:33:27+01:00
WIP on converting error calls to GHC diagnostics in GHC_CPP
- - - - -
9cafc60c by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Working on CPP diagnostic reporting
- - - - -
6c2b4b4c by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Tweak some tests/lint warnings
- - - - -
69940b06 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
More error reporting in Macro
- - - - -
2fef4fa7 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Some cleanups
- - - - -
6c6fb819 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Some cleanup
- - - - -
90d4eede by Alan Zimmerman at 2025-06-23T18:33:27+01:00
GHC_CPP: Working on improving error reporting
- - - - -
4175b3cc by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Harvest some commonality
- - - - -
3d43d296 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Use PPM as Maybe inside PP
- - - - -
50267897 by Alan Zimmerman at 2025-06-23T18:33:27+01:00
Clean up a bit
- - - - -
162 changed files:
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Parser/Monad.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/DataCon.hs-boot
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Parser.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser.hs-boot
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- + compiler/GHC/Parser/PreProcess.hs
- + compiler/GHC/Parser/PreProcess/Eval.hs
- + compiler/GHC/Parser/PreProcess/Lexer.x
- + compiler/GHC/Parser/PreProcess/Macro.hs
- + compiler/GHC/Parser/PreProcess/ParsePP.hs
- + compiler/GHC/Parser/PreProcess/Parser.y
- + compiler/GHC/Parser/PreProcess/ParserM.hs
- + compiler/GHC/Parser/PreProcess/State.hs
- compiler/GHC/Parser/Utils.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/debugging.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- ghc/GHCi/UI.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/stack.yaml.lock
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- linters/lint-whitespace/lint-whitespace.cabal
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- testsuite/tests/driver/T4437.hs
- testsuite/tests/ghc-api/T11579.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.stderr
- + testsuite/tests/ghc-cpp/GhcCpp02.hs
- + testsuite/tests/ghc-cpp/GhcCpp02.stderr
- + testsuite/tests/ghc-cpp/all.T
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout
- testsuite/tests/hiefile/should_run/all.T
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- + testsuite/tests/printer/CppCommentPlacement.hs
- testsuite/tests/printer/T18791.stderr
- + testsuite/tests/th/GadtConSigs_th_dump1.hs
- + testsuite/tests/th/GadtConSigs_th_dump1.stderr
- + testsuite/tests/th/GadtConSigs_th_pprint1.hs
- + testsuite/tests/th/GadtConSigs_th_pprint1.stderr
- testsuite/tests/th/T20868.stdout
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/T23739a.hs
- + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T20443b.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr
- + testsuite/tests/vdq-rta/should_compile/T25127_data.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_data_inst.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_infix.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_newtype.hs
- testsuite/tests/vdq-rta/should_compile/all.T
- testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.stderr
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- + utils/check-cpp/.ghci
- + utils/check-cpp/.gitignore
- + utils/check-cpp/Eval.hs
- + utils/check-cpp/Example1.hs
- + utils/check-cpp/Example10.hs
- + utils/check-cpp/Example11.hs
- + utils/check-cpp/Example12.hs
- + utils/check-cpp/Example13.hs
- + utils/check-cpp/Example2.hs
- + utils/check-cpp/Example3.hs
- + utils/check-cpp/Example4.hs
- + utils/check-cpp/Example5.hs
- + utils/check-cpp/Example6.hs
- + utils/check-cpp/Example7.hs
- + utils/check-cpp/Example8.hs
- + utils/check-cpp/Example9.hs
- + utils/check-cpp/Lexer.x
- + utils/check-cpp/Macro.hs
- + utils/check-cpp/Main.hs
- + utils/check-cpp/ParsePP.hs
- + utils/check-cpp/ParseSimulate.hs
- + utils/check-cpp/Parser.y
- + utils/check-cpp/ParserM.hs
- + utils/check-cpp/PreProcess.hs
- + utils/check-cpp/README.md
- + utils/check-cpp/State.hs
- + utils/check-cpp/run.sh
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/check-exact/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eadbe239c57c52d209ea58aa56e2603...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eadbe239c57c52d209ea58aa56e2603...
You're receiving this email because of your account on gitlab.haskell.org.