[Git][ghc/ghc][wip/spj-apporv-Oct24] 70 commits: level imports: Fix infinite loop with cyclic module imports
by Apoorv Ingle (@ani) 04 Aug '25
by Apoorv Ingle (@ani) 04 Aug '25
04 Aug '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00
level imports: Fix infinite loop with cyclic module imports
I didn't anticipate that downsweep would run before we checked for
cyclic imports. Therefore we need to use the reachability function which
handles cyclic graphs.
Fixes #26087
- - - - -
d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00
Fix documentation about deriving from generics
- - - - -
f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00
Fix issues with toRational for types capable to represent infinite and not-a-number values
This commit fixes all of the following pitfalls:
> toRational (read "Infinity" :: Double)
179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1
> toRational (read "NaN" :: Double)
269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
> realToFrac (read "NaN" :: Double) -- With -O0
Infinity
> realToFrac (read "NaN" :: Double) -- With -O1
NaN
> realToFrac (read "NaN" :: Double) :: CDouble
Infinity
> realToFrac (read "NaN" :: CDouble) :: Double
Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338
- - - - -
5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
- - - - -
9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00
template haskell: use a precise condition when implicitly lifting
Implicit lifting corrects a level error by replacing references to `x`
with `$(lift x)`, therefore you can use a level `n` binding at level `n
+ 1`, if it can be lifted.
Therefore, we now have a precise check that the use level is 1 more than
the bind level.
Before this bug was not observable as you only had 0 and 1 contexts but
it is easily evident when using explicit level imports.
Fixes #26088
- - - - -
5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
- - - - -
c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag for -fexpose-overloaded-unfoldings
Fixes #26112
- - - - -
49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00
Refactor GHC.Driver.Errors.printMessages
- - - - -
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-04:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
- - - - -
0a583689 by Sylvain Henry at 2025-07-24T16:20:26-04:00
STM: don't create a transaction in the rhs of catchRetry# (#26028)
We don't need to create a transaction for the rhs of (catchRetry#)
because contrary to the lhs we don't need to abort it on retry. Moreover
it is particularly harmful if we have code such as (#26028):
let cN = readTVar vN >> retry
tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...))
atomically tree
Because it will stack transactions for the rhss and the read-sets of all
the transactions will be iteratively merged in O(n^2) after the
execution of the most nested retry.
- - - - -
a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Refactor of Specialise.hs
This patch just tidies up `specHeader` a bit, removing one
of its many results, and adding some comments.
No change in behaviour.
Also add a few more `HasDebugCallStack` contexts.
- - - - -
1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* I improved `solveOneFromTheOther` to account for rewriter sets. Previously
it would solve a non-rewritten dict from a rewritten one. For equalities
we were already dealing with this, in
Some incidental refactoring
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
* GHC.Core.FVs.exprFVs now returns /all/ free vars.
Use `exprLocalFVs` for Local vars.
Reason: I wanted another variant for /evidence/ variables.
* Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.)
Rename `isEvVar` to `isEvId`.
* I moved `inert_safehask` out of `InertCans` and into `InertSet` where it
more properly belongs.
Compiler-perf changes:
* There was a palpable bug (#26117) which this MR fixes in
newWantedEvVar, which bypassed all the subtle overlapping-Given
and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this
but leads to extra dictionary bindings; they are optimised away quickly
but they made CoOpt_Read allocate 3.6% more.
* Hpapily T15164 improves.
* The net compiler-allocation change is 0.0%
Metric Decrease:
T15164
Metric Increase:
CoOpt_Read
T12425
- - - - -
953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Solve forall-constraints immediately, or not at all
This MR refactors the constraint solver to solve forall-constraints immediately,
rather than emitting an implication constraint to be solved later.
The most immediate motivation was that when solving quantified constraints
in SPECIALISE pragmas, we really really don't want to leave behind half-
solved implications. Also it's in tune with the approach of the new
short-cut solver, which recursively invokes the solver.
It /also/ saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler. Much nicer.
It also improves error messages a bit.
All described in Note [Solving a Wanted forall-constraint] in
GHC.Tc.Solver.Solve.
One tiresome point: in the tricky case of `inferConstraintsCoerceBased`
we make a forall-constraint. This we /do/ want to partially solve, so
we can infer a suitable context. (I'd be quite happy to force the user to
write a context, bt I don't want to change behavior.) So we want to generate
an /implication/ constraint in `emitPredSpecConstraints` rather than a
/forall-constraint/ as we were doing before. Discussed in (WFA3) of
the above Note.
Incidental refactoring
* `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for
the DerivEnv that the caller had just consulted. Nicer to pass it as an
argument I think, so I have done that. No change in behaviour.
- - - - -
6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Remove duplicated code in Ast.hs for evTermFreeVars
This is just a tidy up.
- - - - -
1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Small tc-tracing changes only
- - - - -
0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00
Respect `-fdiagnostics-as-json` for core diagnostics (see #24113)
- - - - -
cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00
docs: add since pragma to Data.List.NonEmpty.mapMaybe
- - - - -
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
On i386-linux:
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
bf03bbaa by Simon Hengel at 2025-08-01T04:39:05-04:00
Don't use MCDiagnostic for `ghcExit`
This changes the error message of `ghcExit` from
```
<no location info>: error:
Compilation had errors
```
to
```
Compilation had errors
```
- - - - -
a889ec75 by Simon Hengel at 2025-08-01T04:39:05-04:00
Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113)
- - - - -
81577fe7 by Ben Gamari at 2025-08-02T04:29:39-04:00
configure: Allow override of CrossCompiling
As noted in #26236, the current inference logic is a bit simplistic. In
particular, there are many cases (e.g. building for a new libc) where
the target and host triples may differ yet we are still able to run the
produced artifacts as native code.
Closes #26236.
- - - - -
01136779 by Andreas Klebinger at 2025-08-02T04:30:20-04:00
rts: Support COFF BigObj files in archives.
- - - - -
0813650d by Apoorv Ingle at 2025-08-03T19:13:15-05:00
- Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed.
- Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx`
- `tcXExpr` is less hacky now
- do not look through HsExpansion applications
- kill OrigPat and remove HsThingRn From VAExpansion
- look through XExpr ExpandedThingRn while inferring type of head
- always set in generated code after stepping inside a ExpandedThingRn
- fixing record update error messages
- remove special case of tcbody from tcLambdaMatches
- wrap last stmt expansion in a HsPar so that the error messages are prettier
- remove special case of dsExpr for ExpandedThingTc
- make EExpand (HsExpr GhcRn) instead of EExpand HsThingRn
- fixing error messages for rebindable
- - - - -
e20bd319 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix the case where head of the application chain is an expanded expression and the argument is a type application c.f. T19167.hs
- - - - -
0ea9ea9e by Apoorv Ingle at 2025-08-03T19:13:15-05:00
move setQLInstLevel inside tcInstFun
- - - - -
1b66023e by Apoorv Ingle at 2025-08-03T19:13:15-05:00
ignore ds warnings originating from gen locations
- - - - -
21efb731 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
filter expr stmts error msgs
- - - - -
60fa9a93 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
exception for AppDo while making error ctxt
- - - - -
aa94adc9 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
moving around things for locations and error ctxts
- - - - -
a47a85da by Apoorv Ingle at 2025-08-03T19:13:15-05:00
popErrCtxt doesn't push contexts and popErrCtxts in the first argument to bind and >> in do expansion statements
- - - - -
fbb55000 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
f1475379 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
f0bff7b4 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
check the right origin for record selector incomplete warnings
- - - - -
2798c3a3 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
kill VAExpansion
- - - - -
b9ed648a by Apoorv Ingle at 2025-08-03T19:13:15-05:00
pass CtOrigin to tcApp for instantiateSigma
- - - - -
28a109c4 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
do not suppress pprArising
- - - - -
8067ecd1 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
kill VACall
- - - - -
be84a464 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
kill AppCtxt
- - - - -
567d99ca by Apoorv Ingle at 2025-08-03T19:13:15-05:00
remove addHeadCtxt
- - - - -
fff80dad by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix pprArising for MonadFailErrors
- - - - -
1a52df2a by Apoorv Ingle at 2025-08-03T19:13:15-05:00
rename ctxt to sloc
- - - - -
2b1f6d5a by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix RepPolyDoBind error message herald
- - - - -
ef2e5c64 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
SrcCodeCtxt
more changes
- - - - -
2198ff22 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
make tcl_in_gen_code a SrcCodeCtxt and rename DoOrigin to DoStmtOrigin
- - - - -
77528226 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
make error messages for records saner
- - - - -
1a29b178 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
accept the right test output
- - - - -
f9f5d16d by Apoorv Ingle at 2025-08-03T19:13:15-05:00
make make sure to set inGenerated code for RecordUpdate checks
- - - - -
ac7f4e47 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
rename HsThingRn to SrcCodeOrigin
- - - - -
5e88dc4b by Apoorv Ingle at 2025-08-03T19:13:15-05:00
minor lclenv getter setter changes
- - - - -
636ac88d by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix exprCtOrigin for HsProjection case. It was assigned to be SectionOrigin, but it should be GetFieldOrigin
- - - - -
b461eade by Apoorv Ingle at 2025-08-03T19:13:15-05:00
undo test changes
- - - - -
ddf645e4 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix unused do binding warning error location
- - - - -
b059017c by Apoorv Ingle at 2025-08-03T19:13:15-05:00
FRRRecordUpdate message change
- - - - -
591a4de7 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
- kill tcl_in_gen_code
- It is subsumed by `ErrCtxtStack` which keep tracks of `ErrCtxt` and code ctxt
- - - - -
62f356cb by Apoorv Ingle at 2025-08-03T19:13:15-05:00
kill ExpectedFunTyOrig
- - - - -
0dde07c3 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
update argument position number of CtOrigin
- - - - -
c5ba18ef by Apoorv Ingle at 2025-08-03T19:13:15-05:00
fix suggestion in error message for record field and modify herald everywhere
- - - - -
0cb13b2e by Apoorv Ingle at 2025-08-03T19:13:15-05:00
new CtOrigin ExpectedTySyntax
- - - - -
3b3b8191 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
more changes to printing origin
- - - - -
caa263c2 by Apoorv Ingle at 2025-08-03T19:13:15-05:00
rep poly test case error messages
- - - - -
78abcf2e by Apoorv Ingle at 2025-08-03T19:13:15-05:00
OrigPat pprCtO says a do statement to mimic DoPatOrigin
- - - - -
569ae5a5 by Apoorv Ingle at 2025-08-03T20:40:26-05:00
remove location from OrigPat
- - - - -
197 changed files:
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- + compiler/GHC/Tc/Gen/App.hs-boot
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Logger.hs
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/win32-dlls.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Generics.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/PrimOps.cmm
- rts/RaiseAsync.c
- rts/RtsFlags.c
- rts/STM.c
- rts/Timer.c
- rts/include/rts/Flags.h
- rts/linker/LoadArchive.c
- testsuite/tests/corelint/T21115b.stderr
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/deriving/should_compile/T20815.hs
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/haddock/haddock_testsuite/Makefile
- + testsuite/tests/haddock/haddock_testsuite/T26114.hs
- + testsuite/tests/haddock/haddock_testsuite/T26114.stdout
- testsuite/tests/haddock/haddock_testsuite/all.T
- testsuite/tests/hiefile/should_run/HieQueries.stdout
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- + testsuite/tests/lib/stm/T26028.hs
- + testsuite/tests/lib/stm/T26028.stdout
- + testsuite/tests/lib/stm/all.T
- testsuite/tests/numeric/should_run/T9810.stdout
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail10.stderr
- testsuite/tests/parser/should_fail/RecordDotSyntaxFail11.stderr
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/quantified-constraints/T15290a.stderr
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/rep-poly/RepPolyDoBind.stderr
- testsuite/tests/rep-poly/RepPolyDoBody1.stderr
- testsuite/tests/rep-poly/RepPolyDoBody2.stderr
- testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/flags/all.T
- + testsuite/tests/simplCore/should_compile/T26115.hs
- + testsuite/tests/simplCore/should_compile/T26115.stderr
- + testsuite/tests/simplCore/should_compile/T26116.hs
- + testsuite/tests/simplCore/should_compile/T26116.stderr
- + testsuite/tests/simplCore/should_compile/T26117.hs
- + testsuite/tests/simplCore/should_compile/T26117.stderr
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/splice-imports/T26087.stderr
- + testsuite/tests/splice-imports/T26087A.hs
- + testsuite/tests/splice-imports/T26087B.hs
- + testsuite/tests/splice-imports/T26088.stderr
- + testsuite/tests/splice-imports/T26088A.hs
- + testsuite/tests/splice-imports/T26088B.hs
- testsuite/tests/splice-imports/all.T
- testsuite/tests/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T14605.hs
- testsuite/tests/typecheck/should_fail/T14605.stderr
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T18640a.stderr
- testsuite/tests/typecheck/should_fail/T18640b.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T21530b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3323.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail102.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/typecheck/should_fail/tcfail174.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba88d72c5a6ae14c4a4efaa0cffd2a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba88d72c5a6ae14c4a4efaa0cffd2a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-apporv-Oct24] OrigPat pprCtO says a do statement to mimic DoPatOrigin
by Apoorv Ingle (@ani) 04 Aug '25
by Apoorv Ingle (@ani) 04 Aug '25
04 Aug '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
ba88d72c by Apoorv Ingle at 2025-08-03T19:11:55-05:00
OrigPat pprCtO says a do statement to mimic DoPatOrigin
- - - - -
2 changed files:
- compiler/GHC/Tc/Types/Origin.hs
- − compiler/hie.yaml
Changes:
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -1096,7 +1096,7 @@ pprCtO (ExpansionOrigin (OrigExpr (ExplicitList{}))) = text "an overloaded list"
pprCtO (ExpansionOrigin (OrigExpr (HsIf{}))) = text "an if-then-else expression"
pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e
pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement"
-pprCtO (ExpansionOrigin (OrigPat{})) = text "a pattern"
+pprCtO (ExpansionOrigin (OrigPat{})) = text "a do statement"
pprCtO (ExpectedTySyntax o _) = pprCtO o
pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator"
pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern"
=====================================
compiler/hie.yaml deleted
=====================================
@@ -1,8 +0,0 @@
-# This is a IDE configuration file which tells IDEs such as `ghcide` how
-# to set up a GHC API session for this project.
-#
-# To use it in windows systems replace the config with
-# cradle: {bios: {program: "./hadrian/hie-bios.bat"}}
-#
-# The format is documented here - https://github.com/mpickering/hie-bios
-cradle: {bios: {program: "./hadrian/hie-bios"}}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba88d72c5a6ae14c4a4efaa0cffd2a5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba88d72c5a6ae14c4a4efaa0cffd2a5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Teo Camarasu (@teo) 03 Aug '25
by Teo Camarasu (@teo) 03 Aug '25
03 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
54687aa5 by Teo Camarasu at 2025-08-03T01:27:17+01:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
c7b625a9 by Teo Camarasu at 2025-08-03T01:27:18+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
7 changed files:
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- testsuite/tests/interface-stability/template-haskell-exports.stdout
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
=====================================
@@ -555,20 +555,6 @@ pragInlD name inline rm phases
pragOpaqueD :: Quote m => Name -> m Dec
pragOpaqueD name = pure $ PragmaD $ OpaqueP name
-{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
-pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
-pragSpecD n ty phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
-
-{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
-pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
-pragSpecInlD n ty inline phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
-
pragSpecED :: Quote m
=> Maybe [m (TyVarBndr ())] -> [m RuleBndr]
-> m Exp
@@ -868,22 +854,6 @@ implicitParamT n t
t' <- t
pure $ ImplicitParamT n t'
-{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
-classP :: Quote m => Name -> [m Type] -> m Pred
-classP cla tys
- = do
- tysl <- sequenceA tys
- pure (foldl AppT (ConT cla) tysl)
-
-{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
-equalP :: Quote m => m Type -> m Type -> m Pred
-equalP tleft tright
- = do
- tleft1 <- tleft
- tright1 <- tright
- eqT <- equalityT
- pure (foldl AppT eqT [tleft1, tright1])
-
promotedT :: Quote m => Name -> m Type
promotedT = pure . PromotedT
@@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
sourceLazy = pure SourceLazy
sourceStrict = pure SourceStrict
-{-# DEPRECATED isStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
-{-# DEPRECATED notStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
-{-# DEPRECATED unpacked
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
-isStrict, notStrict, unpacked :: Quote m => m Strict
-isStrict = bang noSourceUnpackedness sourceStrict
-notStrict = bang noSourceUnpackedness noSourceStrictness
-unpacked = bang sourceUnpack sourceStrict
-
bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
bang u s = do u' <- u
s' <- s
@@ -931,16 +887,6 @@ bangType = liftA2 (,)
varBangType :: Quote m => Name -> m BangType -> m VarBangType
varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
-{-# DEPRECATED strictType
- "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
-strictType :: Quote m => m Strict -> m Type -> m StrictType
-strictType = bangType
-
-{-# DEPRECATED varStrictType
- "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
-varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
-varStrictType = varBangType
-
-- * Type Literals
-- MonadFail here complicates things (a lot) because it would mean we would
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -24,40 +24,22 @@
module GHC.Internal.TH.Lift
( Lift(..)
- -- * Generic Lift implementations
- , dataToQa
- , dataToCodeQ
- , dataToExpQ
- , liftDataTyped
- , liftData
- , dataToPatQ
-- * Wired-in names
, liftString
- , trueName
- , falseName
- , nothingName
- , justName
- , leftName
- , rightName
- , nonemptyName
)
where
import GHC.Internal.TH.Syntax
import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
-import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
import GHC.Internal.Data.Either
-import GHC.Internal.Type.Reflection
import GHC.Internal.Data.Bool
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
-import GHC.Internal.Data.Foldable
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
import GHC.Internal.Integer
import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Int
-import GHC.Internal.Data.Data hiding (Fixity)
import GHC.Internal.Natural
import GHC.Internal.ForeignPtr
@@ -294,20 +276,6 @@ deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f)
deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
=> Lift (# a | b | c | d | e | f | g #)
-trueName, falseName :: Name
-trueName = 'True
-falseName = 'False
-
-nothingName, justName :: Name
-nothingName = 'Nothing
-justName = 'Just
-
-leftName, rightName :: Name
-leftName = 'Left
-rightName = 'Right
-
-nonemptyName :: Name
-nonemptyName = '(:|)
-----------------------------------------------------
--
@@ -443,157 +411,3 @@ deriving instance Lift Info
deriving instance Lift AnnLookup
-- | @since template-haskell-2.22.1.0
deriving instance Lift Extension
-
------------------------------------------------------
---
--- Generic Lift implementations
---
------------------------------------------------------
-
--- | 'dataToQa' is an internal utility function for constructing generic
--- conversion functions from types with 'Data' instances to various
--- quasi-quoting representations. See the source of 'dataToExpQ' and
--- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
--- and @appQ@ are overloadable to account for different syntax for
--- expressions and patterns; @antiQ@ allows you to override type-specific
--- cases, a common usage is just @const Nothing@, which results in
--- no overloading.
-dataToQa :: forall m a k q. (Quote m, Data a)
- => (Name -> k)
- -> (Lit -> m q)
- -> (k -> [m q] -> m q)
- -> (forall b . Data b => b -> Maybe (m q))
- -> a
- -> m q
-dataToQa mkCon mkLit appCon antiQ t =
- case antiQ t of
- Nothing ->
- case constrRep constr of
- AlgConstr _ ->
- appCon (mkCon funOrConName) conArgs
- where
- funOrConName :: Name
- funOrConName =
- case showConstr constr of
- "(:)" -> Name (mkOccName ":")
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@"[]" -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@('(':_) -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Tuple"))
-
- -- Tricky case: see Note [Data for non-algebraic types]
- fun@(x:_) | startsVarSym x || startsVarId x
- -> mkNameG_v tyconPkg tyconMod fun
- con -> mkNameG_d tyconPkg tyconMod con
-
- where
- tycon :: TyCon
- tycon = (typeRepTyCon . typeOf) t
-
- tyconPkg, tyconMod :: String
- tyconPkg = tyConPackage tycon
- tyconMod = tyConModule tycon
-
- conArgs :: [m q]
- conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
- IntConstr n ->
- mkLit $ IntegerL n
- FloatConstr n ->
- mkLit $ RationalL n
- CharConstr c ->
- mkLit $ CharL c
- where
- constr :: Constr
- constr = toConstr t
-
- Just y -> y
-
-
-{- Note [Data for non-algebraic types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Class Data was originally intended for algebraic data types. But
-it is possible to use it for abstract types too. For example, in
-package `text` we find
-
- instance Data Text where
- ...
- toConstr _ = packConstr
-
- packConstr :: Constr
- packConstr = mkConstr textDataType "pack" [] Prefix
-
-Here `packConstr` isn't a real data constructor, it's an ordinary
-function. Two complications
-
-* In such a case, we must take care to build the Name using
- mkNameG_v (for values), not mkNameG_d (for data constructors).
- See #10796.
-
-* The pseudo-constructor is named only by its string, here "pack".
- But 'dataToQa' needs the TyCon of its defining module, and has
- to assume it's defined in the same module as the TyCon itself.
- But nothing enforces that; #12596 shows what goes wrong if
- "pack" is defined in a different module than the data type "Text".
- -}
-
--- | A typed variant of 'dataToExpQ'.
-dataToCodeQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (Code m b))
- -> a -> Code m a
-dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
-
--- | 'dataToExpQ' converts a value to a 'Exp' representation of the
--- same value, in the SYB style. It is generalized to take a function
--- override type-specific cases; see 'liftData' for a more commonly
--- used variant.
-dataToExpQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Exp))
- -> a
- -> m Exp
-dataToExpQ = dataToQa varOrConE litE (foldl appE)
- where
- -- Make sure that VarE is used if the Constr value relies on a
- -- function underneath the surface (instead of a constructor).
- -- See #10796.
- varOrConE s =
- case nameSpace s of
- Just VarName -> return (VarE s)
- Just (FldName {}) -> return (VarE s)
- Just DataName -> return (ConE s)
- _ -> error $ "Can't construct an expression from name "
- ++ showName s
- appE x y = do { a <- x; b <- y; return (AppE a b)}
- litE c = return (LitE c)
-
--- | A typed variant of 'liftData'.
-liftDataTyped :: (Quote m, Data a) => a -> Code m a
-liftDataTyped = dataToCodeQ (const Nothing)
-
--- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
--- works for any type with a 'Data' instance.
-liftData :: (Quote m, Data a) => a -> m Exp
-liftData = dataToExpQ (const Nothing)
-
--- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
--- value, in the SYB style. It takes a function to handle type-specific cases,
--- alternatively, pass @const Nothing@ to get default behavior.
-dataToPatQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Pat))
- -> a
- -> m Pat
-dataToPatQ = dataToQa id litP conP
- where litP l = return (LitP l)
- conP n ps =
- case nameSpace n of
- Just DataName -> do
- ps' <- sequence ps
- return (ConP n [] ps')
- _ -> error $ "Can't construct a pattern from name "
- ++ showName n
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -22,9 +22,6 @@ module GHC.Internal.TH.Syntax
-- * Language extensions
, module GHC.Internal.LanguageExtensions
, ForeignSrcLang(..)
- -- * Notes
- -- ** Unresolved Infix
- -- $infix
) where
#ifdef BOOTSTRAP_TH
@@ -847,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
addTopDecls :: [Dec] -> Q ()
addTopDecls ds = Q (qAddTopDecls ds)
--- |
-addForeignFile :: ForeignSrcLang -> String -> Q ()
-addForeignFile = addForeignSource
-{-# DEPRECATED addForeignFile
- "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
- #-} -- deprecated in 8.6
-- | Emit a foreign file which will be compiled and linked to the object for
-- the current module. Currently only languages that can be compiled with
@@ -1614,73 +1605,6 @@ maxPrecedence = (9::Int)
defaultFixity :: Fixity
defaultFixity = Fixity maxPrecedence InfixL
-
-{-
-Note [Unresolved infix]
-~~~~~~~~~~~~~~~~~~~~~~~
--}
-{- $infix #infix#
-
-When implementing antiquotation for quasiquoters, one often wants
-to parse strings into expressions:
-
-> parse :: String -> Maybe Exp
-
-But how should we parse @a + b * c@? If we don't know the fixities of
-@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
-+ b) * c@.
-
-In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
-which stand for \"unresolved infix expression / pattern / type / promoted
-constructor\", respectively. When the compiler is given a splice containing a
-tree of @UInfixE@ applications such as
-
-> UInfixE
-> (UInfixE e1 op1 e2)
-> op2
-> (UInfixE e3 op3 e4)
-
-it will look up and the fixities of the relevant operators and
-reassociate the tree as necessary.
-
- * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
- which are of use for parsing expressions like
-
- > (a + b * c) + d * e
-
- * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
- reassociated.
-
- * The 'UInfixE' constructor doesn't support sections. Sections
- such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
- sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
- outer-most section, and use 'UInfixE' constructors for all
- other operators:
-
- > InfixE
- > Just (UInfixE ...a + b * c...)
- > op
- > Nothing
-
- Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
- into 'Exp's differently:
-
- > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
- > -- will result in a fixity error if (+) is left-infix
- > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
- > -- no fixity errors
-
- * Quoted expressions such as
-
- > [| a * b + c |] :: Q Exp
- > [p| a : b : c |] :: Q Pat
- > [t| T + T |] :: Q Type
-
- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
- 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
-
--}
-
-----------------------------------------------------
--
-- The main syntax data types
=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing
conP :: Quote m => Name -> [m Pat] -> m Pat
conP n xs = Internal.conP n [] xs
+
+
+--------------------------------------------------------------------------------
+-- * Constraint predicates (deprecated)
+
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Quote m => Name -> [m Type] -> m Pred
+classP cla tys
+ = do
+ tysl <- sequenceA tys
+ pure (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: Quote m => m Type -> m Type -> m Pred
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ pure (foldl AppT eqT [tleft1, tright1])
+
+--------------------------------------------------------------------------------
+-- * Strictness queries (deprecated)
+{-# DEPRECATED isStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
+{-# DEPRECATED notStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
+{-# DEPRECATED unpacked
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
+isStrict, notStrict, unpacked :: Quote m => m Strict
+isStrict = bang noSourceUnpackedness sourceStrict
+notStrict = bang noSourceUnpackedness noSourceStrictness
+unpacked = bang sourceUnpack sourceStrict
+
+{-# DEPRECATED strictType
+ "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
+strictType :: Quote m => m Strict -> m Type -> m StrictType
+strictType = bangType
+
+{-# DEPRECATED varStrictType
+ "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
+varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
+varStrictType = varBangType
+
+--------------------------------------------------------------------------------
+-- * Specialisation pragmas (deprecated)
+
+{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
+pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
+pragSpecD n ty phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
+
+{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
+pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
+pragSpecInlD n ty inline phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
=====================================
libraries/template-haskell/Language/Haskell/TH/Quote.hs
=====================================
@@ -17,12 +17,12 @@ module Language.Haskell.TH.Quote
( QuasiQuoter(..)
, quoteFile
-- * For backwards compatibility
- ,dataToQa, dataToExpQ, dataToPatQ
+ , dataToQa, dataToExpQ, dataToPatQ
) where
import GHC.Boot.TH.Syntax
import GHC.Boot.TH.Quote
-import GHC.Boot.TH.Lift
+import Language.Haskell.TH.Syntax (dataToQa, dataToExpQ, dataToPatQ)
-- | 'quoteFile' takes a 'QuasiQuoter' and lifts it into one that read
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,8 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,19 +192,267 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
+ -- * Notes
+ -- ** Unresolved Infix
+ -- $infix
)
where
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
import System.FilePath
+import Data.Data hiding (Fixity(..))
+import Data.List.NonEmpty (NonEmpty(..))
+import GHC.Lexeme ( startsVarSym, startsVarId )
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
-- and exports additionally functions that depend on filepath.
+-- |
+addForeignFile :: ForeignSrcLang -> String -> Q ()
+addForeignFile = addForeignSource
+{-# DEPRECATED addForeignFile
+ "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
+ #-} -- deprecated in 8.6
+
-- | The input is a filepath, which if relative is offset by the package root.
makeRelativeToProject :: FilePath -> Q FilePath
makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
+
+trueName, falseName :: Name
+trueName = 'True
+falseName = 'False
+
+nothingName, justName :: Name
+nothingName = 'Nothing
+justName = 'Just
+
+leftName, rightName :: Name
+leftName = 'Left
+rightName = 'Right
+
+nonemptyName :: Name
+nonemptyName = '(:|)
+
+-----------------------------------------------------
+--
+-- Generic Lift implementations
+--
+-----------------------------------------------------
+
+-- | 'dataToQa' is an internal utility function for constructing generic
+-- conversion functions from types with 'Data' instances to various
+-- quasi-quoting representations. See the source of 'dataToExpQ' and
+-- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
+-- and @appQ@ are overloadable to account for different syntax for
+-- expressions and patterns; @antiQ@ allows you to override type-specific
+-- cases, a common usage is just @const Nothing@, which results in
+-- no overloading.
+dataToQa :: forall m a k q. (Quote m, Data a)
+ => (Name -> k)
+ -> (Lit -> m q)
+ -> (k -> [m q] -> m q)
+ -> (forall b . Data b => b -> Maybe (m q))
+ -> a
+ -> m q
+dataToQa mkCon mkLit appCon antiQ t =
+ case antiQ t of
+ Nothing ->
+ case constrRep constr of
+ AlgConstr _ ->
+ appCon (mkCon funOrConName) conArgs
+ where
+ funOrConName :: Name
+ funOrConName =
+ case showConstr constr of
+ "(:)" -> Name (mkOccName ":")
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@"[]" -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@('(':_) -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Tuple"))
+
+ -- Tricky case: see Note [Data for non-algebraic types]
+ fun@(x:_) | startsVarSym x || startsVarId x
+ -> mkNameG_v tyconPkg tyconMod fun
+ con -> mkNameG_d tyconPkg tyconMod con
+
+ where
+ tycon :: TyCon
+ tycon = (typeRepTyCon . typeOf) t
+
+ tyconPkg, tyconMod :: String
+ tyconPkg = tyConPackage tycon
+ tyconMod = tyConModule tycon
+
+ conArgs :: [m q]
+ conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
+ IntConstr n ->
+ mkLit $ IntegerL n
+ FloatConstr n ->
+ mkLit $ RationalL n
+ CharConstr c ->
+ mkLit $ CharL c
+ where
+ constr :: Constr
+ constr = toConstr t
+
+ Just y -> y
+
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types. But
+it is possible to use it for abstract types too. For example, in
+package `text` we find
+
+ instance Data Text where
+ ...
+ toConstr _ = packConstr
+
+ packConstr :: Constr
+ packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordinary
+function. Two complications
+
+* In such a case, we must take care to build the Name using
+ mkNameG_v (for values), not mkNameG_d (for data constructors).
+ See #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+ But 'dataToQa' needs the TyCon of its defining module, and has
+ to assume it's defined in the same module as the TyCon itself.
+ But nothing enforces that; #12596 shows what goes wrong if
+ "pack" is defined in a different module than the data type "Text".
+ -}
+
+-- | A typed variant of 'dataToExpQ'.
+dataToCodeQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (Code m b))
+ -> a -> Code m a
+dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
+
+-- | 'dataToExpQ' converts a value to a 'Exp' representation of the
+-- same value, in the SYB style. It is generalized to take a function
+-- override type-specific cases; see 'liftData' for a more commonly
+-- used variant.
+dataToExpQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Exp))
+ -> a
+ -> m Exp
+dataToExpQ = dataToQa varOrConE litE (foldl appE)
+ where
+ -- Make sure that VarE is used if the Constr value relies on a
+ -- function underneath the surface (instead of a constructor).
+ -- See #10796.
+ varOrConE s =
+ case nameSpace s of
+ Just VarName -> return (VarE s)
+ Just (FldName {}) -> return (VarE s)
+ Just DataName -> return (ConE s)
+ _ -> error $ "Can't construct an expression from name "
+ ++ showName s
+ appE x y = do { a <- x; b <- y; return (AppE a b)}
+ litE c = return (LitE c)
+
+-- | A typed variant of 'liftData'.
+liftDataTyped :: (Quote m, Data a) => a -> Code m a
+liftDataTyped = dataToCodeQ (const Nothing)
+
+-- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
+-- works for any type with a 'Data' instance.
+liftData :: (Quote m, Data a) => a -> m Exp
+liftData = dataToExpQ (const Nothing)
+
+-- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
+-- value, in the SYB style. It takes a function to handle type-specific cases,
+-- alternatively, pass @const Nothing@ to get default behavior.
+dataToPatQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Pat))
+ -> a
+ -> m Pat
+dataToPatQ = dataToQa id litP conP
+ where litP l = return (LitP l)
+ conP n ps =
+ case nameSpace n of
+ Just DataName -> do
+ ps' <- sequence ps
+ return (ConP n [] ps')
+ _ -> error $ "Can't construct a pattern from name "
+ ++ showName n
+
+{-
+Note [Unresolved infix]
+~~~~~~~~~~~~~~~~~~~~~~~
+-}
+{- $infix #infix#
+
+When implementing antiquotation for quasiquoters, one often wants
+to parse strings into expressions:
+
+> parse :: String -> Maybe Exp
+
+But how should we parse @a + b * c@? If we don't know the fixities of
+@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
++ b) * c@.
+
+In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
+which stand for \"unresolved infix expression / pattern / type / promoted
+constructor\", respectively. When the compiler is given a splice containing a
+tree of @UInfixE@ applications such as
+
+> UInfixE
+> (UInfixE e1 op1 e2)
+> op2
+> (UInfixE e3 op3 e4)
+
+it will look up and the fixities of the relevant operators and
+reassociate the tree as necessary.
+
+ * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
+ which are of use for parsing expressions like
+
+ > (a + b * c) + d * e
+
+ * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
+ reassociated.
+
+ * The 'UInfixE' constructor doesn't support sections. Sections
+ such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
+ sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
+ outer-most section, and use 'UInfixE' constructors for all
+ other operators:
+
+ > InfixE
+ > Just (UInfixE ...a + b * c...)
+ > op
+ > Nothing
+
+ Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
+ into 'Exp's differently:
+
+ > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
+ > -- will result in a fixity error if (+) is left-infix
+ > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
+ > -- no fixity errors
+
+ * Quoted expressions such as
+
+ > [| a * b + c |] :: Q Exp
+ > [p| a : b : c |] :: Q Pat
+ > [t| T + T |] :: Q Type
+
+ will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
+ 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
+
+-}
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1373,7 +1373,7 @@ module Language.Haskell.TH.Quote where
quoteFile :: QuasiQuoter -> QuasiQuoter
module Language.Haskell.TH.Syntax where
- -- Safety: Safe
+ -- Safety: Trustworthy
type AnnLookup :: *
data AnnLookup = AnnLookupModule Module | AnnLookupName Name
type AnnTarget :: *
@@ -1720,8 +1720,8 @@ module Language.Haskell.TH.Syntax where
qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m ()
qAddModFinalizer :: Q () -> m ()
qAddCorePlugin :: GHC.Internal.Base.String -> m ()
- qGetQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => m (GHC.Internal.Maybe.Maybe a)
- qPutQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> m ()
+ qGetQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => m (GHC.Internal.Maybe.Maybe a)
+ qPutQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> m ()
qIsExtEnabled :: Extension -> m GHC.Internal.Types.Bool
qExtsEnabled :: m [Extension]
qPutDoc :: DocLoc -> GHC.Internal.Base.String -> m ()
@@ -1802,7 +1802,7 @@ module Language.Haskell.TH.Syntax where
falseName :: Name
getDoc :: DocLoc -> Q (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
getPackageRoot :: Q GHC.Internal.IO.FilePath
- getQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => Q (GHC.Internal.Maybe.Maybe a)
+ getQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => Q (GHC.Internal.Maybe.Maybe a)
get_cons_names :: Con -> [Name]
hoistCode :: forall (m :: * -> *) (n :: * -> *) (r :: GHC.Internal.Types.RuntimeRep) (a :: TYPE r). GHC.Internal.Base.Monad m => (forall x. m x -> n x) -> Code m a -> Code n a
isExtEnabled :: Extension -> Q GHC.Internal.Types.Bool
@@ -1849,7 +1849,7 @@ module Language.Haskell.TH.Syntax where
oneName :: Name
pkgString :: PkgName -> GHC.Internal.Base.String
putDoc :: DocLoc -> GHC.Internal.Base.String -> Q ()
- putQ :: forall a. ghc-internal-9.1300.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> Q ()
+ putQ :: forall a. ghc-internal-9.1500.0:GHC.Internal.Data.Typeable.Internal.Typeable a => a -> Q ()
recover :: forall a. Q a -> Q a -> Q a
reify :: Name -> Q Info
reifyAnnotations :: forall a. GHC.Internal.Data.Data.Data a => AnnLookup -> Q [a]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a694bd768d2afc123e92dd464e973…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a694bd768d2afc123e92dd464e973…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T21730-import] More test output changes
by Brandon Chinn (@brandonchinn178) 02 Aug '25
by Brandon Chinn (@brandonchinn178) 02 Aug '25
02 Aug '25
Brandon Chinn pushed to branch wip/T21730-import at Glasgow Haskell Compiler / GHC
Commits:
ebf6de3e by Brandon Chinn at 2025-08-02T15:57:23-07:00
More test output changes
- - - - -
2 changed files:
- testsuite/tests/module/mod150.stderr
- testsuite/tests/parser/should_compile/T7476/T7476.stdout
Changes:
=====================================
testsuite/tests/module/mod150.stderr
=====================================
@@ -1,7 +1,7 @@
mod150.hs:2:20: error: [GHC-69158]
Conflicting exports for ‘id’:
+ ‘module M’ exports ‘M.id’ defined at mod150.hs:2:42
‘module Prelude’ exports ‘Prelude.id’
imported from ‘Prelude’
(and originally defined in ‘GHC.Internal.Base’)
- ‘module M’ exports ‘M.id’ defined at mod150.hs:2:42
=====================================
testsuite/tests/parser/should_compile/T7476/T7476.stdout
=====================================
@@ -1 +1 @@
-import Control.Applicative ( (<**>) )
+import Control.Applicative ( Applicative(pure), (<**>) )
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebf6de3e9023c90bbb6960c9d2b9170…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebf6de3e9023c90bbb6960c9d2b9170…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Teo Camarasu (@teo) 02 Aug '25
by Teo Camarasu (@teo) 02 Aug '25
02 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
20e1d987 by Teo Camarasu at 2025-08-02T23:30:26+01:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
2a694bd7 by Teo Camarasu at 2025-08-02T23:30:27+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
6 changed files:
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
=====================================
@@ -555,20 +555,6 @@ pragInlD name inline rm phases
pragOpaqueD :: Quote m => Name -> m Dec
pragOpaqueD name = pure $ PragmaD $ OpaqueP name
-{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
-pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
-pragSpecD n ty phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
-
-{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
-pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
-pragSpecInlD n ty inline phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
-
pragSpecED :: Quote m
=> Maybe [m (TyVarBndr ())] -> [m RuleBndr]
-> m Exp
@@ -868,22 +854,6 @@ implicitParamT n t
t' <- t
pure $ ImplicitParamT n t'
-{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
-classP :: Quote m => Name -> [m Type] -> m Pred
-classP cla tys
- = do
- tysl <- sequenceA tys
- pure (foldl AppT (ConT cla) tysl)
-
-{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
-equalP :: Quote m => m Type -> m Type -> m Pred
-equalP tleft tright
- = do
- tleft1 <- tleft
- tright1 <- tright
- eqT <- equalityT
- pure (foldl AppT eqT [tleft1, tright1])
-
promotedT :: Quote m => Name -> m Type
promotedT = pure . PromotedT
@@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
sourceLazy = pure SourceLazy
sourceStrict = pure SourceStrict
-{-# DEPRECATED isStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
-{-# DEPRECATED notStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
-{-# DEPRECATED unpacked
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
-isStrict, notStrict, unpacked :: Quote m => m Strict
-isStrict = bang noSourceUnpackedness sourceStrict
-notStrict = bang noSourceUnpackedness noSourceStrictness
-unpacked = bang sourceUnpack sourceStrict
-
bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
bang u s = do u' <- u
s' <- s
@@ -931,16 +887,6 @@ bangType = liftA2 (,)
varBangType :: Quote m => Name -> m BangType -> m VarBangType
varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
-{-# DEPRECATED strictType
- "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
-strictType :: Quote m => m Strict -> m Type -> m StrictType
-strictType = bangType
-
-{-# DEPRECATED varStrictType
- "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
-varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
-varStrictType = varBangType
-
-- * Type Literals
-- MonadFail here complicates things (a lot) because it would mean we would
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -24,40 +24,22 @@
module GHC.Internal.TH.Lift
( Lift(..)
- -- * Generic Lift implementations
- , dataToQa
- , dataToCodeQ
- , dataToExpQ
- , liftDataTyped
- , liftData
- , dataToPatQ
-- * Wired-in names
, liftString
- , trueName
- , falseName
- , nothingName
- , justName
- , leftName
- , rightName
- , nonemptyName
)
where
import GHC.Internal.TH.Syntax
import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
-import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
import GHC.Internal.Data.Either
-import GHC.Internal.Type.Reflection
import GHC.Internal.Data.Bool
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
-import GHC.Internal.Data.Foldable
import GHC.Internal.Data.NonEmpty (NonEmpty(..))
import GHC.Internal.Integer
import GHC.Internal.Real
import GHC.Internal.Word
import GHC.Internal.Int
-import GHC.Internal.Data.Data hiding (Fixity)
import GHC.Internal.Natural
import GHC.Internal.ForeignPtr
@@ -294,20 +276,6 @@ deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f)
deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
=> Lift (# a | b | c | d | e | f | g #)
-trueName, falseName :: Name
-trueName = 'True
-falseName = 'False
-
-nothingName, justName :: Name
-nothingName = 'Nothing
-justName = 'Just
-
-leftName, rightName :: Name
-leftName = 'Left
-rightName = 'Right
-
-nonemptyName :: Name
-nonemptyName = '(:|)
-----------------------------------------------------
--
@@ -443,157 +411,3 @@ deriving instance Lift Info
deriving instance Lift AnnLookup
-- | @since template-haskell-2.22.1.0
deriving instance Lift Extension
-
------------------------------------------------------
---
--- Generic Lift implementations
---
------------------------------------------------------
-
--- | 'dataToQa' is an internal utility function for constructing generic
--- conversion functions from types with 'Data' instances to various
--- quasi-quoting representations. See the source of 'dataToExpQ' and
--- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
--- and @appQ@ are overloadable to account for different syntax for
--- expressions and patterns; @antiQ@ allows you to override type-specific
--- cases, a common usage is just @const Nothing@, which results in
--- no overloading.
-dataToQa :: forall m a k q. (Quote m, Data a)
- => (Name -> k)
- -> (Lit -> m q)
- -> (k -> [m q] -> m q)
- -> (forall b . Data b => b -> Maybe (m q))
- -> a
- -> m q
-dataToQa mkCon mkLit appCon antiQ t =
- case antiQ t of
- Nothing ->
- case constrRep constr of
- AlgConstr _ ->
- appCon (mkCon funOrConName) conArgs
- where
- funOrConName :: Name
- funOrConName =
- case showConstr constr of
- "(:)" -> Name (mkOccName ":")
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@"[]" -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@('(':_) -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Tuple"))
-
- -- Tricky case: see Note [Data for non-algebraic types]
- fun@(x:_) | startsVarSym x || startsVarId x
- -> mkNameG_v tyconPkg tyconMod fun
- con -> mkNameG_d tyconPkg tyconMod con
-
- where
- tycon :: TyCon
- tycon = (typeRepTyCon . typeOf) t
-
- tyconPkg, tyconMod :: String
- tyconPkg = tyConPackage tycon
- tyconMod = tyConModule tycon
-
- conArgs :: [m q]
- conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
- IntConstr n ->
- mkLit $ IntegerL n
- FloatConstr n ->
- mkLit $ RationalL n
- CharConstr c ->
- mkLit $ CharL c
- where
- constr :: Constr
- constr = toConstr t
-
- Just y -> y
-
-
-{- Note [Data for non-algebraic types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Class Data was originally intended for algebraic data types. But
-it is possible to use it for abstract types too. For example, in
-package `text` we find
-
- instance Data Text where
- ...
- toConstr _ = packConstr
-
- packConstr :: Constr
- packConstr = mkConstr textDataType "pack" [] Prefix
-
-Here `packConstr` isn't a real data constructor, it's an ordinary
-function. Two complications
-
-* In such a case, we must take care to build the Name using
- mkNameG_v (for values), not mkNameG_d (for data constructors).
- See #10796.
-
-* The pseudo-constructor is named only by its string, here "pack".
- But 'dataToQa' needs the TyCon of its defining module, and has
- to assume it's defined in the same module as the TyCon itself.
- But nothing enforces that; #12596 shows what goes wrong if
- "pack" is defined in a different module than the data type "Text".
- -}
-
--- | A typed variant of 'dataToExpQ'.
-dataToCodeQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (Code m b))
- -> a -> Code m a
-dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
-
--- | 'dataToExpQ' converts a value to a 'Exp' representation of the
--- same value, in the SYB style. It is generalized to take a function
--- override type-specific cases; see 'liftData' for a more commonly
--- used variant.
-dataToExpQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Exp))
- -> a
- -> m Exp
-dataToExpQ = dataToQa varOrConE litE (foldl appE)
- where
- -- Make sure that VarE is used if the Constr value relies on a
- -- function underneath the surface (instead of a constructor).
- -- See #10796.
- varOrConE s =
- case nameSpace s of
- Just VarName -> return (VarE s)
- Just (FldName {}) -> return (VarE s)
- Just DataName -> return (ConE s)
- _ -> error $ "Can't construct an expression from name "
- ++ showName s
- appE x y = do { a <- x; b <- y; return (AppE a b)}
- litE c = return (LitE c)
-
--- | A typed variant of 'liftData'.
-liftDataTyped :: (Quote m, Data a) => a -> Code m a
-liftDataTyped = dataToCodeQ (const Nothing)
-
--- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
--- works for any type with a 'Data' instance.
-liftData :: (Quote m, Data a) => a -> m Exp
-liftData = dataToExpQ (const Nothing)
-
--- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
--- value, in the SYB style. It takes a function to handle type-specific cases,
--- alternatively, pass @const Nothing@ to get default behavior.
-dataToPatQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Pat))
- -> a
- -> m Pat
-dataToPatQ = dataToQa id litP conP
- where litP l = return (LitP l)
- conP n ps =
- case nameSpace n of
- Just DataName -> do
- ps' <- sequence ps
- return (ConP n [] ps')
- _ -> error $ "Can't construct a pattern from name "
- ++ showName n
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -22,9 +22,6 @@ module GHC.Internal.TH.Syntax
-- * Language extensions
, module GHC.Internal.LanguageExtensions
, ForeignSrcLang(..)
- -- * Notes
- -- ** Unresolved Infix
- -- $infix
) where
#ifdef BOOTSTRAP_TH
@@ -847,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
addTopDecls :: [Dec] -> Q ()
addTopDecls ds = Q (qAddTopDecls ds)
--- |
-addForeignFile :: ForeignSrcLang -> String -> Q ()
-addForeignFile = addForeignSource
-{-# DEPRECATED addForeignFile
- "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
- #-} -- deprecated in 8.6
-- | Emit a foreign file which will be compiled and linked to the object for
-- the current module. Currently only languages that can be compiled with
@@ -1614,73 +1605,6 @@ maxPrecedence = (9::Int)
defaultFixity :: Fixity
defaultFixity = Fixity maxPrecedence InfixL
-
-{-
-Note [Unresolved infix]
-~~~~~~~~~~~~~~~~~~~~~~~
--}
-{- $infix #infix#
-
-When implementing antiquotation for quasiquoters, one often wants
-to parse strings into expressions:
-
-> parse :: String -> Maybe Exp
-
-But how should we parse @a + b * c@? If we don't know the fixities of
-@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
-+ b) * c@.
-
-In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
-which stand for \"unresolved infix expression / pattern / type / promoted
-constructor\", respectively. When the compiler is given a splice containing a
-tree of @UInfixE@ applications such as
-
-> UInfixE
-> (UInfixE e1 op1 e2)
-> op2
-> (UInfixE e3 op3 e4)
-
-it will look up and the fixities of the relevant operators and
-reassociate the tree as necessary.
-
- * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
- which are of use for parsing expressions like
-
- > (a + b * c) + d * e
-
- * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
- reassociated.
-
- * The 'UInfixE' constructor doesn't support sections. Sections
- such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
- sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
- outer-most section, and use 'UInfixE' constructors for all
- other operators:
-
- > InfixE
- > Just (UInfixE ...a + b * c...)
- > op
- > Nothing
-
- Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
- into 'Exp's differently:
-
- > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
- > -- will result in a fixity error if (+) is left-infix
- > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
- > -- no fixity errors
-
- * Quoted expressions such as
-
- > [| a * b + c |] :: Q Exp
- > [p| a : b : c |] :: Q Pat
- > [t| T + T |] :: Q Type
-
- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
- 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
-
--}
-
-----------------------------------------------------
--
-- The main syntax data types
=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing
conP :: Quote m => Name -> [m Pat] -> m Pat
conP n xs = Internal.conP n [] xs
+
+
+--------------------------------------------------------------------------------
+-- * Constraint predicates (deprecated)
+
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Quote m => Name -> [m Type] -> m Pred
+classP cla tys
+ = do
+ tysl <- sequenceA tys
+ pure (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: Quote m => m Type -> m Type -> m Pred
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ pure (foldl AppT eqT [tleft1, tright1])
+
+--------------------------------------------------------------------------------
+-- * Strictness queries (deprecated)
+{-# DEPRECATED isStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
+{-# DEPRECATED notStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
+{-# DEPRECATED unpacked
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
+isStrict, notStrict, unpacked :: Quote m => m Strict
+isStrict = bang noSourceUnpackedness sourceStrict
+notStrict = bang noSourceUnpackedness noSourceStrictness
+unpacked = bang sourceUnpack sourceStrict
+
+{-# DEPRECATED strictType
+ "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
+strictType :: Quote m => m Strict -> m Type -> m StrictType
+strictType = bangType
+
+{-# DEPRECATED varStrictType
+ "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
+varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
+varStrictType = varBangType
+
+--------------------------------------------------------------------------------
+-- * Specialisation pragmas (deprecated)
+
+{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
+pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
+pragSpecD n ty phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
+
+{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
+pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
+pragSpecInlD n ty inline phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
=====================================
libraries/template-haskell/Language/Haskell/TH/Quote.hs
=====================================
@@ -17,12 +17,12 @@ module Language.Haskell.TH.Quote
( QuasiQuoter(..)
, quoteFile
-- * For backwards compatibility
- ,dataToQa, dataToExpQ, dataToPatQ
+ , dataToQa, dataToExpQ, dataToPatQ
) where
import GHC.Boot.TH.Syntax
import GHC.Boot.TH.Quote
-import GHC.Boot.TH.Lift
+import Language.Haskell.TH.Syntax (dataToQa, dataToExpQ, dataToPatQ)
-- | 'quoteFile' takes a 'QuasiQuoter' and lifts it into one that read
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,8 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,19 +192,267 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
+ -- * Notes
+ -- ** Unresolved Infix
+ -- $infix
)
where
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
import System.FilePath
+import Data.Data hiding (Fixity(..))
+import Data.List.NonEmpty (NonEmpty(..))
+import GHC.Lexeme ( startsVarSym, startsVarId )
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
-- and exports additionally functions that depend on filepath.
+-- |
+addForeignFile :: ForeignSrcLang -> String -> Q ()
+addForeignFile = addForeignSource
+{-# DEPRECATED addForeignFile
+ "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
+ #-} -- deprecated in 8.6
+
-- | The input is a filepath, which if relative is offset by the package root.
makeRelativeToProject :: FilePath -> Q FilePath
makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
+
+trueName, falseName :: Name
+trueName = 'True
+falseName = 'False
+
+nothingName, justName :: Name
+nothingName = 'Nothing
+justName = 'Just
+
+leftName, rightName :: Name
+leftName = 'Left
+rightName = 'Right
+
+nonemptyName :: Name
+nonemptyName = '(:|)
+
+-----------------------------------------------------
+--
+-- Generic Lift implementations
+--
+-----------------------------------------------------
+
+-- | 'dataToQa' is an internal utility function for constructing generic
+-- conversion functions from types with 'Data' instances to various
+-- quasi-quoting representations. See the source of 'dataToExpQ' and
+-- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
+-- and @appQ@ are overloadable to account for different syntax for
+-- expressions and patterns; @antiQ@ allows you to override type-specific
+-- cases, a common usage is just @const Nothing@, which results in
+-- no overloading.
+dataToQa :: forall m a k q. (Quote m, Data a)
+ => (Name -> k)
+ -> (Lit -> m q)
+ -> (k -> [m q] -> m q)
+ -> (forall b . Data b => b -> Maybe (m q))
+ -> a
+ -> m q
+dataToQa mkCon mkLit appCon antiQ t =
+ case antiQ t of
+ Nothing ->
+ case constrRep constr of
+ AlgConstr _ ->
+ appCon (mkCon funOrConName) conArgs
+ where
+ funOrConName :: Name
+ funOrConName =
+ case showConstr constr of
+ "(:)" -> Name (mkOccName ":")
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@"[]" -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@('(':_) -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Tuple"))
+
+ -- Tricky case: see Note [Data for non-algebraic types]
+ fun@(x:_) | startsVarSym x || startsVarId x
+ -> mkNameG_v tyconPkg tyconMod fun
+ con -> mkNameG_d tyconPkg tyconMod con
+
+ where
+ tycon :: TyCon
+ tycon = (typeRepTyCon . typeOf) t
+
+ tyconPkg, tyconMod :: String
+ tyconPkg = tyConPackage tycon
+ tyconMod = tyConModule tycon
+
+ conArgs :: [m q]
+ conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
+ IntConstr n ->
+ mkLit $ IntegerL n
+ FloatConstr n ->
+ mkLit $ RationalL n
+ CharConstr c ->
+ mkLit $ CharL c
+ where
+ constr :: Constr
+ constr = toConstr t
+
+ Just y -> y
+
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types. But
+it is possible to use it for abstract types too. For example, in
+package `text` we find
+
+ instance Data Text where
+ ...
+ toConstr _ = packConstr
+
+ packConstr :: Constr
+ packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordinary
+function. Two complications
+
+* In such a case, we must take care to build the Name using
+ mkNameG_v (for values), not mkNameG_d (for data constructors).
+ See #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+ But 'dataToQa' needs the TyCon of its defining module, and has
+ to assume it's defined in the same module as the TyCon itself.
+ But nothing enforces that; #12596 shows what goes wrong if
+ "pack" is defined in a different module than the data type "Text".
+ -}
+
+-- | A typed variant of 'dataToExpQ'.
+dataToCodeQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (Code m b))
+ -> a -> Code m a
+dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
+
+-- | 'dataToExpQ' converts a value to a 'Exp' representation of the
+-- same value, in the SYB style. It is generalized to take a function
+-- override type-specific cases; see 'liftData' for a more commonly
+-- used variant.
+dataToExpQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Exp))
+ -> a
+ -> m Exp
+dataToExpQ = dataToQa varOrConE litE (foldl appE)
+ where
+ -- Make sure that VarE is used if the Constr value relies on a
+ -- function underneath the surface (instead of a constructor).
+ -- See #10796.
+ varOrConE s =
+ case nameSpace s of
+ Just VarName -> return (VarE s)
+ Just (FldName {}) -> return (VarE s)
+ Just DataName -> return (ConE s)
+ _ -> error $ "Can't construct an expression from name "
+ ++ showName s
+ appE x y = do { a <- x; b <- y; return (AppE a b)}
+ litE c = return (LitE c)
+
+-- | A typed variant of 'liftData'.
+liftDataTyped :: (Quote m, Data a) => a -> Code m a
+liftDataTyped = dataToCodeQ (const Nothing)
+
+-- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
+-- works for any type with a 'Data' instance.
+liftData :: (Quote m, Data a) => a -> m Exp
+liftData = dataToExpQ (const Nothing)
+
+-- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
+-- value, in the SYB style. It takes a function to handle type-specific cases,
+-- alternatively, pass @const Nothing@ to get default behavior.
+dataToPatQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Pat))
+ -> a
+ -> m Pat
+dataToPatQ = dataToQa id litP conP
+ where litP l = return (LitP l)
+ conP n ps =
+ case nameSpace n of
+ Just DataName -> do
+ ps' <- sequence ps
+ return (ConP n [] ps')
+ _ -> error $ "Can't construct a pattern from name "
+ ++ showName n
+
+{-
+Note [Unresolved infix]
+~~~~~~~~~~~~~~~~~~~~~~~
+-}
+{- $infix #infix#
+
+When implementing antiquotation for quasiquoters, one often wants
+to parse strings into expressions:
+
+> parse :: String -> Maybe Exp
+
+But how should we parse @a + b * c@? If we don't know the fixities of
+@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
++ b) * c@.
+
+In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
+which stand for \"unresolved infix expression / pattern / type / promoted
+constructor\", respectively. When the compiler is given a splice containing a
+tree of @UInfixE@ applications such as
+
+> UInfixE
+> (UInfixE e1 op1 e2)
+> op2
+> (UInfixE e3 op3 e4)
+
+it will look up and the fixities of the relevant operators and
+reassociate the tree as necessary.
+
+ * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
+ which are of use for parsing expressions like
+
+ > (a + b * c) + d * e
+
+ * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
+ reassociated.
+
+ * The 'UInfixE' constructor doesn't support sections. Sections
+ such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
+ sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
+ outer-most section, and use 'UInfixE' constructors for all
+ other operators:
+
+ > InfixE
+ > Just (UInfixE ...a + b * c...)
+ > op
+ > Nothing
+
+ Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
+ into 'Exp's differently:
+
+ > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
+ > -- will result in a fixity error if (+) is left-infix
+ > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
+ > -- no fixity errors
+
+ * Quoted expressions such as
+
+ > [| a * b + c |] :: Q Exp
+ > [p| a : b : c |] :: Q Pat
+ > [t| T + T |] :: Q Type
+
+ will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
+ 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
+
+-}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9645818a2d778c8bef5a082bde9094…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9645818a2d778c8bef5a082bde9094…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed new branch wip/T26255 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26255
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26256] 10 commits: Update comments on `OptKind` to reflect the code reality
by Simon Peyton Jones (@simonpj) 02 Aug '25
by Simon Peyton Jones (@simonpj) 02 Aug '25
02 Aug '25
Simon Peyton Jones pushed to branch wip/T26256 at Glasgow Haskell Compiler / GHC
Commits:
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
On i386-linux:
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
bf03bbaa by Simon Hengel at 2025-08-01T04:39:05-04:00
Don't use MCDiagnostic for `ghcExit`
This changes the error message of `ghcExit` from
```
<no location info>: error:
Compilation had errors
```
to
```
Compilation had errors
```
- - - - -
a889ec75 by Simon Hengel at 2025-08-01T04:39:05-04:00
Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113)
- - - - -
81577fe7 by Ben Gamari at 2025-08-02T04:29:39-04:00
configure: Allow override of CrossCompiling
As noted in #26236, the current inference logic is a bit simplistic. In
particular, there are many cases (e.g. building for a new libc) where
the target and host triples may differ yet we are still able to run the
produced artifacts as native code.
Closes #26236.
- - - - -
01136779 by Andreas Klebinger at 2025-08-02T04:30:20-04:00
rts: Support COFF BigObj files in archives.
- - - - -
8ca2bd9c by Simon Peyton Jones at 2025-08-02T22:56:05+01:00
Take more care in zonkEqTypes on AppTy/AppTy
This patch fixes #26256.
See Note [zonkEqTypes and the PKTI] in GHC.Tc.Solver.Equality
- - - - -
37 changed files:
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Utils/Error.hs
- configure.ac
- docs/users_guide/runtime_control.rst
- docs/users_guide/win32-dlls.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/RtsFlags.c
- rts/Timer.c
- rts/include/rts/Flags.h
- rts/linker/LoadArchive.c
- testsuite/tests/corelint/T21115b.stderr
- + testsuite/tests/partial-sigs/should_compile/T26256.hs
- + testsuite/tests/partial-sigs/should_compile/T26256.stderr
- testsuite/tests/partial-sigs/should_compile/all.T
- testsuite/tests/rts/flags/all.T
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62c9fa95d821aa28fe38952b89a1e8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62c9fa95d821aa28fe38952b89a1e8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Teo Camarasu (@teo) 02 Aug '25
by Teo Camarasu (@teo) 02 Aug '25
02 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
07723dcb by Teo Camarasu at 2025-08-02T22:10:51+01:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
9645818a by Teo Camarasu at 2025-08-02T22:10:51+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
7 changed files:
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- rts/Messages.c
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
=====================================
@@ -555,20 +555,6 @@ pragInlD name inline rm phases
pragOpaqueD :: Quote m => Name -> m Dec
pragOpaqueD name = pure $ PragmaD $ OpaqueP name
-{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
-pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
-pragSpecD n ty phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
-
-{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
-pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
-pragSpecInlD n ty inline phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
-
pragSpecED :: Quote m
=> Maybe [m (TyVarBndr ())] -> [m RuleBndr]
-> m Exp
@@ -868,22 +854,6 @@ implicitParamT n t
t' <- t
pure $ ImplicitParamT n t'
-{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
-classP :: Quote m => Name -> [m Type] -> m Pred
-classP cla tys
- = do
- tysl <- sequenceA tys
- pure (foldl AppT (ConT cla) tysl)
-
-{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
-equalP :: Quote m => m Type -> m Type -> m Pred
-equalP tleft tright
- = do
- tleft1 <- tleft
- tright1 <- tright
- eqT <- equalityT
- pure (foldl AppT eqT [tleft1, tright1])
-
promotedT :: Quote m => Name -> m Type
promotedT = pure . PromotedT
@@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
sourceLazy = pure SourceLazy
sourceStrict = pure SourceStrict
-{-# DEPRECATED isStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
-{-# DEPRECATED notStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
-{-# DEPRECATED unpacked
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
-isStrict, notStrict, unpacked :: Quote m => m Strict
-isStrict = bang noSourceUnpackedness sourceStrict
-notStrict = bang noSourceUnpackedness noSourceStrictness
-unpacked = bang sourceUnpack sourceStrict
-
bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
bang u s = do u' <- u
s' <- s
@@ -931,16 +887,6 @@ bangType = liftA2 (,)
varBangType :: Quote m => Name -> m BangType -> m VarBangType
varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
-{-# DEPRECATED strictType
- "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
-strictType :: Quote m => m Strict -> m Type -> m StrictType
-strictType = bangType
-
-{-# DEPRECATED varStrictType
- "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
-varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
-varStrictType = varBangType
-
-- * Type Literals
-- MonadFail here complicates things (a lot) because it would mean we would
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -24,31 +24,15 @@
module GHC.Internal.TH.Lift
( Lift(..)
- -- * Generic Lift implementations
- , dataToQa
- , dataToCodeQ
- , dataToExpQ
- , liftDataTyped
- , liftData
- , dataToPatQ
-- * Wired-in names
, liftString
- , trueName
- , falseName
- , nothingName
- , justName
- , leftName
- , rightName
- , nonemptyName
)
where
import GHC.Internal.TH.Syntax
import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
-import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
import GHC.Internal.Data.Either
-import GHC.Internal.Type.Reflection
import GHC.Internal.Data.Bool
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
import GHC.Internal.Data.Foldable
@@ -294,20 +278,6 @@ deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f)
deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
=> Lift (# a | b | c | d | e | f | g #)
-trueName, falseName :: Name
-trueName = 'True
-falseName = 'False
-
-nothingName, justName :: Name
-nothingName = 'Nothing
-justName = 'Just
-
-leftName, rightName :: Name
-leftName = 'Left
-rightName = 'Right
-
-nonemptyName :: Name
-nonemptyName = '(:|)
-----------------------------------------------------
--
@@ -443,157 +413,3 @@ deriving instance Lift Info
deriving instance Lift AnnLookup
-- | @since template-haskell-2.22.1.0
deriving instance Lift Extension
-
------------------------------------------------------
---
--- Generic Lift implementations
---
------------------------------------------------------
-
--- | 'dataToQa' is an internal utility function for constructing generic
--- conversion functions from types with 'Data' instances to various
--- quasi-quoting representations. See the source of 'dataToExpQ' and
--- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
--- and @appQ@ are overloadable to account for different syntax for
--- expressions and patterns; @antiQ@ allows you to override type-specific
--- cases, a common usage is just @const Nothing@, which results in
--- no overloading.
-dataToQa :: forall m a k q. (Quote m, Data a)
- => (Name -> k)
- -> (Lit -> m q)
- -> (k -> [m q] -> m q)
- -> (forall b . Data b => b -> Maybe (m q))
- -> a
- -> m q
-dataToQa mkCon mkLit appCon antiQ t =
- case antiQ t of
- Nothing ->
- case constrRep constr of
- AlgConstr _ ->
- appCon (mkCon funOrConName) conArgs
- where
- funOrConName :: Name
- funOrConName =
- case showConstr constr of
- "(:)" -> Name (mkOccName ":")
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@"[]" -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@('(':_) -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Tuple"))
-
- -- Tricky case: see Note [Data for non-algebraic types]
- fun@(x:_) | startsVarSym x || startsVarId x
- -> mkNameG_v tyconPkg tyconMod fun
- con -> mkNameG_d tyconPkg tyconMod con
-
- where
- tycon :: TyCon
- tycon = (typeRepTyCon . typeOf) t
-
- tyconPkg, tyconMod :: String
- tyconPkg = tyConPackage tycon
- tyconMod = tyConModule tycon
-
- conArgs :: [m q]
- conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
- IntConstr n ->
- mkLit $ IntegerL n
- FloatConstr n ->
- mkLit $ RationalL n
- CharConstr c ->
- mkLit $ CharL c
- where
- constr :: Constr
- constr = toConstr t
-
- Just y -> y
-
-
-{- Note [Data for non-algebraic types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Class Data was originally intended for algebraic data types. But
-it is possible to use it for abstract types too. For example, in
-package `text` we find
-
- instance Data Text where
- ...
- toConstr _ = packConstr
-
- packConstr :: Constr
- packConstr = mkConstr textDataType "pack" [] Prefix
-
-Here `packConstr` isn't a real data constructor, it's an ordinary
-function. Two complications
-
-* In such a case, we must take care to build the Name using
- mkNameG_v (for values), not mkNameG_d (for data constructors).
- See #10796.
-
-* The pseudo-constructor is named only by its string, here "pack".
- But 'dataToQa' needs the TyCon of its defining module, and has
- to assume it's defined in the same module as the TyCon itself.
- But nothing enforces that; #12596 shows what goes wrong if
- "pack" is defined in a different module than the data type "Text".
- -}
-
--- | A typed variant of 'dataToExpQ'.
-dataToCodeQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (Code m b))
- -> a -> Code m a
-dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
-
--- | 'dataToExpQ' converts a value to a 'Exp' representation of the
--- same value, in the SYB style. It is generalized to take a function
--- override type-specific cases; see 'liftData' for a more commonly
--- used variant.
-dataToExpQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Exp))
- -> a
- -> m Exp
-dataToExpQ = dataToQa varOrConE litE (foldl appE)
- where
- -- Make sure that VarE is used if the Constr value relies on a
- -- function underneath the surface (instead of a constructor).
- -- See #10796.
- varOrConE s =
- case nameSpace s of
- Just VarName -> return (VarE s)
- Just (FldName {}) -> return (VarE s)
- Just DataName -> return (ConE s)
- _ -> error $ "Can't construct an expression from name "
- ++ showName s
- appE x y = do { a <- x; b <- y; return (AppE a b)}
- litE c = return (LitE c)
-
--- | A typed variant of 'liftData'.
-liftDataTyped :: (Quote m, Data a) => a -> Code m a
-liftDataTyped = dataToCodeQ (const Nothing)
-
--- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
--- works for any type with a 'Data' instance.
-liftData :: (Quote m, Data a) => a -> m Exp
-liftData = dataToExpQ (const Nothing)
-
--- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
--- value, in the SYB style. It takes a function to handle type-specific cases,
--- alternatively, pass @const Nothing@ to get default behavior.
-dataToPatQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Pat))
- -> a
- -> m Pat
-dataToPatQ = dataToQa id litP conP
- where litP l = return (LitP l)
- conP n ps =
- case nameSpace n of
- Just DataName -> do
- ps' <- sequence ps
- return (ConP n [] ps')
- _ -> error $ "Can't construct a pattern from name "
- ++ showName n
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -22,9 +22,6 @@ module GHC.Internal.TH.Syntax
-- * Language extensions
, module GHC.Internal.LanguageExtensions
, ForeignSrcLang(..)
- -- * Notes
- -- ** Unresolved Infix
- -- $infix
) where
#ifdef BOOTSTRAP_TH
@@ -847,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
addTopDecls :: [Dec] -> Q ()
addTopDecls ds = Q (qAddTopDecls ds)
--- |
-addForeignFile :: ForeignSrcLang -> String -> Q ()
-addForeignFile = addForeignSource
-{-# DEPRECATED addForeignFile
- "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
- #-} -- deprecated in 8.6
-- | Emit a foreign file which will be compiled and linked to the object for
-- the current module. Currently only languages that can be compiled with
@@ -1614,73 +1605,6 @@ maxPrecedence = (9::Int)
defaultFixity :: Fixity
defaultFixity = Fixity maxPrecedence InfixL
-
-{-
-Note [Unresolved infix]
-~~~~~~~~~~~~~~~~~~~~~~~
--}
-{- $infix #infix#
-
-When implementing antiquotation for quasiquoters, one often wants
-to parse strings into expressions:
-
-> parse :: String -> Maybe Exp
-
-But how should we parse @a + b * c@? If we don't know the fixities of
-@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
-+ b) * c@.
-
-In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
-which stand for \"unresolved infix expression / pattern / type / promoted
-constructor\", respectively. When the compiler is given a splice containing a
-tree of @UInfixE@ applications such as
-
-> UInfixE
-> (UInfixE e1 op1 e2)
-> op2
-> (UInfixE e3 op3 e4)
-
-it will look up and the fixities of the relevant operators and
-reassociate the tree as necessary.
-
- * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
- which are of use for parsing expressions like
-
- > (a + b * c) + d * e
-
- * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
- reassociated.
-
- * The 'UInfixE' constructor doesn't support sections. Sections
- such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
- sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
- outer-most section, and use 'UInfixE' constructors for all
- other operators:
-
- > InfixE
- > Just (UInfixE ...a + b * c...)
- > op
- > Nothing
-
- Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
- into 'Exp's differently:
-
- > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
- > -- will result in a fixity error if (+) is left-infix
- > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
- > -- no fixity errors
-
- * Quoted expressions such as
-
- > [| a * b + c |] :: Q Exp
- > [p| a : b : c |] :: Q Pat
- > [t| T + T |] :: Q Type
-
- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
- 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
-
--}
-
-----------------------------------------------------
--
-- The main syntax data types
=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing
conP :: Quote m => Name -> [m Pat] -> m Pat
conP n xs = Internal.conP n [] xs
+
+
+--------------------------------------------------------------------------------
+-- * Constraint predicates (deprecated)
+
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Quote m => Name -> [m Type] -> m Pred
+classP cla tys
+ = do
+ tysl <- sequenceA tys
+ pure (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: Quote m => m Type -> m Type -> m Pred
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ pure (foldl AppT eqT [tleft1, tright1])
+
+--------------------------------------------------------------------------------
+-- * Strictness queries (deprecated)
+{-# DEPRECATED isStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
+{-# DEPRECATED notStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
+{-# DEPRECATED unpacked
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
+isStrict, notStrict, unpacked :: Quote m => m Strict
+isStrict = bang noSourceUnpackedness sourceStrict
+notStrict = bang noSourceUnpackedness noSourceStrictness
+unpacked = bang sourceUnpack sourceStrict
+
+{-# DEPRECATED strictType
+ "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
+strictType :: Quote m => m Strict -> m Type -> m StrictType
+strictType = bangType
+
+{-# DEPRECATED varStrictType
+ "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
+varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
+varStrictType = varBangType
+
+--------------------------------------------------------------------------------
+-- * Specialisation pragmas (deprecated)
+
+{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
+pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
+pragSpecD n ty phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
+
+{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
+pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
+pragSpecInlD n ty inline phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
=====================================
libraries/template-haskell/Language/Haskell/TH/Quote.hs
=====================================
@@ -17,12 +17,12 @@ module Language.Haskell.TH.Quote
( QuasiQuoter(..)
, quoteFile
-- * For backwards compatibility
- ,dataToQa, dataToExpQ, dataToPatQ
+ , dataToQa, dataToExpQ, dataToPatQ
) where
import GHC.Boot.TH.Syntax
import GHC.Boot.TH.Quote
-import GHC.Boot.TH.Lift
+import Language.Haskell.TH.Syntax (dataToQa, dataToExpQ, dataToPatQ)
-- | 'quoteFile' takes a 'QuasiQuoter' and lifts it into one that read
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,8 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,19 +192,267 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
+ -- * Notes
+ -- ** Unresolved Infix
+ -- $infix
)
where
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
import System.FilePath
+import Data.Data hiding (Fixity(..))
+import Data.List.NonEmpty (NonEmpty(..))
+import GHC.Lexeme ( startsVarSym, startsVarId )
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
-- and exports additionally functions that depend on filepath.
+-- |
+addForeignFile :: ForeignSrcLang -> String -> Q ()
+addForeignFile = addForeignSource
+{-# DEPRECATED addForeignFile
+ "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
+ #-} -- deprecated in 8.6
+
-- | The input is a filepath, which if relative is offset by the package root.
makeRelativeToProject :: FilePath -> Q FilePath
makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
+
+trueName, falseName :: Name
+trueName = 'True
+falseName = 'False
+
+nothingName, justName :: Name
+nothingName = 'Nothing
+justName = 'Just
+
+leftName, rightName :: Name
+leftName = 'Left
+rightName = 'Right
+
+nonemptyName :: Name
+nonemptyName = '(:|)
+
+-----------------------------------------------------
+--
+-- Generic Lift implementations
+--
+-----------------------------------------------------
+
+-- | 'dataToQa' is an internal utility function for constructing generic
+-- conversion functions from types with 'Data' instances to various
+-- quasi-quoting representations. See the source of 'dataToExpQ' and
+-- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
+-- and @appQ@ are overloadable to account for different syntax for
+-- expressions and patterns; @antiQ@ allows you to override type-specific
+-- cases, a common usage is just @const Nothing@, which results in
+-- no overloading.
+dataToQa :: forall m a k q. (Quote m, Data a)
+ => (Name -> k)
+ -> (Lit -> m q)
+ -> (k -> [m q] -> m q)
+ -> (forall b . Data b => b -> Maybe (m q))
+ -> a
+ -> m q
+dataToQa mkCon mkLit appCon antiQ t =
+ case antiQ t of
+ Nothing ->
+ case constrRep constr of
+ AlgConstr _ ->
+ appCon (mkCon funOrConName) conArgs
+ where
+ funOrConName :: Name
+ funOrConName =
+ case showConstr constr of
+ "(:)" -> Name (mkOccName ":")
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@"[]" -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@('(':_) -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Tuple"))
+
+ -- Tricky case: see Note [Data for non-algebraic types]
+ fun@(x:_) | startsVarSym x || startsVarId x
+ -> mkNameG_v tyconPkg tyconMod fun
+ con -> mkNameG_d tyconPkg tyconMod con
+
+ where
+ tycon :: TyCon
+ tycon = (typeRepTyCon . typeOf) t
+
+ tyconPkg, tyconMod :: String
+ tyconPkg = tyConPackage tycon
+ tyconMod = tyConModule tycon
+
+ conArgs :: [m q]
+ conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
+ IntConstr n ->
+ mkLit $ IntegerL n
+ FloatConstr n ->
+ mkLit $ RationalL n
+ CharConstr c ->
+ mkLit $ CharL c
+ where
+ constr :: Constr
+ constr = toConstr t
+
+ Just y -> y
+
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types. But
+it is possible to use it for abstract types too. For example, in
+package `text` we find
+
+ instance Data Text where
+ ...
+ toConstr _ = packConstr
+
+ packConstr :: Constr
+ packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordinary
+function. Two complications
+
+* In such a case, we must take care to build the Name using
+ mkNameG_v (for values), not mkNameG_d (for data constructors).
+ See #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+ But 'dataToQa' needs the TyCon of its defining module, and has
+ to assume it's defined in the same module as the TyCon itself.
+ But nothing enforces that; #12596 shows what goes wrong if
+ "pack" is defined in a different module than the data type "Text".
+ -}
+
+-- | A typed variant of 'dataToExpQ'.
+dataToCodeQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (Code m b))
+ -> a -> Code m a
+dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
+
+-- | 'dataToExpQ' converts a value to a 'Exp' representation of the
+-- same value, in the SYB style. It is generalized to take a function
+-- override type-specific cases; see 'liftData' for a more commonly
+-- used variant.
+dataToExpQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Exp))
+ -> a
+ -> m Exp
+dataToExpQ = dataToQa varOrConE litE (foldl appE)
+ where
+ -- Make sure that VarE is used if the Constr value relies on a
+ -- function underneath the surface (instead of a constructor).
+ -- See #10796.
+ varOrConE s =
+ case nameSpace s of
+ Just VarName -> return (VarE s)
+ Just (FldName {}) -> return (VarE s)
+ Just DataName -> return (ConE s)
+ _ -> error $ "Can't construct an expression from name "
+ ++ showName s
+ appE x y = do { a <- x; b <- y; return (AppE a b)}
+ litE c = return (LitE c)
+
+-- | A typed variant of 'liftData'.
+liftDataTyped :: (Quote m, Data a) => a -> Code m a
+liftDataTyped = dataToCodeQ (const Nothing)
+
+-- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
+-- works for any type with a 'Data' instance.
+liftData :: (Quote m, Data a) => a -> m Exp
+liftData = dataToExpQ (const Nothing)
+
+-- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
+-- value, in the SYB style. It takes a function to handle type-specific cases,
+-- alternatively, pass @const Nothing@ to get default behavior.
+dataToPatQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Pat))
+ -> a
+ -> m Pat
+dataToPatQ = dataToQa id litP conP
+ where litP l = return (LitP l)
+ conP n ps =
+ case nameSpace n of
+ Just DataName -> do
+ ps' <- sequence ps
+ return (ConP n [] ps')
+ _ -> error $ "Can't construct a pattern from name "
+ ++ showName n
+
+{-
+Note [Unresolved infix]
+~~~~~~~~~~~~~~~~~~~~~~~
+-}
+{- $infix #infix#
+
+When implementing antiquotation for quasiquoters, one often wants
+to parse strings into expressions:
+
+> parse :: String -> Maybe Exp
+
+But how should we parse @a + b * c@? If we don't know the fixities of
+@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
++ b) * c@.
+
+In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
+which stand for \"unresolved infix expression / pattern / type / promoted
+constructor\", respectively. When the compiler is given a splice containing a
+tree of @UInfixE@ applications such as
+
+> UInfixE
+> (UInfixE e1 op1 e2)
+> op2
+> (UInfixE e3 op3 e4)
+
+it will look up and the fixities of the relevant operators and
+reassociate the tree as necessary.
+
+ * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
+ which are of use for parsing expressions like
+
+ > (a + b * c) + d * e
+
+ * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
+ reassociated.
+
+ * The 'UInfixE' constructor doesn't support sections. Sections
+ such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
+ sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
+ outer-most section, and use 'UInfixE' constructors for all
+ other operators:
+
+ > InfixE
+ > Just (UInfixE ...a + b * c...)
+ > op
+ > Nothing
+
+ Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
+ into 'Exp's differently:
+
+ > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
+ > -- will result in a fixity error if (+) is left-infix
+ > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
+ > -- no fixity errors
+
+ * Quoted expressions such as
+
+ > [| a * b + c |] :: Q Exp
+ > [p| a : b : c |] :: Q Pat
+ > [t| T + T |] :: Q Type
+
+ will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
+ 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
+
+-}
=====================================
rts/Messages.c
=====================================
@@ -187,6 +187,10 @@ uint32_t messageBlackHole(Capability *cap, MessageBlackHole *msg)
return 0;
}
+ if(bh_info == &stg_WHITEHOLE_info){
+ fprintf(stderr, "\noh nooo %xll\n", ((StgInd*)bh)->indirectee);
+ }
+
// The blackhole must indirect to a TSO, a BLOCKING_QUEUE, an IND,
// or a value.
StgClosure *p;
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ae6f4e8057f47963fd50265e3d47f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ae6f4e8057f47963fd50265e3d47f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 2 commits: template-haskell: move some identifiers from ghc-internal to template-haskell
by Teo Camarasu (@teo) 02 Aug '25
by Teo Camarasu (@teo) 02 Aug '25
02 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
1fce5d46 by Teo Camarasu at 2025-08-02T22:05:13+01:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
6ae6f4e8 by Teo Camarasu at 2025-08-02T22:06:43+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
7 changed files:
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- rts/Messages.c
Changes:
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
=====================================
@@ -555,20 +555,6 @@ pragInlD name inline rm phases
pragOpaqueD :: Quote m => Name -> m Dec
pragOpaqueD name = pure $ PragmaD $ OpaqueP name
-{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
-pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
-pragSpecD n ty phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
-
-{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
-pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
-pragSpecInlD n ty inline phases
- = do
- ty1 <- ty
- pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
-
pragSpecED :: Quote m
=> Maybe [m (TyVarBndr ())] -> [m RuleBndr]
-> m Exp
@@ -868,22 +854,6 @@ implicitParamT n t
t' <- t
pure $ ImplicitParamT n t'
-{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
-classP :: Quote m => Name -> [m Type] -> m Pred
-classP cla tys
- = do
- tysl <- sequenceA tys
- pure (foldl AppT (ConT cla) tysl)
-
-{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
-equalP :: Quote m => m Type -> m Type -> m Pred
-equalP tleft tright
- = do
- tleft1 <- tleft
- tright1 <- tright
- eqT <- equalityT
- pure (foldl AppT eqT [tleft1, tright1])
-
promotedT :: Quote m => Name -> m Type
promotedT = pure . PromotedT
@@ -906,20 +876,6 @@ noSourceStrictness = pure NoSourceStrictness
sourceLazy = pure SourceLazy
sourceStrict = pure SourceStrict
-{-# DEPRECATED isStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
-{-# DEPRECATED notStrict
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
-{-# DEPRECATED unpacked
- ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
- "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
-isStrict, notStrict, unpacked :: Quote m => m Strict
-isStrict = bang noSourceUnpackedness sourceStrict
-notStrict = bang noSourceUnpackedness noSourceStrictness
-unpacked = bang sourceUnpack sourceStrict
-
bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang
bang u s = do u' <- u
s' <- s
@@ -931,16 +887,6 @@ bangType = liftA2 (,)
varBangType :: Quote m => Name -> m BangType -> m VarBangType
varBangType v bt = (\(b, t) -> (v, b, t)) <$> bt
-{-# DEPRECATED strictType
- "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
-strictType :: Quote m => m Strict -> m Type -> m StrictType
-strictType = bangType
-
-{-# DEPRECATED varStrictType
- "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
-varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
-varStrictType = varBangType
-
-- * Type Literals
-- MonadFail here complicates things (a lot) because it would mean we would
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -24,31 +24,15 @@
module GHC.Internal.TH.Lift
( Lift(..)
- -- * Generic Lift implementations
- , dataToQa
- , dataToCodeQ
- , dataToExpQ
- , liftDataTyped
- , liftData
- , dataToPatQ
-- * Wired-in names
, liftString
- , trueName
- , falseName
- , nothingName
- , justName
- , leftName
- , rightName
- , nonemptyName
)
where
import GHC.Internal.TH.Syntax
import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives]
-import GHC.Internal.Lexeme ( startsVarSym, startsVarId )
import GHC.Internal.Data.Either
-import GHC.Internal.Type.Reflection
import GHC.Internal.Data.Bool
import GHC.Internal.Base hiding (NonEmpty(..), Type, Module, inline)
import GHC.Internal.Data.Foldable
@@ -294,20 +278,6 @@ deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f)
deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
=> Lift (# a | b | c | d | e | f | g #)
-trueName, falseName :: Name
-trueName = 'True
-falseName = 'False
-
-nothingName, justName :: Name
-nothingName = 'Nothing
-justName = 'Just
-
-leftName, rightName :: Name
-leftName = 'Left
-rightName = 'Right
-
-nonemptyName :: Name
-nonemptyName = '(:|)
-----------------------------------------------------
--
@@ -443,157 +413,3 @@ deriving instance Lift Info
deriving instance Lift AnnLookup
-- | @since template-haskell-2.22.1.0
deriving instance Lift Extension
-
------------------------------------------------------
---
--- Generic Lift implementations
---
------------------------------------------------------
-
--- | 'dataToQa' is an internal utility function for constructing generic
--- conversion functions from types with 'Data' instances to various
--- quasi-quoting representations. See the source of 'dataToExpQ' and
--- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
--- and @appQ@ are overloadable to account for different syntax for
--- expressions and patterns; @antiQ@ allows you to override type-specific
--- cases, a common usage is just @const Nothing@, which results in
--- no overloading.
-dataToQa :: forall m a k q. (Quote m, Data a)
- => (Name -> k)
- -> (Lit -> m q)
- -> (k -> [m q] -> m q)
- -> (forall b . Data b => b -> Maybe (m q))
- -> a
- -> m q
-dataToQa mkCon mkLit appCon antiQ t =
- case antiQ t of
- Nothing ->
- case constrRep constr of
- AlgConstr _ ->
- appCon (mkCon funOrConName) conArgs
- where
- funOrConName :: Name
- funOrConName =
- case showConstr constr of
- "(:)" -> Name (mkOccName ":")
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@"[]" -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Types"))
- con@('(':_) -> Name (mkOccName con)
- (NameG DataName
- (mkPkgName "ghc-internal")
- (mkModName "GHC.Internal.Tuple"))
-
- -- Tricky case: see Note [Data for non-algebraic types]
- fun@(x:_) | startsVarSym x || startsVarId x
- -> mkNameG_v tyconPkg tyconMod fun
- con -> mkNameG_d tyconPkg tyconMod con
-
- where
- tycon :: TyCon
- tycon = (typeRepTyCon . typeOf) t
-
- tyconPkg, tyconMod :: String
- tyconPkg = tyConPackage tycon
- tyconMod = tyConModule tycon
-
- conArgs :: [m q]
- conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
- IntConstr n ->
- mkLit $ IntegerL n
- FloatConstr n ->
- mkLit $ RationalL n
- CharConstr c ->
- mkLit $ CharL c
- where
- constr :: Constr
- constr = toConstr t
-
- Just y -> y
-
-
-{- Note [Data for non-algebraic types]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Class Data was originally intended for algebraic data types. But
-it is possible to use it for abstract types too. For example, in
-package `text` we find
-
- instance Data Text where
- ...
- toConstr _ = packConstr
-
- packConstr :: Constr
- packConstr = mkConstr textDataType "pack" [] Prefix
-
-Here `packConstr` isn't a real data constructor, it's an ordinary
-function. Two complications
-
-* In such a case, we must take care to build the Name using
- mkNameG_v (for values), not mkNameG_d (for data constructors).
- See #10796.
-
-* The pseudo-constructor is named only by its string, here "pack".
- But 'dataToQa' needs the TyCon of its defining module, and has
- to assume it's defined in the same module as the TyCon itself.
- But nothing enforces that; #12596 shows what goes wrong if
- "pack" is defined in a different module than the data type "Text".
- -}
-
--- | A typed variant of 'dataToExpQ'.
-dataToCodeQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (Code m b))
- -> a -> Code m a
-dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
-
--- | 'dataToExpQ' converts a value to a 'Exp' representation of the
--- same value, in the SYB style. It is generalized to take a function
--- override type-specific cases; see 'liftData' for a more commonly
--- used variant.
-dataToExpQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Exp))
- -> a
- -> m Exp
-dataToExpQ = dataToQa varOrConE litE (foldl appE)
- where
- -- Make sure that VarE is used if the Constr value relies on a
- -- function underneath the surface (instead of a constructor).
- -- See #10796.
- varOrConE s =
- case nameSpace s of
- Just VarName -> return (VarE s)
- Just (FldName {}) -> return (VarE s)
- Just DataName -> return (ConE s)
- _ -> error $ "Can't construct an expression from name "
- ++ showName s
- appE x y = do { a <- x; b <- y; return (AppE a b)}
- litE c = return (LitE c)
-
--- | A typed variant of 'liftData'.
-liftDataTyped :: (Quote m, Data a) => a -> Code m a
-liftDataTyped = dataToCodeQ (const Nothing)
-
--- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
--- works for any type with a 'Data' instance.
-liftData :: (Quote m, Data a) => a -> m Exp
-liftData = dataToExpQ (const Nothing)
-
--- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
--- value, in the SYB style. It takes a function to handle type-specific cases,
--- alternatively, pass @const Nothing@ to get default behavior.
-dataToPatQ :: (Quote m, Data a)
- => (forall b . Data b => b -> Maybe (m Pat))
- -> a
- -> m Pat
-dataToPatQ = dataToQa id litP conP
- where litP l = return (LitP l)
- conP n ps =
- case nameSpace n of
- Just DataName -> do
- ps' <- sequence ps
- return (ConP n [] ps')
- _ -> error $ "Can't construct a pattern from name "
- ++ showName n
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -22,9 +22,6 @@ module GHC.Internal.TH.Syntax
-- * Language extensions
, module GHC.Internal.LanguageExtensions
, ForeignSrcLang(..)
- -- * Notes
- -- ** Unresolved Infix
- -- $infix
) where
#ifdef BOOTSTRAP_TH
@@ -847,12 +844,6 @@ addTempFile suffix = Q (qAddTempFile suffix)
addTopDecls :: [Dec] -> Q ()
addTopDecls ds = Q (qAddTopDecls ds)
--- |
-addForeignFile :: ForeignSrcLang -> String -> Q ()
-addForeignFile = addForeignSource
-{-# DEPRECATED addForeignFile
- "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
- #-} -- deprecated in 8.6
-- | Emit a foreign file which will be compiled and linked to the object for
-- the current module. Currently only languages that can be compiled with
@@ -1614,73 +1605,6 @@ maxPrecedence = (9::Int)
defaultFixity :: Fixity
defaultFixity = Fixity maxPrecedence InfixL
-
-{-
-Note [Unresolved infix]
-~~~~~~~~~~~~~~~~~~~~~~~
--}
-{- $infix #infix#
-
-When implementing antiquotation for quasiquoters, one often wants
-to parse strings into expressions:
-
-> parse :: String -> Maybe Exp
-
-But how should we parse @a + b * c@? If we don't know the fixities of
-@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
-+ b) * c@.
-
-In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
-which stand for \"unresolved infix expression / pattern / type / promoted
-constructor\", respectively. When the compiler is given a splice containing a
-tree of @UInfixE@ applications such as
-
-> UInfixE
-> (UInfixE e1 op1 e2)
-> op2
-> (UInfixE e3 op3 e4)
-
-it will look up and the fixities of the relevant operators and
-reassociate the tree as necessary.
-
- * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
- which are of use for parsing expressions like
-
- > (a + b * c) + d * e
-
- * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
- reassociated.
-
- * The 'UInfixE' constructor doesn't support sections. Sections
- such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
- sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
- outer-most section, and use 'UInfixE' constructors for all
- other operators:
-
- > InfixE
- > Just (UInfixE ...a + b * c...)
- > op
- > Nothing
-
- Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
- into 'Exp's differently:
-
- > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
- > -- will result in a fixity error if (+) is left-infix
- > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
- > -- no fixity errors
-
- * Quoted expressions such as
-
- > [| a * b + c |] :: Q Exp
- > [p| a : b : c |] :: Q Pat
- > [t| T + T |] :: Q Type
-
- will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
- 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
-
--}
-
-----------------------------------------------------
--
-- The main syntax data types
=====================================
libraries/template-haskell/Language/Haskell/TH/Lib.hs
=====================================
@@ -395,3 +395,66 @@ mdoE = Internal.mdoE Nothing
conP :: Quote m => Name -> [m Pat] -> m Pat
conP n xs = Internal.conP n [] xs
+
+
+--------------------------------------------------------------------------------
+-- * Constraint predicates (deprecated)
+
+{-# DEPRECATED classP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use 'conT' and 'appT'." #-}
+classP :: Quote m => Name -> [m Type] -> m Pred
+classP cla tys
+ = do
+ tysl <- sequenceA tys
+ pure (foldl AppT (ConT cla) tysl)
+
+{-# DEPRECATED equalP "As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see 'equalityT'." #-}
+equalP :: Quote m => m Type -> m Type -> m Pred
+equalP tleft tright
+ = do
+ tleft1 <- tleft
+ tright1 <- tright
+ eqT <- equalityT
+ pure (foldl AppT eqT [tleft1, tright1])
+
+--------------------------------------------------------------------------------
+-- * Strictness queries (deprecated)
+{-# DEPRECATED isStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness sourceStrict'"] #-}
+{-# DEPRECATED notStrict
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang noSourceUnpackedness noSourceStrictness'"] #-}
+{-# DEPRECATED unpacked
+ ["Use 'bang'. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. ",
+ "Example usage: 'bang sourceUnpack sourceStrict'"] #-}
+isStrict, notStrict, unpacked :: Quote m => m Strict
+isStrict = bang noSourceUnpackedness sourceStrict
+notStrict = bang noSourceUnpackedness noSourceStrictness
+unpacked = bang sourceUnpack sourceStrict
+
+{-# DEPRECATED strictType
+ "As of @template-haskell-2.11.0.0@, 'StrictType' has been replaced by 'BangType'. Please use 'bangType' instead." #-}
+strictType :: Quote m => m Strict -> m Type -> m StrictType
+strictType = bangType
+
+{-# DEPRECATED varStrictType
+ "As of @template-haskell-2.11.0.0@, 'VarStrictType' has been replaced by 'VarBangType'. Please use 'varBangType' instead." #-}
+varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType
+varStrictType = varBangType
+
+--------------------------------------------------------------------------------
+-- * Specialisation pragmas (deprecated)
+
+{-# DEPRECATED pragSpecD "Please use 'pragSpecED' instead. 'pragSpecD' will be removed in GHC 9.18." #-}
+pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec
+pragSpecD n ty phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 Nothing phases
+
+{-# DEPRECATED pragSpecInlD "Please use 'pragSpecInlED' instead. 'pragSpecInlD' will be removed in GHC 9.18." #-}
+pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec
+pragSpecInlD n ty inline phases
+ = do
+ ty1 <- ty
+ pure $ PragmaD $ SpecialiseP n ty1 (Just inline) phases
=====================================
libraries/template-haskell/Language/Haskell/TH/Quote.hs
=====================================
@@ -17,12 +17,12 @@ module Language.Haskell.TH.Quote
( QuasiQuoter(..)
, quoteFile
-- * For backwards compatibility
- ,dataToQa, dataToExpQ, dataToPatQ
+ , dataToQa, dataToExpQ, dataToPatQ
) where
import GHC.Boot.TH.Syntax
import GHC.Boot.TH.Quote
-import GHC.Boot.TH.Lift
+import Language.Haskell.TH.Syntax (dataToQa, dataToExpQ, dataToPatQ)
-- | 'quoteFile' takes a 'QuasiQuoter' and lifts it into one that read
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,8 @@
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Safe #-}
+{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,19 +192,267 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
+ -- * Notes
+ -- ** Unresolved Infix
+ -- $infix
)
where
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
import System.FilePath
+import Data.Data hiding (Fixity(..))
+import Data.List.NonEmpty (NonEmpty(..))
+import GHC.Lexeme ( startsVarSym, startsVarId )
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
-- and exports additionally functions that depend on filepath.
+-- |
+addForeignFile :: ForeignSrcLang -> String -> Q ()
+addForeignFile = addForeignSource
+{-# DEPRECATED addForeignFile
+ "Use 'Language.Haskell.TH.Syntax.addForeignSource' instead"
+ #-} -- deprecated in 8.6
+
-- | The input is a filepath, which if relative is offset by the package root.
makeRelativeToProject :: FilePath -> Q FilePath
makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
+
+trueName, falseName :: Name
+trueName = 'True
+falseName = 'False
+
+nothingName, justName :: Name
+nothingName = 'Nothing
+justName = 'Just
+
+leftName, rightName :: Name
+leftName = 'Left
+rightName = 'Right
+
+nonemptyName :: Name
+nonemptyName = '(:|)
+
+-----------------------------------------------------
+--
+-- Generic Lift implementations
+--
+-----------------------------------------------------
+
+-- | 'dataToQa' is an internal utility function for constructing generic
+-- conversion functions from types with 'Data' instances to various
+-- quasi-quoting representations. See the source of 'dataToExpQ' and
+-- 'dataToPatQ' for two example usages: @mkCon@, @mkLit@
+-- and @appQ@ are overloadable to account for different syntax for
+-- expressions and patterns; @antiQ@ allows you to override type-specific
+-- cases, a common usage is just @const Nothing@, which results in
+-- no overloading.
+dataToQa :: forall m a k q. (Quote m, Data a)
+ => (Name -> k)
+ -> (Lit -> m q)
+ -> (k -> [m q] -> m q)
+ -> (forall b . Data b => b -> Maybe (m q))
+ -> a
+ -> m q
+dataToQa mkCon mkLit appCon antiQ t =
+ case antiQ t of
+ Nothing ->
+ case constrRep constr of
+ AlgConstr _ ->
+ appCon (mkCon funOrConName) conArgs
+ where
+ funOrConName :: Name
+ funOrConName =
+ case showConstr constr of
+ "(:)" -> Name (mkOccName ":")
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@"[]" -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Types"))
+ con@('(':_) -> Name (mkOccName con)
+ (NameG DataName
+ (mkPkgName "ghc-internal")
+ (mkModName "GHC.Internal.Tuple"))
+
+ -- Tricky case: see Note [Data for non-algebraic types]
+ fun@(x:_) | startsVarSym x || startsVarId x
+ -> mkNameG_v tyconPkg tyconMod fun
+ con -> mkNameG_d tyconPkg tyconMod con
+
+ where
+ tycon :: TyCon
+ tycon = (typeRepTyCon . typeOf) t
+
+ tyconPkg, tyconMod :: String
+ tyconPkg = tyConPackage tycon
+ tyconMod = tyConModule tycon
+
+ conArgs :: [m q]
+ conArgs = gmapQ (dataToQa mkCon mkLit appCon antiQ) t
+ IntConstr n ->
+ mkLit $ IntegerL n
+ FloatConstr n ->
+ mkLit $ RationalL n
+ CharConstr c ->
+ mkLit $ CharL c
+ where
+ constr :: Constr
+ constr = toConstr t
+
+ Just y -> y
+
+
+{- Note [Data for non-algebraic types]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Class Data was originally intended for algebraic data types. But
+it is possible to use it for abstract types too. For example, in
+package `text` we find
+
+ instance Data Text where
+ ...
+ toConstr _ = packConstr
+
+ packConstr :: Constr
+ packConstr = mkConstr textDataType "pack" [] Prefix
+
+Here `packConstr` isn't a real data constructor, it's an ordinary
+function. Two complications
+
+* In such a case, we must take care to build the Name using
+ mkNameG_v (for values), not mkNameG_d (for data constructors).
+ See #10796.
+
+* The pseudo-constructor is named only by its string, here "pack".
+ But 'dataToQa' needs the TyCon of its defining module, and has
+ to assume it's defined in the same module as the TyCon itself.
+ But nothing enforces that; #12596 shows what goes wrong if
+ "pack" is defined in a different module than the data type "Text".
+ -}
+
+-- | A typed variant of 'dataToExpQ'.
+dataToCodeQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (Code m b))
+ -> a -> Code m a
+dataToCodeQ f = unsafeCodeCoerce . dataToExpQ (fmap unTypeCode . f)
+
+-- | 'dataToExpQ' converts a value to a 'Exp' representation of the
+-- same value, in the SYB style. It is generalized to take a function
+-- override type-specific cases; see 'liftData' for a more commonly
+-- used variant.
+dataToExpQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Exp))
+ -> a
+ -> m Exp
+dataToExpQ = dataToQa varOrConE litE (foldl appE)
+ where
+ -- Make sure that VarE is used if the Constr value relies on a
+ -- function underneath the surface (instead of a constructor).
+ -- See #10796.
+ varOrConE s =
+ case nameSpace s of
+ Just VarName -> return (VarE s)
+ Just (FldName {}) -> return (VarE s)
+ Just DataName -> return (ConE s)
+ _ -> error $ "Can't construct an expression from name "
+ ++ showName s
+ appE x y = do { a <- x; b <- y; return (AppE a b)}
+ litE c = return (LitE c)
+
+-- | A typed variant of 'liftData'.
+liftDataTyped :: (Quote m, Data a) => a -> Code m a
+liftDataTyped = dataToCodeQ (const Nothing)
+
+-- | 'liftData' is a variant of 'lift' in the 'Lift' type class which
+-- works for any type with a 'Data' instance.
+liftData :: (Quote m, Data a) => a -> m Exp
+liftData = dataToExpQ (const Nothing)
+
+-- | 'dataToPatQ' converts a value to a 'Pat' representation of the same
+-- value, in the SYB style. It takes a function to handle type-specific cases,
+-- alternatively, pass @const Nothing@ to get default behavior.
+dataToPatQ :: (Quote m, Data a)
+ => (forall b . Data b => b -> Maybe (m Pat))
+ -> a
+ -> m Pat
+dataToPatQ = dataToQa id litP conP
+ where litP l = return (LitP l)
+ conP n ps =
+ case nameSpace n of
+ Just DataName -> do
+ ps' <- sequence ps
+ return (ConP n [] ps')
+ _ -> error $ "Can't construct a pattern from name "
+ ++ showName n
+
+{-
+Note [Unresolved infix]
+~~~~~~~~~~~~~~~~~~~~~~~
+-}
+{- $infix #infix#
+
+When implementing antiquotation for quasiquoters, one often wants
+to parse strings into expressions:
+
+> parse :: String -> Maybe Exp
+
+But how should we parse @a + b * c@? If we don't know the fixities of
+@+@ and @*@, we don't know whether to parse it as @a + (b * c)@ or @(a
++ b) * c@.
+
+In cases like this, use 'UInfixE', 'UInfixP', 'UInfixT', or 'PromotedUInfixT',
+which stand for \"unresolved infix expression / pattern / type / promoted
+constructor\", respectively. When the compiler is given a splice containing a
+tree of @UInfixE@ applications such as
+
+> UInfixE
+> (UInfixE e1 op1 e2)
+> op2
+> (UInfixE e3 op3 e4)
+
+it will look up and the fixities of the relevant operators and
+reassociate the tree as necessary.
+
+ * trees will not be reassociated across 'ParensE', 'ParensP', or 'ParensT',
+ which are of use for parsing expressions like
+
+ > (a + b * c) + d * e
+
+ * 'InfixE', 'InfixP', 'InfixT', and 'PromotedInfixT' expressions are never
+ reassociated.
+
+ * The 'UInfixE' constructor doesn't support sections. Sections
+ such as @(a *)@ have no ambiguity, so 'InfixE' suffices. For longer
+ sections such as @(a + b * c -)@, use an 'InfixE' constructor for the
+ outer-most section, and use 'UInfixE' constructors for all
+ other operators:
+
+ > InfixE
+ > Just (UInfixE ...a + b * c...)
+ > op
+ > Nothing
+
+ Sections such as @(a + b +)@ and @((a + b) +)@ should be rendered
+ into 'Exp's differently:
+
+ > (+ a + b) ---> InfixE Nothing + (Just $ UInfixE a + b)
+ > -- will result in a fixity error if (+) is left-infix
+ > (+ (a + b)) ---> InfixE Nothing + (Just $ ParensE $ UInfixE a + b)
+ > -- no fixity errors
+
+ * Quoted expressions such as
+
+ > [| a * b + c |] :: Q Exp
+ > [p| a : b : c |] :: Q Pat
+ > [t| T + T |] :: Q Type
+
+ will never contain 'UInfixE', 'UInfixP', 'UInfixT', 'PromotedUInfixT',
+ 'InfixT', 'PromotedInfixT, 'ParensE', 'ParensP', or 'ParensT' constructors.
+
+-}
=====================================
rts/Messages.c
=====================================
@@ -187,6 +187,10 @@ uint32_t messageBlackHole(Capability *cap, MessageBlackHole *msg)
return 0;
}
+ if(bh_info == &stg_WHITEHOLE_info){
+ fprintf(stderr, "\noh nooo %xll\n", ((StgInd*)bh)->indirectee);
+ }
+
// The blackhole must indirect to a TSO, a BLOCKING_QUEUE, an IND,
// or a value.
StgClosure *p;
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30ad77f3e4dbe6b449a03a08ff046b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30ad77f3e4dbe6b449a03a08ff046b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 62 commits: Fix documentation for HEAP_PROF_SAMPLE_STRING
by Teo Camarasu (@teo) 02 Aug '25
by Teo Camarasu (@teo) 02 Aug '25
02 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
f707bab4 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Specialise: Improve specialisation by refactoring interestingDict
This MR addresses #26051, which concerns missed type-class specialisation.
The main payload of the MR is to completely refactor the key function
`interestingDict` in GHC.Core.Opt.Specialise
The main change is that we now also look at the structure of the
dictionary we consider specializing on, rather than only the type.
See the big `Note [Interesting dictionary arguments]`
- - - - -
ca7a9d42 by Simon Peyton Jones at 2025-07-12T14:56:16+01:00
Treat tuple dictionaries uniformly; don't unbox them
See `Note [Do not unbox class dictionaries]` in DmdAnal.hs,
sep (DNB1).
This MR reverses the plan in #23398, which suggested a special case to
unbox tuple dictionaries in worker/wrapper. But:
- This was the cause of a pile of complexity in the specialiser (#26158)
- Even with that complexity, specialision was still bad, very bad
See https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
And it's entirely unnecessary! Specialision works fine without
unboxing tuple dictionaries.
- - - - -
be7296c9 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Remove complex special case from the type-class specialiser
There was a pretty tricky special case in Specialise which is no
longer necessary.
* Historical Note [Floating dictionaries out of cases]
* #26158
* #19747 https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
This MR removes it. Hooray.
- - - - -
4acf3a86 by Ben Gamari at 2025-07-15T05:46:32-04:00
configure: bump version to 9.15
- - - - -
45efaf71 by Teo Camarasu at 2025-07-15T05:47:13-04:00
rts/nonmovingGC: remove n_free
We remove the nonmovingHeap.n_free variable.
We wanted this to track the length of nonmovingHeap.free.
But this isn't possible to do atomically.
When this isn't accurate we can get a segfault by going past the end of
the list.
Instead, we just count the length of the list when we grab it in
nonmovingPruneFreeSegment.
Resolves #26186
- - - - -
c635f164 by Ben Gamari at 2025-07-15T14:05:54-04:00
configure: Drop probing of ld.gold
As noted in #25716, `gold` has been dropped from binutils-2.44.
Fixes #25716.
Metric Increase:
size_hello_artifact_gzip
size_hello_unicode_gzip
ghc_prim_so
- - - - -
637bb538 by Ben Gamari at 2025-07-15T14:05:55-04:00
testsuite/recomp015: Ignore stderr
This is necessary since ld.bfd complains
that we don't have a .note.GNU-stack section,
potentially resulting in an executable stack.
- - - - -
d3cd4ec8 by Wen Kokke at 2025-07-15T14:06:39-04:00
Fix documentation for heap profile ID
- - - - -
73082769 by Ben Gamari at 2025-07-15T16:56:38-04:00
Bump win32-tarballs to v0.9
- - - - -
3b63b254 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle null terminated string tables
As of `llvm-ar` now emits filename tables terminated with null
characters instead of the usual POSIX `/\n` sequence.
Fixes #26150.
- - - - -
195f6527 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: rename label so name doesn't conflict with param
- - - - -
63373b95 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Handle API set symbol versioning conflicts
- - - - -
48e9aa3e by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Mark API set symbols as HIDDEN and correct symbol type
- - - - -
959e827a by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Implement WEAK EXTERNAL undef redirection by target symbol name
- - - - -
65f19293 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle string table entries terminated with /
llvm-ar appears to terminate string table entries with `/\n` [1]. This
matters in the case of thin archives, since the filename is used. In the
past this worked since `llvm-ar` would produce archives with "small"
filenames when possible. However, now it appears to always use the
string table.
[1] https://github.com/llvm/llvm-project/blob/bfb686bb5ba503e9386dc899e1ebbe248…
- - - - -
9cbb3ef5 by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Mark T12497 as fixed
Thanks to the LLVM toolchain update.
Closes #22694.
- - - - -
2854407e by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Accept new output of T11223_link_order_a_b_2_fail on Windows
The archive member number changed due to the fact that llvm-ar now uses a
string table.
- - - - -
28439593 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/linker/PEi386: Implement IMAGE_REL_AMD64_SECREL
This appears to now be used by libc++ as distributed by msys2.
- - - - -
2b053755 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Cleanup merge resolution residue in lookupSymbolInDLL_PEi386 and make safe without dependent
- - - - -
e8acd2e7 by Wen Kokke at 2025-07-16T08:37:04-04:00
Remove the `profile_id` parameter from various RTS functions.
Various RTS functions took a `profile_id` parameter, intended to be used to
distinguish parallel heap profile breakdowns (e.g., `-hT` and `-hi`). However,
this feature was never implemented and the `profile_id` parameter was set to 0
throughout the RTS. This commit removes the parameter but leaves the hardcoded
profile ID in the functions that emit the encoded eventlog events as to not
change the protocol.
The affected functions are `traceHeapProfBegin`, `postHeapProfBegin`,
`traceHeapProfSampleString`, `postHeapProfSampleString`,
`traceHeapProfSampleCostCentre`, and `postHeapProfSampleCostCentre`.
- - - - -
76d392a2 by Wen Kokke at 2025-07-16T08:37:04-04:00
Make `traceHeapProfBegin` an init event.
- - - - -
bbaa44a7 by Peng Fan at 2025-07-16T16:50:42-04:00
NCG/LA64: Support finer-grained DBAR hints
For LA664 and newer uarchs, they have made finer granularity hints
available:
Bit4: ordering or completion (0: completion, 1: ordering)
Bit3: barrier for previous read (0: true, 1: false)
Bit2: barrier for previous write (0: true, 1: false)
Bit1: barrier for succeeding read (0: true, 1: false)
Bit0: barrier for succeeding write (0: true, 1: false)
And not affect the existing models because other hints are treated
as 'dbar 0' there.
- - - - -
7da86e16 by Andreas Klebinger at 2025-07-16T16:51:25-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
- - - - -
7ee22fd5 by ARATA Mizuki at 2025-07-17T06:05:30-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
c6cd2da1 by Jappie Klooster at 2025-07-17T06:06:20-04:00
Update interact docs to explain about buffering
We need to tell the user to set to the
appropriate buffer format.
Otherwise, this function may get randomly stuck,
or just behave confusingly.
issue: https://gitlab.haskell.org/ghc/ghc/-/issues/26131
NB, I'm running this with cabal *NOT* ghci. ghci messes with buffering anyway.
```haskell
interaction :: String -> String
interaction "jappie" = "hi"
interaction "jakob" = "hello"
interaction x = "unkown input: " <> x
main :: IO ()
main = interact interaction
```
so in my input (prefixed by `>`) I get:
```
> jappie
unkown input: jappie
```
we confirmed later this was due to lack of \n matching.
Anyway movnig on to more unexpected stuff:
```haskell
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
get's stuck forever.
actually `^D` (ctrl+d) unstucks it and runs all input as expected.
for example you can get:
```
> sdfkds
> fakdsf
unkown input: sdfkdsunkown input: fakdsf
```
This program works!
```haskell
interaction :: String -> String
interaction "jappie" = "hi \n"
interaction "jakob" = "hello \n"
interaction x = "unkown input: " <> x <> "\n"
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
the reason is that linebuffering is set for both in and output by default.
so lines eats the input lines, and all the \n postfixes make sure the buffer
is put out.
- - - - -
9fa590a6 by Zubin Duggal at 2025-07-17T06:07:03-04:00
fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory
Fixes #24093
- - - - -
cc650b4b by Andrew Lelechenko at 2025-07-17T12:30:24-04:00
Add Data.List.NonEmpty.mapMaybe
As per https://github.com/haskell/core-libraries-committee/issues/337
- - - - -
360fa82c by Duncan Coutts at 2025-07-17T12:31:14-04:00
base: Deprecate GHC.Weak.Finalize.runFinalizerBatch
https://github.com/haskell/core-libraries-committee/issues/342
- - - - -
f4e8466c by Alan Zimmerman at 2025-07-17T12:31:55-04:00
EPA: Update exact printing based on GHC 9.14 tests
As a result of migrating the GHC ghc-9.14 branch tests to
ghc-exactprint in
https://github.com/alanz/ghc-exactprint/tree/ghc-9.14, a couple of
discrepancies were picked up
- The opening paren for a DefaultDecl was printed in the wrong place
- The import declaration level specifiers were not printed.
This commit adds those fixes, and some tests for them.
The tests brought to light that the ImportDecl ppr instance had not
been updated for level specifiers, so it updates that too.
- - - - -
8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00
level imports: Fix infinite loop with cyclic module imports
I didn't anticipate that downsweep would run before we checked for
cyclic imports. Therefore we need to use the reachability function which
handles cyclic graphs.
Fixes #26087
- - - - -
d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00
Fix documentation about deriving from generics
- - - - -
f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00
Fix issues with toRational for types capable to represent infinite and not-a-number values
This commit fixes all of the following pitfalls:
> toRational (read "Infinity" :: Double)
179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1
> toRational (read "NaN" :: Double)
269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
> realToFrac (read "NaN" :: Double) -- With -O0
Infinity
> realToFrac (read "NaN" :: Double) -- With -O1
NaN
> realToFrac (read "NaN" :: Double) :: CDouble
Infinity
> realToFrac (read "NaN" :: CDouble) :: Double
Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338
- - - - -
5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
- - - - -
9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00
template haskell: use a precise condition when implicitly lifting
Implicit lifting corrects a level error by replacing references to `x`
with `$(lift x)`, therefore you can use a level `n` binding at level `n
+ 1`, if it can be lifted.
Therefore, we now have a precise check that the use level is 1 more than
the bind level.
Before this bug was not observable as you only had 0 and 1 contexts but
it is easily evident when using explicit level imports.
Fixes #26088
- - - - -
5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
- - - - -
c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag for -fexpose-overloaded-unfoldings
Fixes #26112
- - - - -
49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00
Refactor GHC.Driver.Errors.printMessages
- - - - -
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-04:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
- - - - -
0a583689 by Sylvain Henry at 2025-07-24T16:20:26-04:00
STM: don't create a transaction in the rhs of catchRetry# (#26028)
We don't need to create a transaction for the rhs of (catchRetry#)
because contrary to the lhs we don't need to abort it on retry. Moreover
it is particularly harmful if we have code such as (#26028):
let cN = readTVar vN >> retry
tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...))
atomically tree
Because it will stack transactions for the rhss and the read-sets of all
the transactions will be iteratively merged in O(n^2) after the
execution of the most nested retry.
- - - - -
a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Refactor of Specialise.hs
This patch just tidies up `specHeader` a bit, removing one
of its many results, and adding some comments.
No change in behaviour.
Also add a few more `HasDebugCallStack` contexts.
- - - - -
1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* I improved `solveOneFromTheOther` to account for rewriter sets. Previously
it would solve a non-rewritten dict from a rewritten one. For equalities
we were already dealing with this, in
Some incidental refactoring
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
* GHC.Core.FVs.exprFVs now returns /all/ free vars.
Use `exprLocalFVs` for Local vars.
Reason: I wanted another variant for /evidence/ variables.
* Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.)
Rename `isEvVar` to `isEvId`.
* I moved `inert_safehask` out of `InertCans` and into `InertSet` where it
more properly belongs.
Compiler-perf changes:
* There was a palpable bug (#26117) which this MR fixes in
newWantedEvVar, which bypassed all the subtle overlapping-Given
and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this
but leads to extra dictionary bindings; they are optimised away quickly
but they made CoOpt_Read allocate 3.6% more.
* Hpapily T15164 improves.
* The net compiler-allocation change is 0.0%
Metric Decrease:
T15164
Metric Increase:
CoOpt_Read
T12425
- - - - -
953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Solve forall-constraints immediately, or not at all
This MR refactors the constraint solver to solve forall-constraints immediately,
rather than emitting an implication constraint to be solved later.
The most immediate motivation was that when solving quantified constraints
in SPECIALISE pragmas, we really really don't want to leave behind half-
solved implications. Also it's in tune with the approach of the new
short-cut solver, which recursively invokes the solver.
It /also/ saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler. Much nicer.
It also improves error messages a bit.
All described in Note [Solving a Wanted forall-constraint] in
GHC.Tc.Solver.Solve.
One tiresome point: in the tricky case of `inferConstraintsCoerceBased`
we make a forall-constraint. This we /do/ want to partially solve, so
we can infer a suitable context. (I'd be quite happy to force the user to
write a context, bt I don't want to change behavior.) So we want to generate
an /implication/ constraint in `emitPredSpecConstraints` rather than a
/forall-constraint/ as we were doing before. Discussed in (WFA3) of
the above Note.
Incidental refactoring
* `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for
the DerivEnv that the caller had just consulted. Nicer to pass it as an
argument I think, so I have done that. No change in behaviour.
- - - - -
6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Remove duplicated code in Ast.hs for evTermFreeVars
This is just a tidy up.
- - - - -
1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Small tc-tracing changes only
- - - - -
0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00
Respect `-fdiagnostics-as-json` for core diagnostics (see #24113)
- - - - -
cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00
docs: add since pragma to Data.List.NonEmpty.mapMaybe
- - - - -
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
On i386-linux:
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
bf03bbaa by Simon Hengel at 2025-08-01T04:39:05-04:00
Don't use MCDiagnostic for `ghcExit`
This changes the error message of `ghcExit` from
```
<no location info>: error:
Compilation had errors
```
to
```
Compilation had errors
```
- - - - -
a889ec75 by Simon Hengel at 2025-08-01T04:39:05-04:00
Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113)
- - - - -
70f6f73f by Teo Camarasu at 2025-08-02T22:03:22+01:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
- - - - -
30ad77f3 by Teo Camarasu at 2025-08-02T22:03:23+01:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
222 changed files:
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Logger.hs
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/profiling.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/win32-dlls.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Generics.hs
- libraries/base/src/GHC/Weak/Finalize.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- m4/find_ld.m4
- mk/get-win32-tarballs.py
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/Messages.c
- rts/PrimOps.cmm
- rts/ProfHeap.c
- rts/RaiseAsync.c
- rts/RetainerSet.c
- rts/RtsFlags.c
- rts/STM.c
- rts/Timer.c
- rts/Trace.c
- rts/Trace.h
- rts/eventlog/EventLog.c
- rts/eventlog/EventLog.h
- rts/include/rts/Flags.h
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/Sanity.c
- testsuite/tests/corelint/T21115b.stderr
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/deriving/should_compile/T20815.hs
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/dmdanal/should_compile/T23398.hs
- testsuite/tests/dmdanal/should_compile/T23398.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/haddock/haddock_testsuite/Makefile
- + testsuite/tests/haddock/haddock_testsuite/T26114.hs
- + testsuite/tests/haddock/haddock_testsuite/T26114.stdout
- testsuite/tests/haddock/haddock_testsuite/all.T
- testsuite/tests/hiefile/should_run/HieQueries.stdout
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/lib/stm/T26028.hs
- + testsuite/tests/lib/stm/T26028.stdout
- + testsuite/tests/lib/stm/all.T
- testsuite/tests/numeric/should_run/T9810.stdout
- + testsuite/tests/perf/should_run/SpecTyFamRun.hs
- + testsuite/tests/perf/should_run/SpecTyFamRun.stdout
- + testsuite/tests/perf/should_run/SpecTyFam_Import.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/TestLevelImports.hs
- + testsuite/tests/printer/TestNamedDefaults.hs
- testsuite/tests/printer/all.T
- testsuite/tests/quantified-constraints/T15290a.stderr
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/all.T
- testsuite/tests/rts/flags/all.T
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/doublex2_shuffle.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle.stdout
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.stdout
- + testsuite/tests/simplCore/should_compile/T26051.hs
- + testsuite/tests/simplCore/should_compile/T26051.stderr
- + testsuite/tests/simplCore/should_compile/T26051_Import.hs
- + testsuite/tests/simplCore/should_compile/T26115.hs
- + testsuite/tests/simplCore/should_compile/T26115.stderr
- + testsuite/tests/simplCore/should_compile/T26116.hs
- + testsuite/tests/simplCore/should_compile/T26116.stderr
- + testsuite/tests/simplCore/should_compile/T26117.hs
- + testsuite/tests/simplCore/should_compile/T26117.stderr
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/splice-imports/T26087.stderr
- + testsuite/tests/splice-imports/T26087A.hs
- + testsuite/tests/splice-imports/T26087B.hs
- + testsuite/tests/splice-imports/T26088.stderr
- + testsuite/tests/splice-imports/T26088A.hs
- + testsuite/tests/splice-imports/T26088B.hs
- testsuite/tests/splice-imports/all.T
- testsuite/tests/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_fail/T14605.hs
- testsuite/tests/typecheck/should_fail/T14605.stderr
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T18640a.stderr
- testsuite/tests/typecheck/should_fail/T18640b.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T21530b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/tcfail174.stderr
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e734fb21a6e6cf6ca2a9444d1984d5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e734fb21a6e6cf6ca2a9444d1984d5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0