[Git][ghc/ghc][wip/tsan/codegen] 59 commits: Add unsafePtrEquality# restricted to UnliftedTypes

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Dec 5 23:43:57 UTC 2022



Ben Gamari pushed to branch wip/tsan/codegen at Glasgow Haskell Compiler / GHC


Commits:
9d61c182 by Oleg Grenrus at 2022-11-22T15:59:34-05:00
Add unsafePtrEquality# restricted to UnliftedTypes

- - - - -
e817c871 by Jonathan Dowland at 2022-11-22T16:00:14-05:00
utils/unlit: adjust parser to match Report spec

The Haskell 2010 Report says that, for Latex-style Literate format,
"Program code begins on the first line following a line that begins
\begin{code}". (This is unchanged from the 98 Report)

However the unlit.c implementation only matches a line that contains
"\begin{code}" and nothing else. One consequence of this is that one
cannot suffix Latex options to the code environment. I.e., this does
not work:

\begin{code}[label=foo,caption=Foo Code]

Adjust the matcher to conform to the specification from the Report.

The Haskell Wiki currently recommends suffixing a '%' to \begin{code}
in order to deliberately hide a code block from Haskell. This is bad
advice, as it's relying on an implementation quirk rather than specified
behaviour. None-the-less, some people have tried to use it, c.f.
<https://mail.haskell.org/pipermail/haskell-cafe/2009-September/066780.html>

An alternative solution is to define a separate, equivalent Latex
environment to "code", that is functionally identical in Latex but
ignored by unlit. This should not be a burden: users are required to
manually define the code environment anyway, as it is not provided
by the Latex verbatim or lstlistings packages usually used for
presenting code in documents.

Fixes #3549.

- - - - -
0b7fef11 by Teo Camarasu at 2022-11-23T12:44:33-05:00
Fix eventlog all option

Previously it didn't enable/disable nonmoving_gc and ticky event types

Fixes #21813

- - - - -
04d0618c by Arnaud Spiwack at 2022-11-23T12:45:14-05:00
Expand Note [Linear types] with the stance on linting linearity

Per the discussion on #22123

- - - - -
e1538516 by Lawton Nichols at 2022-11-23T12:45:55-05:00
Add documentation on custom Prelude modules (#22228)

Specifically, custom Prelude modules that are named `Prelude`.

- - - - -
b5c71454 by Sylvain Henry at 2022-11-23T12:46:35-05:00
Don't let configure perform trivial substitutions (#21846)

Hadrian now performs substitutions, especially to generate .cabal files
from .cabal.in files. Two benefits:

1. We won't have to re-configure when we modify thing.cabal.in. Hadrian
   will take care of this for us.

2. It paves the way to allow the same package to be configured
   differently by Hadrian in the same session. This will be useful to
   fix #19174: we want to build a stage2 cross-compiler for the host
   platform and a stage1 compiler for the cross target platform in the
   same Hadrian session.

- - - - -
99aca26b by nineonine at 2022-11-23T12:47:11-05:00
CApiFFI: add ConstPtr for encoding const-qualified pointer return types (#22043)

Previously, when using `capi` calling convention in foreign declarations,
code generator failed to handle const-cualified pointer return types.
This resulted in CC toolchain throwing `-Wincompatible-pointer-types-discards-qualifiers`
warning.

`Foreign.C.Types.ConstPtr` newtype was introduced to handle these cases -
special treatment was put in place to generate appropritetly qualified C
wrapper that no longer triggers the above mentioned warning.

Fixes #22043

- - - - -
040bfdc3 by M Farkas-Dyck at 2022-11-23T21:59:03-05:00
Scrub some no-warning pragmas.

- - - - -
178c1fd8 by Vladislav Zavialov at 2022-11-23T21:59:39-05:00
Check if the SDoc starts with a single quote (#22488)

This patch fixes pretty-printing of character literals
inside promoted lists and tuples.

When we pretty-print a promoted list or tuple whose first element
starts with a single quote, we want to add a space between the opening
bracket and the element:

	'[True]    -- ok
	'[ 'True]  -- ok
	'['True]   -- not ok

If we don't add the space, we accidentally produce a character
literal '['.

Before this patch, pprSpaceIfPromotedTyCon inspected the type as an AST
and tried to guess if it would be rendered with a single quote. However,
it missed the case when the inner type was itself a character literal:

	'[ 'x']  -- ok
	'['x']   -- not ok

Instead of adding this particular case, I opted for a more future-proof
solution: check the SDoc directly. This way we can detect if the single
quote is actually there instead of trying to predict it from the AST.
The new function is called spaceIfSingleQuote.

- - - - -
11627c42 by Matthew Pickering at 2022-11-23T22:00:15-05:00
notes: Fix references to HPT space leak note

Updating this note was missed when updating the HPT to the HUG.

Fixes #22477

- - - - -
86ff1523 by Andrei Borzenkov at 2022-11-24T17:24:51-05:00
Convert diagnostics in GHC.Rename.Expr to proper TcRnMessage (#20115)

Problem: avoid usage of TcRnMessageUnknown

Solution:
The following `TcRnMessage` messages has been introduced:
  TcRnNoRebindableSyntaxRecordDot
  TcRnNoFieldPunsRecordDot
  TcRnIllegalStaticExpression
  TcRnIllegalStaticFormInSplice
  TcRnListComprehensionDuplicateBinding
  TcRnEmptyStmtsGroup
  TcRnLastStmtNotExpr
  TcRnUnexpectedStatementInContext
  TcRnIllegalTupleSection
  TcRnIllegalImplicitParameterBindings
  TcRnSectionWithoutParentheses

Co-authored-by: sheaf <sam.derbyshire at gmail.com>

- - - - -
d198a19a by Cheng Shao at 2022-11-24T17:25:29-05:00
rts: fix missing Arena.h symbols in RtsSymbols.c

It was an unfortunate oversight in !8961 and broke devel2 builds.

- - - - -
5943e739 by Bodigrim at 2022-11-25T04:38:28-05:00
Assorted fixes to avoid Data.List.{head,tail}

- - - - -
1f1b99b8 by sheaf at 2022-11-25T04:38:28-05:00
Review suggestions for assorted fixes to avoid Data.List.{head,tail}

- - - - -
13d627bb by Vladislav Zavialov at 2022-11-25T04:39:04-05:00
Print unticked promoted data constructors (#20531)

Before this patch, GHC unconditionally printed ticks before promoted
data constructors:

	ghci> type T = True  -- unticked (user-written)
	ghci> :kind! T
	T :: Bool
	= 'True              -- ticked (compiler output)

After this patch, GHC prints ticks only when necessary:

	ghci> type F = False    -- unticked (user-written)
	ghci> :kind! F
	F :: Bool
	= False                 -- unticked (compiler output)

	ghci> data False        -- introduce ambiguity
	ghci> :kind! F
	F :: Bool
	= 'False                -- ticked by necessity (compiler output)

The old behavior can be enabled by -fprint-redundant-promotion-ticks.

Summary of changes:
* Rename PrintUnqualified to NamePprCtx
* Add QueryPromotionTick to it
* Consult the GlobalRdrEnv to decide whether to print a tick (see mkPromTick)
* Introduce -fprint-redundant-promotion-ticks

Co-authored-by: Artyom Kuznetsov <hi at wzrd.ht>

- - - - -
d10dc6bd by Simon Peyton Jones at 2022-11-25T22:31:27+00:00
Fix decomposition of TyConApps

Ticket #22331 showed that we were being too eager to decompose
a Wanted TyConApp, leading to incompleteness in the solver.

To understand all this I ended up doing a substantial rewrite
of the old Note [Decomposing equalities], now reborn as
Note [Decomposing TyConApp equalities]. Plus rewrites of other
related Notes.

The actual fix is very minor and actually simplifies the code: in
`can_decompose` in `GHC.Tc.Solver.Canonical.canTyConApp`, we now call
`noMatchableIrreds`.  A closely related refactor: we stop trying to
use the same "no matchable givens" function here as in
`matchClassInst`.  Instead split into two much simpler functions.

- - - - -
2da5c38a by Will Hawkins at 2022-11-26T04:05:04-05:00
Redirect output of musttail attribute test

Compilation output from test for support of musttail attribute leaked to
the console.

- - - - -
0eb1c331 by Cheng Shao at 2022-11-28T08:55:53+00:00
Move hs_mulIntMayOflo cbits to ghc-prim

It's only used by wasm NCG at the moment, but ghc-prim is a more
reasonable place for hosting out-of-line primops. Also, we only need a
single version of hs_mulIntMayOflo.

- - - - -
36b53a9d by Cheng Shao at 2022-11-28T09:05:57+00:00
compiler: generate ccalls for clz/ctz/popcnt in wasm NCG

We used to generate a single wasm clz/ctz/popcnt opcode, but it's
wrong when it comes to subwords, so might as well generate ccalls for
them. See #22470 for details.

- - - - -
d4134e92 by Cheng Shao at 2022-11-28T23:48:14-05:00
compiler: remove unused MO_U_MulMayOflo

We actually only emit MO_S_MulMayOflo and never emit MO_U_MulMayOflo anywhere.

- - - - -
8d15eadc by Apoorv Ingle at 2022-11-29T03:09:31-05:00
Killing cc_fundeps, streamlining kind equality orientation, and type equality processing order

Fixes: #217093
Associated to #19415

This change
* Flips the orientation of the the generated kind equality coercion in canEqLHSHetero;
* Removes `cc_fundeps` in CDictCan as the check was incomplete;
* Changes `canDecomposableTyConAppOk` to ensure we process kind equalities before type equalities and avoiding a call to `canEqLHSHetero` while processing wanted TyConApp equalities
* Adds 2 new tests for validating the change
   - testsuites/typecheck/should_compile/T21703.hs and
   - testsuites/typecheck/should_fail/T19415b.hs (a simpler version of T19415.hs)
* Misc: Due to the change in the equality direction some error messages now have flipped type mismatch errors
* Changes in Notes:
  - Note [Fundeps with instances, and equality orientation] supercedes Note [Fundeps with instances]
  - Added Note [Kind Equality Orientation] to visualize the kind flipping
  - Added Note [Decomposing Dependent TyCons and Processing Wanted Equalties]

- - - - -
646969d4 by Krzysztof Gogolewski at 2022-11-29T03:10:13-05:00
Change printing of sized literals to match the proposal

Literals in Core were printed as e.g. 0xFF#16 :: Int16#.
The proposal 451 now specifies syntax 0xFF#Int16.
This change affects the Core printer only - more to be done later.

Part of #21422.

- - - - -
02e282ec by Simon Peyton Jones at 2022-11-29T03:10:48-05:00
Be a bit more selective about floating bottoming expressions

This MR arranges to float a bottoming expression to the top
only if it escapes a value lambda.

See #22494 and Note [Floating to the top] in SetLevels.

This has a generally beneficial effect in nofib

+-------------------------------++----------+
|                               ||tsv (rel) |
+===============================++==========+
|           imaginary/paraffins ||   -0.93% |
|                imaginary/rfib ||   -0.05% |
|                      real/fem ||   -0.03% |
|                    real/fluid ||   -0.01% |
|                   real/fulsom ||   +0.05% |
|                   real/gamteb ||   -0.27% |
|                       real/gg ||   -0.10% |
|                   real/hidden ||   -0.01% |
|                      real/hpg ||   -0.03% |
|                      real/scs ||  -11.13% |
|         shootout/k-nucleotide ||   -0.01% |
|               shootout/n-body ||   -0.08% |
|   shootout/reverse-complement ||   -0.00% |
|        shootout/spectral-norm ||   -0.02% |
|             spectral/fibheaps ||   -0.20% |
|           spectral/hartel/fft ||   -1.04% |
|         spectral/hartel/solid ||   +0.33% |
|     spectral/hartel/wave4main ||   -0.35% |
|                 spectral/mate ||   +0.76% |
+===============================++==========+
|                     geom mean ||   -0.12% |

The effect on compile time is generally slightly beneficial

Metrics: compile_time/bytes allocated
----------------------------------------------
MultiLayerModulesTH_OneShot(normal)  +0.3%
                  PmSeriesG(normal)  -0.2%
                  PmSeriesT(normal)  -0.1%
                     T10421(normal)  -0.1%
                    T10421a(normal)  -0.1%
                     T10858(normal)  -0.1%
                     T11276(normal)  -0.1%
                    T11303b(normal)  -0.2%
                     T11545(normal)  -0.1%
                     T11822(normal)  -0.1%
                     T12150(optasm)  -0.1%
                     T12234(optasm)  -0.3%
                     T13035(normal)  -0.2%
                     T16190(normal)  -0.1%
                     T16875(normal)  -0.4%
                    T17836b(normal)  -0.2%
                     T17977(normal)  -0.2%
                    T17977b(normal)  -0.2%
                     T18140(normal)  -0.1%
                     T18282(normal)  -0.1%
                     T18304(normal)  -0.2%
                    T18698a(normal)  -0.1%
                     T18923(normal)  -0.1%
                     T20049(normal)  -0.1%
                    T21839r(normal)  -0.1%
                      T5837(normal)  -0.4%
                      T6048(optasm)  +3.2% BAD
                      T9198(normal)  -0.2%
                      T9630(normal)  -0.1%
       TcPlugin_RewritePerf(normal)  -0.4%
             hard_hole_fits(normal)  -0.1%

                          geo. mean  -0.0%
                          minimum    -0.4%
                          maximum    +3.2%

The T6048 outlier is hard to pin down, but it may be the effect of
reading in more interface files definitions. It's a small program for
which compile time is very short, so I'm not bothered about it.

Metric Increase:
    T6048

- - - - -
ab23dc5e by Ben Gamari at 2022-11-29T03:11:25-05:00
testsuite: Mark unpack_sums_6 as fragile due to #22504

This test is explicitly dependent upon runtime, which is generally not
appropriate given that the testsuite is run in parallel and generally
saturates the CPU.

- - - - -
def47dd3 by Ben Gamari at 2022-11-29T03:11:25-05:00
testsuite: Don't use grep -q in unpack_sums_7

`grep -q` closes stdin as soon as it finds the pattern it is looking
for, resulting in #22484.

- - - - -
cc25d52e by Sylvain Henry at 2022-11-29T09:44:31+01:00
Add Javascript backend

Add JS backend adapted from the GHCJS project by Luite Stegeman.

Some features haven't been ported or implemented yet. Tests for these
features have been disabled with an associated gitlab ticket.

Bump array submodule

Work funded by IOG.

Co-authored-by: Jeffrey Young <jeffrey.young at iohk.io>
Co-authored-by: Luite Stegeman <stegeman at gmail.com>
Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com>

- - - - -
68c966cd by sheaf at 2022-11-30T09:31:25-05:00
Fix @since annotations on WithDict and Coercible

Fixes #22453

- - - - -
a3a8e9e9 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00
Be more careful in GHC.Tc.Solver.Interact.solveOneFromTheOther

We were failing to account for the cc_pend_sc flag in this
important function, with the result that we expanded superclasses
forever.

Fixes #22516.

- - - - -
a9d9b8c0 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00
Use mkNakedFunTy in tcPatSynSig

As #22521 showed, in tcPatSynSig we make a "fake type" to
kind-generalise; and that type has unzonked type variables in it. So
we must not use `mkFunTy` (which checks FunTy's invariants) via
`mkPhiTy` when building this type.  Instead we need to use
`mkNakedFunTy`.

Easy fix.

- - - - -
31462d98 by Andreas Klebinger at 2022-11-30T14:50:58-05:00
Properly cast values when writing/reading unboxed sums.

Unboxed sums might store a Int8# value as Int64#. This patch
makes sure we keep track of the actual value type.

See Note [Casting slot arguments] for the details.

- - - - -
10a2a7de by Oleg Grenrus at 2022-11-30T14:51:39-05:00
Move Void to GHC.Base...

This change would allow `Void` to be used deeper in module graph.
For example exported from `Prelude` (though that might be already
possible).

Also this change includes a change `stimes @Void _ x = x`,
https://github.com/haskell/core-libraries-committee/issues/95

While the above is not required, maintaining old stimes behavior
would be tricky as `GHC.Base` doesn't know about `Num` or `Integral`,
which would require more hs-boot files.

- - - - -
b4cfa8e2 by Sebastian Graf at 2022-11-30T14:52:24-05:00
DmdAnal: Reflect the `seq` of strict fields of a DataCon worker (#22475)

See the updated `Note [Data-con worker strictness]`
and the new `Note [Demand transformer for data constructors]`.

Fixes #22475.

- - - - -
d87f28d8 by Baldur Blöndal at 2022-11-30T21:16:36+01:00
Make Functor a quantified superclass of Bifunctor.

See https://github.com/haskell/core-libraries-committee/issues/91 for
discussion.

This change relates Bifunctor with Functor by requiring second = fmap.
Moreover this change is a step towards unblocking the major version bump
of bifunctors and profunctors to major version 6. This paves the way to
move the Profunctor class into base. For that Functor first similarly
becomes a superclass of Profunctor in the new major version 6.

- - - - -
72cf4c5d by doyougnu at 2022-12-01T12:36:44-05:00
FastString: SAT bucket_match

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
afc2540d by Simon Peyton Jones at 2022-12-01T12:37:20-05:00
Add a missing varToCoreExpr in etaBodyForJoinPoint

This subtle bug showed up when compiling a library with 9.4.
See #22491.  The bug is present in master, but it is hard to
trigger; the new regression test T22491 fails in 9.4.

The fix was easy: just add a missing varToCoreExpr in
etaBodyForJoinPoint.

The fix is definitely right though!

I also did some other minor refatoring:
* Moved the preInlineUnconditionally test in simplExprF1 to
  before the call to joinPointBinding_maybe, to avoid fruitless
  eta-expansion.
* Added a boolean from_lam flag to simplNonRecE, to avoid two
  fruitless tests, and commented it a bit better.

These refactorings seem to save 0.1% on compile-time allocation in
perf/compiler; with a max saving of 1.4% in T9961

Metric Decrease:
    T9961

- - - - -
81eeec7f by M Farkas-Dyck at 2022-12-01T12:37:56-05:00
CI: Forbid the fully static build on Alpine to fail.

To do so, we mark some tests broken in this configuration.

- - - - -
c5d1bf29 by Bryan Richter at 2022-12-01T12:37:56-05:00
CI: Remove ARMv7 jobs

These jobs fail (and are allowed to fail) nearly every time.

Soon they won't even be able to run at all, as we won't currently have
runners that can run them.

Fixing the latter problem is tracked in #22409.

I went ahead and removed all settings and configurations.

- - - - -
d82992fd by Bryan Richter at 2022-12-01T12:37:56-05:00
CI: Fix CI lint

Failure was introduced by conflicting changes to gen_ci.hs that did
*not* trigger git conflicts.

- - - - -
ce126993 by Simon Peyton Jones at 2022-12-02T01:22:12-05:00
Refactor TyCon to have a top-level product

This patch changes the representation of TyCon so that it has
a top-level product type, with a field that gives the details
(newtype, type family etc), #22458.

Not much change in allocation, but execution seems to be a bit
faster.

Includes a change to the haddock submodule to adjust for API changes.

- - - - -
74c767df by Matthew Pickering at 2022-12-02T01:22:48-05:00
ApplicativeDo: Set pattern location before running exhaustiveness checker

This improves the error messages of the exhaustiveness checker when
checking statements which have been moved around with ApplicativeDo.

Before:

Test.hs:2:3: warning: [GHC-62161] [-Wincomplete-uni-patterns]
    Pattern match(es) are non-exhaustive
    In a pattern binding:
        Patterns of type ‘Maybe ()’ not matched: Nothing
  |
2 |   let x = ()
  |   ^^^^^^^^^^

After:

Test.hs:4:3: warning: [GHC-62161] [-Wincomplete-uni-patterns]
    Pattern match(es) are non-exhaustive
    In a pattern binding:
        Patterns of type ‘Maybe ()’ not matched: Nothing
  |
4 |   ~(Just res1) <- seq x (pure $ Nothing @())
  |

Fixes #22483

- - - - -
85ecc1a0 by Matthew Pickering at 2022-12-02T19:46:43-05:00
Add special case for :Main module in `GHC.IfaceToCore.mk_top_id`

See Note [Root-main Id]

The `:Main` special binding is actually defined in the current module
(hence don't go looking for it externally) but the module name is rOOT_MAIN
rather than the current module so we need this special case.

There was already some similar logic in `GHC.Rename.Env` for
External Core, but now the "External Core" is in interface files it
needs to be moved here instead.

Fixes #22405

- - - - -
108c319f by Krzysztof Gogolewski at 2022-12-02T19:47:18-05:00
Fix linearity checking in Lint

Lint was not able to see that x*y <= x*y, because this inequality
was decomposed to x <= x*y && y <= x*y, but there was no rule
to see that x <= x*y.

Fixes #22546.

- - - - -
bb674262 by Bryan Richter at 2022-12-03T04:38:46-05:00
Mark T16916 fragile

See https://gitlab.haskell.org/ghc/ghc/-/issues/16966

- - - - -
5d267d46 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00
Refactor: FreshOrReuse instead of addTyClTyVarBinds

This is a refactoring that should have no effect on observable behavior.

Prior to this change, GHC.HsToCore.Quote contained a few closely related
functions to process type variable bindings: addSimpleTyVarBinds,
addHsTyVarBinds, addQTyVarBinds, and addTyClTyVarBinds.

We can classify them by their input type and name generation strategy:

                              Fresh names only    Reuse bound names
                          +---------------------+-------------------+
                   [Name] | addSimpleTyVarBinds |                   |
[LHsTyVarBndr flag GhcRn] |     addHsTyVarBinds |                   |
        LHsQTyVars GhcRn  |      addQTyVarBinds | addTyClTyVarBinds |
                          +---------------------+-------------------+

Note how two functions are missing. Because of this omission, there were
two places where a LHsQTyVars value was constructed just to be able to pass it
to addTyClTyVarBinds:

1. mk_qtvs in addHsOuterFamEqnTyVarBinds    -- bad
2. mkHsQTvs in repFamilyDecl                -- bad

This prevented me from making other changes to LHsQTyVars, so the main
goal of this refactoring is to get rid of those workarounds.

The most direct solution would be to define the missing functions.
But that would lead to a certain amount of code duplication. To avoid
code duplication, I factored out the name generation strategy into a
function parameter:

	data FreshOrReuse
	  = FreshNamesOnly
	  | ReuseBoundNames

	addSimpleTyVarBinds :: FreshOrReuse -> ...
	addHsTyVarBinds     :: FreshOrReuse -> ...
	addQTyVarBinds      :: FreshOrReuse -> ...

- - - - -
c189b831 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00
addHsOuterFamEqnTyVarBinds: use FreshNamesOnly for explicit binders

Consider this example:

	[d| instance forall a. C [a] where
	      type forall b. G [a] b = Proxy b |]

When we process "forall b." in the associated type instance, it is
unambiguously the binding site for "b" and we want a fresh name for it.
Therefore, FreshNamesOnly is more fitting than ReuseBoundNames.
This should not have any observable effect but it avoids pointless
lookups in the MetaEnv.

- - - - -
42512264 by Ross Paterson at 2022-12-03T10:32:45+00:00
Handle type data declarations in Template Haskell quotations and splices (fixes #22500)

This adds a TypeDataD constructor to the Template Haskell Dec type,
and ensures that the constructors it contains go in the TyCls namespace.

- - - - -
1a767fa3 by Vladislav Zavialov at 2022-12-05T05:18:50-05:00
Add BufSpan to EpaLocation (#22319, #22558)

The key part of this patch is the change to mkTokenLocation:

	- mkTokenLocation (RealSrcSpan r _)  = TokenLoc (EpaSpan r)
	+ mkTokenLocation (RealSrcSpan r mb) = TokenLoc (EpaSpan r mb)

mkTokenLocation used to discard the BufSpan, but now it is saved and can
be retrieved from LHsToken or LHsUniToken.

This is made possible by the following change to EpaLocation:

	- data EpaLocation = EpaSpan !RealSrcSpan
	+ data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan)
	                   | ...

The end goal is to make use of the BufSpan in Parser/PostProcess/Haddock.

- - - - -
0927dde4 by Ben Gamari at 2022-12-05T18:42:59-05:00
hadrian: Don't enable TSAN in stage0 build

- - - - -
ade88423 by Ben Gamari at 2022-12-05T18:42:59-05:00
cmm: Introduce blockConcat

- - - - -
4dd2d83f by Ben Gamari at 2022-12-05T18:42:59-05:00
cmm: Introduce MemoryOrderings

- - - - -
e812bb93 by Ben Gamari at 2022-12-05T18:42:59-05:00
llvm: Respect memory specified orderings

- - - - -
cf0915f6 by Ben Gamari at 2022-12-05T18:42:59-05:00
Codegen/x86: Eliminate barrier for relaxed accesses

- - - - -
4e2ae5d2 by Ben Gamari at 2022-12-05T18:42:59-05:00
cmm/Parser: Reduce some repetition

- - - - -
251f8c99 by Ben Gamari at 2022-12-05T18:43:00-05:00
cmm/Parser: Add syntax for ordered loads and stores

- - - - -
699bf77a by Ben Gamari at 2022-12-05T18:43:00-05:00
cmm/Parser: Atomic load syntax

Originally I had thought I would just use the `prim` call syntax instead
of introducing new syntax for atomic loads. However, it turns out that
`prim` call syntax tends to make things quite unreadable. This new
syntax seems quite natural.

- - - - -
65dd69f6 by Ben Gamari at 2022-12-05T18:43:25-05:00
codeGen: Introduce ThreadSanitizer instrumentation

This introduces a new Cmm pass which instruments the program with
ThreadSanitizer annotations, allowing full tracking of mutator memory
accesses via TSAN.

- - - - -
938d6176 by Ben Gamari at 2022-12-05T18:43:26-05:00
Hadrian: Drop TSAN_ENABLED define from flavour

This is redundant since the TSANUtils.h already defines it.

- - - - -
1ee07a55 by Ben Gamari at 2022-12-05T18:43:26-05:00
hadrian: Enable Cmm instrumentation in TSAN flavour

- - - - -
4f85f747 by Ben Gamari at 2022-12-05T18:43:26-05:00
rts: Ensure that global regs are never passed as fun call args

This is in general unsafe as they may be clobbered if they are mapped to
caller-saved machine registers. See Note [Register parameter passing].

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs
- + compiler/GHC/Builtin/PrimOps/Casts.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Config.hs
- compiler/GHC/Cmm/ContFlowOpt.hs
- compiler/GHC/Cmm/Dataflow/Block.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Node.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/ProcPoint.hs
- + compiler/GHC/Cmm/ThreadSanitizer.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/Wasm/Asm.hs
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToAsm/Wasm/Types.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToC.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe44f27593eed7fb00115df0d30ac93481201208...4f85f747b06a3be1591b52c1f15ff6588b8e5764

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe44f27593eed7fb00115df0d30ac93481201208...4f85f747b06a3be1591b52c1f15ff6588b8e5764
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221205/8286538f/attachment-0001.html>


More information about the ghc-commits mailing list