Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
fd64667d by Vladislav Zavialov at 2025-05-20T03:25:08-04:00
Allow the 'data' keyword in import/export lists (#25899)
This patch introduces the 'data' namespace specifier in import and
export lists. The intended use is to import data constructors without
their parent type constructors, e.g.
import Data.Proxy as D (data Proxy)
type DP = D.Proxy -- promoted data constructor
Additionally, it is possible to use 'data' to explicitly qualify any
data constructors or terms, incl. operators and field selectors
import Prelude (Semigroup(data (<>)))
import Data.Function (data (&))
import Data.Monoid (data Dual, data getDual)
x = Dual "Hello" <> Dual "World" & getDual
The implementation mostly builds on top of the existing logic for the
'type' and 'pattern' namespace specifiers, plus there are a few tweaks
to how we generate suggestions in error messages.
- - - - -
acc86753 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Use field selectors when creating BCOs
This makes it easier to grep for these fields.
- - - - -
60a55fd7 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Clarify BCO size
Previously the semantics and size of StgBCO was a bit unclear.
Specifically, the `size` field was documented to contain the size of the
bitmap whereas it was actually the size of the closure *and* bitmap.
Additionally, it was not as clear as it could be that the bitmap was a
full StgLargeBitmap with its own `size` field.
- - - - -
ac9fb269 by Simon Peyton Jones at 2025-05-20T09:19:04-04:00
Track rewriter sets more accurately in constraint solving
This MR addresses #26003, by refactoring the arcane
intricacies of Note [Equalities with incompatible kinds].
NB: now retitled to
Note [Equalities with heterogeneous kinds].
and the main Note for this MR.
In particular:
* Abandon invariant (COERCION-HOLE) in Note [Unification preconditions] in
GHC.Tc.Utils.Unify.
* Abandon invariant (TyEq:CH)) in Note [Canonical equalities] in
GHC.Tc.Types.Constraint.
* Instead: add invariant (REWRITERS) to Note [Unification preconditions]:
unify only if the constraint has an empty rewriter set.
Implementation:
* In canEqCanLHSFinish_try_unification, skip trying unification if there is a
non-empty rewriter set.
* To do this, make sure the rewriter set is zonked; do so in selectNextWorkItem,
which also deals with prioritisation.
* When a coercion hole is filled, kick out inert equalities that have that hole
as a rewriter. It might now be unlocked and available to unify.
* Remove the ad-hoc `ch_hetero_kind` field of `CoercionHole`.
* In `selectNextWorkItem`, priorities equalities withan empty rewriter set.
* Defaulting: see (DE6) in Note [Defaulting equalities]
and Note [Limited defaulting in the ambiguity check]
* Concreteness checks: there is some extra faff to try to get decent
error messages when the FRR (representation-polymorphism) checks
fail. In partiular, add a "When unifying..." explanation when the
representation-polymorphism check arose from another constraint.
- - - - -
86406f48 by Cheng Shao at 2025-05-20T09:19:47-04:00
rts: fix rts_clearMemory logic when sanity checks are enabled
This commit fixes an RTS assertion failure when invoking
rts_clearMemory with +RTS -DS. -DS implies -DZ which asserts that free
blocks contain 0xaa as the designated garbage value. Also adds the
sanity way to rts_clearMemory test to prevent future regression.
Closes #26011.
ChatGPT Codex automatically diagnosed the issue and proposed the
initial patch in a single shot, given a GHC checkout and the following
prompt:
---
Someone is reporting the following error when attempting to use `rts_clearMemory` with the RTS option `-DS`:
```
test.wasm: internal error: ASSERTION FAILED: file rts/sm/Storage.c, line 1216
(GHC version 9.12.2.20250327 for wasm32_unknown_wasi)
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
```
What's the culprit? How do I look into this issue?
---
I manually reviewed & revised the patch, tested and submitted it.
- - - - -
7147370b by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: do not allocate strings in bytecode assembler
This patch refactors the compiler to avoid allocating iserv buffers
for BCONPtrStr at assemble-time. Now BCONPtrStr ByteStrings are
recorded as a part of CompiledByteCode, and actual allocation only
happens at link-time. This refactoring is necessary for adding
bytecode serialization functionality, as explained by the revised
comments in this commit.
- - - - -
a67db612 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_strs serializable
This commit makes the bc_strs field in CompiledByteCode serializable;
similar to previous commit, we preserve the ByteString directly and
defer the actual allocation to link-time, as mentioned in updated
comment.
- - - - -
5faf34ef by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_itbls serializable
This commit makes bc_itbls in CompiledByteCode serializable. A
dedicated ConInfoTable datatype has been added in ghci which is the
recipe for dynamically making a datacon's info table, containing the
payload of the MkConInfoTable iserv message.
- - - - -
2abaf8c1 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove FFIInfo bookkeeping in BCO
This commit removes the bc_ffis field from CompiledByteCode
completely, as well as all the related bookkeeping logic in
GHC.StgToByteCode. bc_ffis is actually *unused* in the rest of GHC
codebase! It is merely a list of FFIInfo, which is just a remote
pointer of the libffi ffi_cif struct; once we allocate the ffi_cif
struct and put its pointer in a CCALL instruction, we'll never free it
anyway. So there is no point of bookkeeping.
- - - - -
adb9e4d2 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make FFIInfo serializable in BCO
This commit makes all the FFIInfo needed in CCALL instructions
serializable. Previously, when doing STG to BCO lowering, we would
allocate a libffi ffi_cif struct and keep its remote pointer as
FFIInfo; but actually we can just keep the type signature as FFIInfo
and defer the actual allocation to link-time.
- - - - -
200f401b by Cheng Shao at 2025-05-20T17:22:19-04:00
ghci: remove redundant NewBreakModule message
This commit removes the redundant NewBreakModule message from ghci: it
just allocates two strings! This functionality can be implemented with
existing MallocStrings in one iserv call.
- - - - -
ddaadca6 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make breakpoint module name and unit id serializable
This commit makes breakpoint module name and unit id serializable, in
BRK_FUN instructions as well as ModBreaks. We can simply keep the
module name and unit ids, and defer the buffer allocation to link
time.
- - - - -
a0fde202 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove unused newModule
This commit removes the now unused newModule function from GHC.
- - - - -
68c8f140 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: add BCONPtrFS for interned top level string literals in BCO
This commit adds BCONPtrFS as a BCO non-pointer literal kind, which
has the same semantics of BCONPtrStr, except it contains a FastString
instead of a ByteString. By using BCONPtrFS to represent top level
string literals that are already FastString in the compilation
pipeline, we enjoy the FastString interning logic and avoid allocating
a bunch of redundant ByteStrings for the same FastStrings, especially
when we lower the BRK_FUN instruction.
- - - - -
f2b532bc by Peng Fan at 2025-05-20T17:23:15-04:00
hadrian: enable GHCi for loongarch64
- - - - -
8ded2330 by kwxm at 2025-05-20T17:24:07-04:00
Fix bugs in `integerRecipMod` and `integerPowMod`
This fixes #26017.
* `integerRecipMod x 1` now returns `(# 1 | #)` for all x; previously it
incorrectly returned `(# | () #)`, indicating failure.
* `integerPowMod 0 e m` now returns `(# | () #)` for e<0 and m>1, indicating
failure; previously it incorrectly returned `(# 0 | #)`.
- - - - -
c9abb87c by Andreas Klebinger at 2025-05-20T17:24:50-04:00
Specialise: Don't float out constraint components.
It was fairly complex to do so and it doesn't seem to improve anything.
Nofib allocations were unaffected as well.
See also Historical Note [Floating dictionaries out of cases]
- - - - -
202b201c by Andreas Klebinger at 2025-05-21T10:16:14-04:00
Interpreter: Add limited support for direct primop evaluation.
This commit adds support for a number of primops directly
to the interpreter. This avoids the indirection of going
through the primop wrapper for those primops speeding interpretation
of optimized code up massively.
Code involving IntSet runs about 25% faster with optimized core and these
changes. For core without breakpoints it's even more pronouced and I
saw reductions in runtime by up to 50%.
Running GHC itself in the interpreter was sped up by ~15% through this
change.
Additionally this comment does a few other related changes:
testsuite:
* Run foundation test in ghci and ghci-opt ways to test these
primops.
* Vastly expand the foundation test to cover all basic primops
by comparing result with the result of calling the wrapper.
Interpreter:
* When pushing arguments for interpreted primops extend each argument to
at least word with when pushing. This avoids some issues with big
endian. We can revisit this if it causes performance issues.
* Restructure the stack chunk check logic. There are now macros for
read accesses which might cross stack chunk boundries and macros which
omit the checks which are used when we statically know we access an
address in the current stack chunk.
- - - - -
67a177b4 by sheaf at 2025-05-21T10:17:04-04:00
QuickLook: do a shape test before unifying
This commit ensures we do a shape test before unifying. This ensures
we don't try to unify a TyVarTv with a non-tyvar, e.g.
alpha[tyv] := Int
On the way, we refactor simpleUnifyCheck:
1. Move the checkTopShape check into simpleUnifyCheck
2. Refactors simpleUnifyCheck to return a value of the new type
SimpleUnifyResult type. Now, simpleUnifyCheck returns "can unify",
"cannot unify" or "dunno" (with "cannot unify" being the new result
it can return). Now:
- touchabilityTest is included; it it fails we return "cannot unify"
- checkTopShape now returns "cannot unify" instead of "dunno" upon failure
3. Move the call to simpleUnifyCheck out of checkTouchableTyVarEq.
After that, checkTouchableTyVarEq becames a simple call to
checkTyEqRhs, so we inline it.
This allows the logic in canEqCanLHSFinish_try_unification to be simplified.
In particular, we now avoid calling 'checkTopShape' twice.
Two further changes suggested by Simon were also implemented:
- In canEqCanLHSFinish, if checkTyEqRhs returns PuFail with
'do_not_prevent_rewriting', we now **continue with this constraint**.
This allows us to use the constraint for rewriting.
- checkTyEqRhs now has a top-level check to avoid flattening a tyfam app
in a top-level equality of the form alpha ~ F tys, as this is
going around in circles. This simplifies the implementation without
any change in behaviour.
Fixes #25950
Fixes #26030
- - - - -
4020972c by sheaf at 2025-05-21T10:17:04-04:00
FixedRuntimeRepError: omit unhelpful explanation
This commit tweaks the FixedRuntimeRepError case of pprTcSolverReportMsg,
to avoid including an explanation which refers to a type variable that
appears nowhere else.
For example, the old error message could look like the following:
The pattern binding does not have a fixed runtime representation.
Its type is:
T :: TYPE R
Cannot unify ‘R’ with the type variable ‘c0’
because the former is not a concrete ‘RuntimeRep’.
With this commit, we now omit the last two lines, because the concrete
type variable (here 'c0') does not appear in the type displayed to the
user (here 'T :: TYPE R').
- - - - -
6d058a69 by Andrea Bedini at 2025-05-21T16:00:51-04:00
Don't fail when ghcversion.h can't be found (#26018)
If ghcversion.h can't be found, don't try to include it. This happens
when there is no rts package in the package db and when -ghcversion-file
argument isn't passed.
Co-authored-by: Syvlain Henry
- - - - -
b1212fbf by Vladislav Zavialov at 2025-05-21T16:01:33-04:00
Implement -Wpattern-namespace-specifier (#25900)
In accordance with GHC Proposal #581 "Namespace-specified imports",
section 2.3 "Deprecate use of pattern in import/export lists", the
`pattern` namespace specifier is now deprecated.
Test cases: T25900 T25900_noext
- - - - -
5f9819f0 by Alan Zimmerman at 2025-05-22T22:12:55+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
- - - - -
11176136 by Alan Zimmerman at 2025-05-22T22:12:55+01:00
Tidy up before re-visiting the continuation mechanic
- - - - -
47e76645 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Switch preprocessor to continuation passing style
Proof of concept, needs tidying up
- - - - -
d44302c4 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Small cleanup
- - - - -
db3471aa by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Get rid of some cruft
- - - - -
b4f1fc0c by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Starting to integrate.
Need to get the pragma recognised and set
- - - - -
bf3e28f1 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Make cppTokens extend to end of line, and process CPP comments
- - - - -
8226c652 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Remove unused ITcppDefined
- - - - -
477dfa48 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Allow spaces between # and keyword for preprocessor directive
- - - - -
68c9e3e3 by Alan Zimmerman at 2025-05-22T22:12:56+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.
- - - - -
4d22e538 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Accumulate CPP continuations, process when ready
Can be simplified further, we only need one CPP token
- - - - -
31df65b6 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Simplify Lexer interface. Only ITcpp
We transfer directive lines through it, then parse them from scratch
in the preprocessor.
- - - - -
759ab4b1 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Deal with directive on last line, with no trailing \n
- - - - -
ec94b890 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Start parsing and processing the directives
- - - - -
3a11de81 by Alan Zimmerman at 2025-05-22T22:12:56+01:00
Prepare for processing include files
- - - - -
72e3501a by Alan Zimmerman at 2025-05-22T22:14:17+01:00
Move PpState into PreProcess
And initParserState, initPragState too
- - - - -
ad21b20d by Alan Zimmerman at 2025-05-22T22:14:20+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
- - - - -
0ca0c855 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Split into separate files
- - - - -
1c4356ce by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Starting on expression parser.
But it hangs. Time for Text.Parsec.Expr
- - - - -
cff5454d by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Start integrating the ghc-cpp work
From https://github.com/alanz/ghc-cpp
- - - - -
4f58197e by Alan Zimmerman at 2025-05-22T22:14:20+01:00
WIP
- - - - -
9d81e1ea by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Fixup after rebase
- - - - -
39af11a7 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
WIP
- - - - -
df0745a3 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Fixup after rebase, including all tests pass
- - - - -
703caf13 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Change pragma usage to GHC_CPP from GhcCPP
- - - - -
a94f407e by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Some comments
- - - - -
6c85f782 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Reformat
- - - - -
d5b5c55c by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Delete unused file
- - - - -
437d8ca4 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Rename module Parse to ParsePP
- - - - -
13103f60 by Alan Zimmerman at 2025-05-22T22:14:20+01:00
Clarify naming in the parser
- - - - -
822515eb by Alan Zimmerman at 2025-05-22T22:14:50+01:00
WIP. Switching to alex/happy to be able to work in-tree
Since Parsec is not available
- - - - -
1b4dd725 by Alan Zimmerman at 2025-05-22T22:14:50+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
- - - - -
95c785ff by Alan Zimmerman at 2025-05-22T22:14:50+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
```
- - - - -
b51beccd by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Rebase, and all tests pass except whitespace for generated parser
- - - - -
a24f5f2f by Alan Zimmerman at 2025-05-22T22:14:50+01:00
More plumbing. Ready for testing tomorrow.
- - - - -
0a0b0708 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Proress. Renamed module State from Types
And at first blush it seems to handle preprocessor scopes properly.
- - - - -
4c69cb5b by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Insert basic GHC version macros into parser
__GLASGOW_HASKELL__
__GLASGOW_HASKELL_FULL_VERSION__
__GLASGOW_HASKELL_PATCHLEVEL1__
__GLASGOW_HASKELL_PATCHLEVEL2__
- - - - -
4b4d6995 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Re-sync check-cpp for easy ghci work
- - - - -
81d37032 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Get rid of warnings
- - - - -
f4e03a2a by Alan Zimmerman at 2025-05-22T22:14:50+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
- - - - -
f2ae2b88 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
WIP. Can crack arguments for #define
Next step it to crack out args in an expansion
- - - - -
d7404efc by Alan Zimmerman at 2025-05-22T22:14:50+01:00
WIP on arg parsing.
- - - - -
01660582 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Progress. Still screwing up nested parens.
- - - - -
94895aeb by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Seems to work, but has redundant code
- - - - -
6c532dd1 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Remove redundant code
- - - - -
095587c5 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Reformat
- - - - -
9d704c28 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Expand args, single pass
Still need to repeat until fixpoint
- - - - -
055f2593 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Fixed point expansion
- - - - -
8a582858 by Alan Zimmerman at 2025-05-22T22:14:50+01:00
Sync the playground to compiler
- - - - -
7fcadd89 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Working on dumping the GHC_CPP result
But We need to keep the BufSpan in a comment
- - - - -
15ef23fe by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Keep BufSpan in queued comments in GHC.Parser.Lexer
- - - - -
7f10bb6a by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Getting close to being able to print the combined tokens
showing what is in and what is out
- - - - -
63d523a6 by Alan Zimmerman at 2025-05-22T22:14:51+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
- - - - -
2e6d0e63 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Clean up a bit
- - - - -
353758ab by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Add -ddump-ghc-cpp option and a test based on it
- - - - -
71ee0255 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Restore Lexer.x rules, we need them for continuation lines
- - - - -
87851fb1 by Alan Zimmerman at 2025-05-22T22:14:51+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
- - - - -
09b9a4bd by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Inserts predefined macros. But does not dump properly
Because the cpp tokens have a trailing newline
- - - - -
1da1f2ba by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Remove unnecessary LExer rules
We *need* the ones that explicitly match to the end of the line.
- - - - -
261a46d8 by Alan Zimmerman at 2025-05-22T22:14:51+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.
- - - - -
6c93fc2b by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Reduce duplication in lexer
- - - - -
8701de14 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Tweaks
- - - - -
a97fd0f3 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Insert min_version predefined macros into state
The mechanism now works. Still need to flesh out the full set.
- - - - -
236db9af by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Trying my alternative pragma syntax.
It works, but dumpGhcCpp is broken, I suspect from the ITcpp token
span update.
- - - - -
3ff850e5 by Alan Zimmerman at 2025-05-22T22:14:51+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
- - - - -
a8b19230 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Remove some tracing
- - - - -
198bdcd1 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Fix test exes for changes
- - - - -
b338bf64 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
For GHC_CPP tests, normalise config-time-based macros
- - - - -
234ff313 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
WIP
- - - - -
28a6e54e by Alan Zimmerman at 2025-05-22T22:14:51+01:00
WIP again. What is wrong?
- - - - -
9ba4a1b7 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Revert to dynflags for normal not pragma lexing
- - - - -
58140acc by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Working on getting check-exact to work properly
- - - - -
75d33a76 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Passes CppCommentPlacement test
- - - - -
c1a161c1 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Starting on exact printing with GHC_CPP
While overriding normal CPP
- - - - -
3ea98183 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Correctly store CPP ignored tokens as comments
By populating the lexeme string in it, based on the bufpos
- - - - -
667e4e28 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
WIP
- - - - -
e9367fbc by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Simplifying
- - - - -
5bbc1e18 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Update the active state logic
- - - - -
30876c4f by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Work the new logic into the mainline code
- - - - -
0461f7c8 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Process `defined` operator
- - - - -
46206cb4 by Alan Zimmerman at 2025-05-22T22:14:51+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.
- - - - -
536358bf by Alan Zimmerman at 2025-05-22T22:14:51+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.
- - - - -
85368bcf by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Process the ! operator in GHC_CPP expressions
- - - - -
e08f6d1b by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Predefine a constant when GHC_CPP is being used.
- - - - -
9f672a34 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
WIP
- - - - -
30b7c3bf by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Skip lines directly in the lexer when required
- - - - -
5a0ee799 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Properly manage location when accepting tokens again
- - - - -
5ad81aa4 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Seems to be working now, for Example9
- - - - -
f6348314 by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Remove tracing
- - - - -
468a126a by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Fix parsing '*' in block comments
Instead of replacing them with '-'
- - - - -
97f6e21b by Alan Zimmerman at 2025-05-22T22:14:51+01:00
Keep the trailing backslash in a ITcpp token
- - - - -
98dddab4 by Alan Zimmerman at 2025-05-22T22:14:52+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
- - - - -
541e71eb by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Replace remaining identifiers with 0 when evaluating
As per the spec
- - - - -
f186b1ee by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Snapshot before rebase
- - - - -
162b6b02 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Skip non-processed lines starting with #
- - - - -
d2bac260 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Export generateMacros so we can use it in ghc-exactprint
- - - - -
d9b1cd5d by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Fix rebase
- - - - -
a0b1a58e by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Expose initParserStateWithMacrosString
- - - - -
27b4a8f4 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Fix buggy lexer cppSkip
It was skipping all lines, not just ones prefixed by #
- - - - -
31fa91e0 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Fix evaluation of && to use the correct operator
- - - - -
54aa92fa by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Deal with closing #-} at the start of a line
- - - - -
16c77f58 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Add the MIN_VERSION_GLASGOW_HASKELL predefined macro
- - - - -
61b5a020 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Include MIN_VERSION_GLASGOW_HASKELL in GhcCpp01.stderr
- - - - -
46f153ba by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Use a strict map for macro defines
- - - - -
ac7432b5 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Process TIdentifierLParen
Which only matters at the start of #define
- - - - -
023b9f5d by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Do not provide TIdentifierLParen paren twice
- - - - -
eace047d by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Handle whitespace between identifier and '(' for directive only
- - - - -
41afd012 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Expose some Lexer bitmap manipulation helpers
- - - - -
24386ed0 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Deal with line pragmas as tokens
Blows up for dumpGhcCpp though
- - - - -
d6f4211b by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Allow strings delimited by a single quote too
- - - - -
86250e0b by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Allow leading whitespace on cpp directives
As per https://timsong-cpp.github.io/cppwp/n4140/cpp#1
- - - - -
d6601e32 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Implement GHC_CPP undef
- - - - -
97ea1aa6 by Alan Zimmerman at 2025-05-22T22:14:52+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
- - - - -
cb611082 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Fix GhcCpp01 test
The LINE pragma stuff works in ghc-exactprint when specifically
setting flag to emit ITline_pragma tokens
- - - - -
55b9208b by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Process comments in CPP directives
- - - - -
ad97286e by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Correctly lex pragmas with finel #-} on a newline
- - - - -
dc5605de by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Do not process CPP-style comments
- - - - -
707fa924 by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Allow cpp-style comments when GHC_CPP enabled
- - - - -
d42d7b4a by Alan Zimmerman at 2025-05-22T22:14:52+01:00
Return other pragmas as cpp ignored when GHC_CPP active
- - - - -
c2eb0e2d by Alan Zimmerman at 2025-05-22T23:21:45+01:00
Fix exactprinting default decl
- - - - -
274 changed files:
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/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/Opt/Specialise.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Tidy.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/ImpExp.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.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/Names.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/debugging.rst
- docs/users_guide/exts/explicit_namespaces.rst
- docs/users_guide/exts/pattern_synonyms.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- hadrian/src/Flavour.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/stack.yaml.lock
- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs
- libraries/ghc-internal/src/GHC/Internal/TypeLits.hs
- libraries/ghc-internal/src/GHC/Internal/TypeNats.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- rts/Disassembler.c
- rts/Interpreter.c
- rts/PrimOps.cmm
- rts/include/rts/Bytecodes.h
- rts/include/rts/storage/Closures.h
- rts/sm/Storage.h
- testsuite/tests/bytecode/T22376/all.T
- testsuite/tests/callarity/unittest/CallArity1.hs
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_fail/T11471.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/T4437.hs
- testsuite/tests/driver/all.T
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/ghc-api/T11579.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.stderr
- + testsuite/tests/ghc-cpp/all.T
- + testsuite/tests/ghci/all.T
- + testsuite/tests/ghci/ghci-mem-primops.hs
- + testsuite/tests/ghci/ghci-mem-primops.script
- + testsuite/tests/ghci/ghci-mem-primops.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/lib/integer/T26017.hs
- + testsuite/tests/lib/integer/T26017.stdout
- testsuite/tests/lib/integer/all.T
- testsuite/tests/lib/integer/integerRecipMod.hs
- testsuite/tests/lib/integer/integerRecipMod.stdout
- testsuite/tests/module/T21826.stderr
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- + testsuite/tests/parser/should_compile/T25900.hs
- + testsuite/tests/parser/should_compile/T25900.stderr
- + testsuite/tests/parser/should_compile/T25900_noext.hs
- + testsuite/tests/parser/should_compile/T25900_noext.stderr
- testsuite/tests/parser/should_compile/all.T
- testsuite/tests/partial-sigs/should_fail/T14040a.stderr
- testsuite/tests/partial-sigs/should_fail/T14584.stderr
- testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs
- testsuite/tests/patsyn/should_compile/T11959.hs
- testsuite/tests/patsyn/should_compile/T11959.stderr
- testsuite/tests/patsyn/should_compile/T11959Lib.hs
- testsuite/tests/patsyn/should_compile/T13350/boolean/Boolean.hs
- testsuite/tests/patsyn/should_compile/T22521.hs
- testsuite/tests/patsyn/should_compile/T9857.hs
- testsuite/tests/patsyn/should_compile/export.hs
- testsuite/tests/perf/should_run/ByteCodeAsm.hs
- testsuite/tests/pmcheck/complete_sigs/T25115a.hs
- testsuite/tests/pmcheck/should_compile/T11822.hs
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/polykinds/T14270.hs
- testsuite/tests/polykinds/T14846.stderr
- + testsuite/tests/printer/CppCommentPlacement.hs
- testsuite/tests/rename/should_compile/T12548.hs
- testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25899a.hs
- + testsuite/tests/rename/should_compile/T25899b.hs
- + testsuite/tests/rename/should_compile/T25899c.hs
- + testsuite/tests/rename/should_compile/T25899c_helper.hs
- + testsuite/tests/rename/should_compile/T25899d.script
- + testsuite/tests/rename/should_compile/T25899d.stdout
- testsuite/tests/rename/should_compile/all.T
- testsuite/tests/rename/should_fail/T22581a.stderr
- testsuite/tests/rename/should_fail/T22581b.stderr
- testsuite/tests/rename/should_fail/T25056.stderr
- testsuite/tests/rename/should_fail/T25056a.hs
- + testsuite/tests/rename/should_fail/T25899e1.hs
- + testsuite/tests/rename/should_fail/T25899e1.stderr
- + testsuite/tests/rename/should_fail/T25899e2.hs
- + testsuite/tests/rename/should_fail/T25899e2.stderr
- + testsuite/tests/rename/should_fail/T25899e3.hs
- + testsuite/tests/rename/should_fail/T25899e3.stderr
- + testsuite/tests/rename/should_fail/T25899e_helper.hs
- + testsuite/tests/rename/should_fail/T25899f.hs
- + testsuite/tests/rename/should_fail/T25899f.stderr
- + testsuite/tests/rename/should_fail/T25899f_helper.hs
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rep-poly/RepPolyArgument.stderr
- testsuite/tests/rep-poly/RepPolyBackpack1.stderr
- testsuite/tests/rep-poly/RepPolyBinder.stderr
- testsuite/tests/rep-poly/RepPolyDoBind.stderr
- testsuite/tests/rep-poly/RepPolyDoBody1.stderr
- testsuite/tests/rep-poly/RepPolyDoBody2.stderr
- testsuite/tests/rep-poly/RepPolyLeftSection2.stderr
- testsuite/tests/rep-poly/RepPolyMagic.stderr
- testsuite/tests/rep-poly/RepPolyMcBind.stderr
- testsuite/tests/rep-poly/RepPolyMcBody.stderr
- testsuite/tests/rep-poly/RepPolyMcGuard.stderr
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyPatBind.stderr
- testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.stderr
- testsuite/tests/rep-poly/RepPolyRule1.stderr
- testsuite/tests/rep-poly/RepPolyTuple.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/RepPolyTupleSection.stderr
- testsuite/tests/rep-poly/RepPolyWrappedVar.stderr
- testsuite/tests/rep-poly/T11473.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/rep-poly/T12973.stderr
- testsuite/tests/rep-poly/T13233.stderr
- testsuite/tests/rep-poly/T13929.stderr
- testsuite/tests/rep-poly/T14561.stderr
- testsuite/tests/rep-poly/T14561b.stderr
- testsuite/tests/rep-poly/T17817.stderr
- testsuite/tests/rep-poly/T19615.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/T23903.stderr
- testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr
- testsuite/tests/simplCore/should_compile/T15186.hs
- testsuite/tests/simplCore/should_compile/T15186A.hs
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/typecheck/no_skolem_info/T14040.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T26030.hs
- testsuite/tests/typecheck/should_compile/TypeRepCon.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T16204c.stderr
- + testsuite/tests/typecheck/should_fail/T25950.hs
- + testsuite/tests/typecheck/should_fail/T25950.stderr
- testsuite/tests/typecheck/should_fail/T7696.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/warnings/should_compile/DataToTagWarnings.hs
- testsuite/tests/warnings/should_compile/T14794a.hs
- testsuite/tests/warnings/should_compile/T14794a.stderr
- testsuite/tests/warnings/should_compile/T14794b.hs
- testsuite/tests/warnings/should_compile/T14794b.stderr
- testsuite/tests/warnings/should_compile/T14794c.hs
- testsuite/tests/warnings/should_compile/T14794c.stderr
- testsuite/tests/warnings/should_compile/T14794d.hs
- testsuite/tests/warnings/should_compile/T14794d.stderr
- testsuite/tests/warnings/should_compile/T14794e.hs
- testsuite/tests/warnings/should_compile/T14794e.stderr
- testsuite/tests/warnings/should_compile/T14794f.hs
- testsuite/tests/warnings/should_compile/T14794f.stderr
- testsuite/tests/wcompat-warnings/Template.hs
- + testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
- + 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/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.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/57c097dad0ebf79e229ccf7f04d2a9a...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57c097dad0ebf79e229ccf7f04d2a9a...
You're receiving this email because of your account on gitlab.haskell.org.