[Git][ghc/ghc][wip/fix-hadrian-ticky] 47 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags

Ben Gamari gitlab at gitlab.haskell.org
Sat Nov 21 20:53:15 UTC 2020



Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC


Commits:
fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00
nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags

It appears this was an oversight as there is no reason the full DynFlags
is necessary.

- - - - -
6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00
Move this_module into NCGConfig

In various places in the NCG we need the Module currently being
compiled. Let's move this into the environment instead of chewing threw
another register.

- - - - -
c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00
codeGen: Produce local symbols for module-internal functions

It turns out that some important native debugging/profiling tools (e.g.
perf) rely only on symbol tables for function name resolution (as
opposed to using DWARF DIEs). However, previously GHC would emit
temporary symbols (e.g. `.La42b`) to identify module-internal
entities. Such symbols are dropped during linking and therefore not
visible to runtime tools (in addition to having rather un-helpful unique
names). For instance, `perf report` would often end up attributing all
cost to the libc `frame_dummy` symbol since Haskell code was no covered
by any proper symbol (see #17605).

We now rather follow the model of C compilers and emit
descriptively-named local symbols for module internal things. Since this
will increase object file size this behavior can be disabled with the
`-fno-expose-internal-symbols` flag.

With this `perf record` can finally be used against Haskell executables.
Even more, with `-g3` `perf annotate` provides inline source code.

- - - - -
584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00
Enable -fexpose-internal-symbols when debug level >=2

This seems like a reasonable default as the object file size increases
by around 5%.

- - - - -
c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00
Fix and enable object unloading in GHCi

Fixes #16525 by tracking dependencies between object file symbols and
marking symbol liveness during garbage collection

See Note [Object unloading] in CheckUnload.c for details.

- - - - -
2782487f by Ray Shih at 2020-11-11T03:20:35-05:00
Add loadNativeObj and unloadNativeObj

(This change is originally written by niteria)

This adds two functions:
* `loadNativeObj`
* `unloadNativeObj`
and implements them for Linux.

They are useful if you want to load a shared object with Haskell code
using the system linker and have GHC call dlclose() after the
code is no longer referenced from the heap.

Using the system linker allows you to load the shared object
above outside the low-mem region. It also loads the DWARF sections
in a way that `perf` understands.

`dl_iterate_phdr` is what makes this implementation Linux specific.

- - - - -
7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00
rts: Introduce highMemDynamic

- - - - -
e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00
Introduce test for dynamic library unloading

This uses the highMemDynamic flag introduced earlier to verify that
dynamic objects are properly unloaded.

- - - - -
5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00
Force argument in setIdMult (#18925)

- - - - -
787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00
testsuite: Add testcase for #18733

- - - - -
5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00
compiler: Fix recompilation checking

In ticket #18733 we noticed a rather serious deficiency in the current
fingerprinting logic for recursive groups. I have described the old
fingerprinting story and its problems in Note [Fingerprinting recursive
groups] and have reworked the story accordingly to avoid these issues.

Fixes #18733.

- - - - -
63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00
Arity: Rework `ArityType` to fix monotonicity (#18870)

As we found out in #18870, `andArityType` is not monotone, with
potentially severe consequences for termination of fixed-point
iteration. That showed in an abundance of "Exciting arity" DEBUG
messages that are emitted whenever we do more than one step in
fixed-point iteration.

The solution necessitates also recording `OneShotInfo` info for
`ABot` arity type. Thus we get the following definition for `ArityType`:

```
data ArityType = AT [OneShotInfo] Divergence
```

The majority of changes in this patch are the result of refactoring use
sites of `ArityType` to match the new definition.

The regression test `T18870` asserts that we indeed don't emit any DEBUG
output anymore for a function where we previously would have.
Similarly, there's a regression test `T18937` for #18937, which we
expect to be broken for now.

Fixes #18870.

- - - - -
197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00
Arity: Emit "Exciting arity" warning only after second iteration (#18937)

See Note [Exciting arity] why we emit the warning at all and why we only
do after the second iteration now.

Fixes #18937.

- - - - -
de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00
Add rts_listThreads and rts_listMiscRoots to RtsAPI.h

These are used to find the current roots of the garbage collector.

Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com>
Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com>
Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com>

- - - - -
24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00
gitlab-ci: Cache cabal store in linting job

- - - - -
0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00
nativeGen/dwarf: Fix procedure end addresses

Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF
information would claim that procedures (represented with a
`DW_TAG_subprogram` DIE) would only span the range covered by their entry
block. This omitted all of the continuation blocks (represented by
`DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing
a end-of-procedure label and using this as the `DW_AT_high_pc` of
procedure `DW_TAG_subprogram` DIEs

Fixes #17605.

- - - - -
1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00
nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3

Standard debugging tools don't know how to understand these so let's not
produce them unless asked.

- - - - -
ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00
nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage

- - - - -
a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00
gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27

- - - - -
d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00
Name (tc)SplitForAll- functions more consistently

There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as
`tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar
things, but vary in the particular form of type variable that they return. To
make things worse, the names of these functions are often quite misleading.
Some particularly egregious examples:

* `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns
  `VarBndr`s.
* `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns
  `TyVar`s.
* `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns
  `InvisTVBinder`s. (This in particular arose in the context of #18939, and
  this finally motivated me to bite the bullet and improve the status quo
  vis-à-vis how we name these functions.)

In an attempt to bring some sanity to how these functions are named, I have
opted to rename most of these functions en masse to use consistent suffixes
that describe the particular form of type variable that each function returns.
In concrete terms, this amounts to:

* Functions that return a `TyVar` now use the suffix `-TyVar`.
  This caused the following functions to be renamed:
  * `splitTyVarForAllTys` -> `splitForAllTyVars`
  * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe`
  * `tcSplitForAllTys` -> `tcSplitForAllTyVars`
  * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars`
* Functions that return a `CoVar` now use the suffix `-CoVar`.
  This caused the following functions to be renamed:
  * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe`
* Functions that return a `TyCoVar` now use the suffix `-TyCoVar`.
  This caused the following functions to be renamed:
  * `splitForAllTy` -> `splitForAllTyCoVar`
  * `splitForAllTys` -> `splitForAllTyCoVars`
  * `splitForAllTys'` -> `splitForAllTyCoVars'`
  * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe`
* Functions that return a `VarBndr` now use the suffix corresponding to the
  most relevant type synonym. This caused the following functions to be renamed:
  * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders`
  * `splitForAllTysInvis` -> `splitForAllInvisTVBinders`
  * `splitForAllTysReq` -> `splitForAllReqTVBinders`
  * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs`
  * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders`
  * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders`
  * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders`
  * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe`

Note that I left the following functions alone:

* Functions that split apart things besides `ForAllTy`s, such as `splitFunTys`
  or `splitPiTys`. Thankfully, there are far fewer of these functions than
  there are functions that split apart `ForAllTy`s, so there isn't much of a
  pressing need to apply the new naming convention elsewhere.
* Functions that split apart `ForAllCo`s in `Coercion`s, such as
  `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new
  naming convention here, but then we'd have to figure out how to disambiguate
  `Type`-splitting functions from `Coercion`-splitting functions. Ultimately,
  the `Coercion`-splitting functions aren't used nearly as much as the
  `Type`-splitting functions, so I decided to leave the former alone.

This is purely refactoring and should cause no change in behavior.

- - - - -
645444af by Ryan Scott at 2020-11-15T03:36:21-05:00
Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places

The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate
cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars`
function (which behaves like `tcSplitForAllTyVars` but only splits invisible
type variables) fixes the issue. However, this led me to realize that _most_
uses of `tcSplitForAllTyVars` in GHC really ought to be
`tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace
most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the
likelihood of such bugs in the future.

I say "most uses" above since there is one notable place where we _do_ want
to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces
the "`Illegal polymorphic type`" error message if you try to use a higher-rank
`forall` without having `RankNTypes` enabled. Here, we really do want to split
all `forall`s, not just invisible ones, or we run the risk of giving an
inaccurate error message in the newly added `T18939_Fail` test case.

I debated at some length whether I wanted to name the new function
`tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end,
I decided that I liked the former better. For consistency's sake, I opted to
rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions
to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the
same naming convention. As a consequence, this ended up requiring a `haddock`
submodule bump.

Fixes #18939.

- - - - -
8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00
AArch64/arm64 adjustments

This addes the necessary logic to support aarch64 on elf, as well
as aarch64 on mach-o, which Apple calls arm64.

We change architecture name to AArch64, which is the official arm
naming scheme.

- - - - -
fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00
ghc-bin: Build with eventlogging by default

We now have all sorts of great facilities using the
eventlog which were previously unavailable without
building a custom GHC. Fix this by linking with
`-eventlog` by default.
- - - - -
52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00
Add Addr# atomic primops (#17751)

This reuses the codegen used for ByteArray#'s atomic primops.

- - - - -
8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00
PmCheck: Print types of uncovered patterns (#18932)

In order to avoid confusion as in #18932, we display the type of the
match variables in the non-exhaustiveness warning, e.g.

```
T18932.hs:14:1: warning: [-Wincomplete-patterns]
    Pattern match(es) are non-exhaustive
    In an equation for ‘g’:
        Patterns of type  ‘T a’, ‘T a’, ‘T a’ not matched:
            (MkT2 _) (MkT1 _) (MkT1 _)
            (MkT2 _) (MkT1 _) (MkT2 _)
            (MkT2 _) (MkT2 _) (MkT1 _)
            (MkT2 _) (MkT2 _) (MkT2 _)
            ...
   |
14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x
   | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
```

It also allows us to omit the type signature on wildcard matches which
we previously showed in only some situations, particularly
`-XEmptyCase`.

Fixes #18932.

- - - - -
165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00
Export indexError from GHC.Ix (#18579)

- - - - -
b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00
Clarify interruptible FFI wrt masking state

- - - - -
321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00
Fix strictness signatures of `prefetchValue*#` primops

Their strictness signatures said the primops are strict in their first
argument, which is wrong: Handing it a thunk will prefetch the pointer
to the thunk, but not evaluate it. Hence not strict.

The regression test `T8256` actually tests for laziness in the first
argument, so GHC apparently never exploited the strictness signature.

See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867,
where this came up.

- - - - -
0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00
Demand: Interleave usage and strictness demands (#18903)

As outlined in #18903, interleaving usage and strictness demands not
only means a more compact demand representation, but also allows us to
express demands that we weren't easily able to express before.

Call demands are *relative* in the sense that a call demand `Cn(cd)`
on `g` says "`g` is called `n` times. *Whenever `g` is called*, the
result is used according to `cd`". Example from #18903:

```hs
h :: Int -> Int
h m =
  let g :: Int -> (Int,Int)
      g 1 = (m, 0)
      g n = (2 * n, 2 `div` n)
      {-# NOINLINE g #-}
  in case m of
    1 -> 0
    2 -> snd (g m)
    _ -> uncurry (+) (g m)
```

Without the interleaved representation, we would just get `L` for the
strictness demand on `g`. Now we are able to express that whenever
`g` is called, its second component is used strictly in denoting `g`
by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the
division, for example.

Fixes #18903.
While fixing regressions, I also discovered and fixed #18957.

Metric Decrease:
    T13253-spj

- - - - -
3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00
Update user's guide entry on demand analysis and worker/wrapper

The demand signature notation has been undocumented for a long time.
The only source to understand it, apart from reading the `Outputable`
instance, has been an outdated wiki page.

Since the previous commits have reworked the demand lattice, I took
it as an opportunity to also write some documentation about notation.

- - - - -
fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00
Find hadrian location more reliably in cabal-install output

Fix #18944

- - - - -
9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00
rts/linker: Align bssSize to page size when mapping symbol extras

We place symbol_extras right after bss. We also need
to ensure that symbol_extras can be mprotect'd independently from the
rest of the image. To ensure this we round up the size of bss to a page
boundary, thus ensuring that symbol_extras is also page-aligned.

- - - - -
b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00
gitlab-ci: Add usage message to ci.sh

- - - - -
802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00
gitlab-ci: Add VERBOSE environment variable

And change the make build system's default behavior to V=0, greatly
reducing build log sizes.

- - - - -
2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00
users-guide: A bit of clean-up in profiling flag documentation

- - - - -
56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00
testsuite: Refactor CountParserDeps

- - - - -
53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00
Introduce -fprof-callers flag

This introducing a new compiler flag to provide a convenient way to
introduce profiler cost-centers on all occurrences of the named
identifier.

Closes #18566.

- - - - -
ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00
Move Plugins into HscEnv (#17957)

Loaded plugins have nothing to do in DynFlags so this patch moves them
into HscEnv (session state).

"DynFlags plugins" become "Driver plugins" to still be able to register
static plugins.

Bump haddock submodule

- - - - -
72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00
Don't initialize plugins in the Core2Core pipeline

Some plugins can be added via TH (cf addCorePlugin). Initialize them in
the driver instead of in the Core2Core pipeline.

- - - - -
ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00
Add regression test for #10504

This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a
regression test to ensure that it stays fixed.

Fixes #10504.

- - - - -
a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00
dwarf: Apply info table offset consistently

Previously we failed to apply the info table offset to the aranges and
DIEs, meaning that we often failed to unwind in gdb. For some reason
this only seemed to manifest in the RTS's Cmm closures. Nevertheless,
now we can unwind completely up to `main`

- - - - -
69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00
hadrian: Disable stripping when debug information is enabled

- - - - -
7566dff3 by Ben Gamari at 2020-11-21T15:41:08-05:00
hadrian: Dump STG when ticky is enabled

This changes the "ticky" modifier to enable dumping of final STG as this
is generally needed to make sense of the ticky profiles.

- - - - -
487b48ca by Ben Gamari at 2020-11-21T15:53:07-05:00
hadrian: Introduce notion of flavour transformers

This extends Hadrian's notion of "flavour", as described in #18942.

- - - - -
246116f3 by Ben Gamari at 2020-11-21T15:53:07-05:00
hadrian: Add a viaLlvmBackend modifier

Note that this also slightly changes the semantics of these flavours as
we only use LLVM for >= stage1 builds.

- - - - -
a47974a2 by Ben Gamari at 2020-11-21T15:53:07-05:00
hadrian: Add profiled_ghc and no_dynamic_ghc modifiers

- - - - -
eb581f0f by Ben Gamari at 2020-11-21T15:53:08-05:00
hadrian: Drop redundant flavour definitions

Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as
these can now be realized with flavour transformers.

- - - - -


30 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Dwarf.hs
- compiler/GHC/CmmToAsm/Dwarf/Constants.hs
- compiler/GHC/CmmToAsm/Dwarf/Types.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- + compiler/GHC/Core/Opt/CallerCC.hs
- + compiler/GHC/Core/Opt/CallerCC.hs-boot
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a1071855094b4578917a1eb53f7b4417ef0a2c3...eb581f0f50bd6c34bcbd8c3518e8d4c44bef495c

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a1071855094b4578917a1eb53f7b4417ef0a2c3...eb581f0f50bd6c34bcbd8c3518e8d4c44bef495c
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/20201121/c63cd8c2/attachment-0001.html>


More information about the ghc-commits mailing list