[Git][ghc/ghc][wip/angerman/aarch64-ncg] 179 commits: rts/linker: Fix relocation overflow in PE linker

Moritz Angermann gitlab at gitlab.haskell.org
Thu Nov 26 03:35:19 UTC 2020



Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC


Commits:
d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00
rts/linker: Fix relocation overflow in PE linker

Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB
relocation failed to account for the signed nature of the value.
Specifically, the overflow check was:

    uint64_t v;
    v = S + A;
    if (v >> 32) { ... }

However, `v` ultimately needs to fit into 32-bits as a signed value.
Consequently, values `v > 2^31` in fact overflow yet this is not caught
by the existing overflow check.

Here we rewrite the overflow check to rather ensure that
`INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition
between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases
but I am leaving fixing this for future work.

This bug was first noticed by @awson.

Fixes #15808.

- - - - -
4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00
Export SPEC from GHC.Exts (#13681)

- - - - -
7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00
ghc-heap: expose decoding from heap representation

Co-authored-by: Sven Tennie <sven.tennie at gmail.com>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>
Co-authored-by: Ben Gamari <bgamari.foss at gmail.com>

- - - - -
fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00
Add test case for #17186.

This got fixed sometime recently; not worth it trying to
figure out which commit.

- - - - -
2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00
Add code comments for StgInfoTable and StgStack structs

- - - - -
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

- - - - -
7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00
rts: Post ticky entry counts to the eventlog

We currently only post the entry counters, not the other global
counters as in my experience the former are more useful. We use the heap
profiler's census period to decide when to dump.

Also spruces up the documentation surrounding ticky-ticky a bit.

- - - - -
bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00
Implement -ddump-c-backend argument

To dump output of the C backend.

- - - - -
901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00
Bump time submodule to 1.11.1

Also bumps directory, Cabal, hpc, time, and unix submodules.

Closes #18847.

- - - - -
92c0afbf by Ben Gamari at 2020-11-22T12:39:38-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.

- - - - -
d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00
hadrian: Introduce notion of flavour transformers

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

- - - - -
179d0bec by Ben Gamari at 2020-11-22T12:39:38-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.

- - - - -
d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00
hadrian: Add profiled_ghc and no_dynamic_ghc modifiers

- - - - -
6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00
hadrian: Drop redundant flavour definitions

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

- - - - -
f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00
rts: Flush eventlog buffers from flushEventLog

As noted in #18043, flushTrace failed flush anything beyond the writer.
This means that a significant amount of data sitting in capability-local
event buffers may never get flushed, despite the users' pleads for us to
flush.

Fix this by making flushEventLog flush all of the event buffers before
flushing the writer.

Fixes #18043.

- - - - -
7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00
gitlab-ci: Run LLVM job on appropriately-labelled MRs

Namely, those marked with the ~"LLVM backend" label

- - - - -
9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00
gitlab-ci: Run LLVM builds on Debian 10

The current Debian 9 image doesn't provide LLVM 7.

- - - - -
2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00
CmmToLlvm: Declare signature for memcmp

Otherwise `opt` fails with:

    error: use of undefined value '@memcmp$def'

- - - - -
aeef1eb6 by Moritz Angermann at 2020-11-26T10:25:21+08:00
[Sized Cmm] properly retain sizes.

This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int#  with
Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us
with properly sized primitives in the codegenerator instead of pretending
they are all full machine words.

This came up when implementing darwinpcs for arm64.  The darwinpcs reqires
us to pack function argugments in excess of registers on the stack.  While
most procedure call standards (pcs) assume arguments are just passed in
8 byte slots; and thus the caller does not know the exact signature to make
the call, darwinpcs requires us to adhere to the prototype, and thus have
the correct sizes.  If we specify CInt in the FFI call, it should correspond
to the C int, and not just be Word sized, when it's only half the size.

- - - - -
38be4fb5 by Moritz Angermann at 2020-11-26T10:25:23+08:00
[Sized Cmm] properly retain sizes.

This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int#  with
Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us
with properly sized primitives in the codegenerator instead of pretending
they are all full machine words.

This came up when implementing darwinpcs for arm64.  The darwinpcs reqires
us to pack function argugments in excess of registers on the stack.  While
most procedure call standards (pcs) assume arguments are just passed in
8 byte slots; and thus the caller does not know the exact signature to make
the call, darwinpcs requires us to adhere to the prototype, and thus have
the correct sizes.  If we specify CInt in the FFI call, it should correspond
to the C int, and not just be Word sized, when it's only half the size.

- - - - -
be61cae2 by Moritz Angermann at 2020-11-26T10:31:10+08:00
Initial NCG

- - - - -
1ec438ea by Moritz Angermann at 2020-11-26T10:31:21+08:00
Address Takenobu's comments

- - - - -
5249fd2c by Moritz Angermann at 2020-11-26T10:31:21+08:00
Fix floating points handling of NaNs

- - - - -
4eb48320 by Moritz Angermann at 2020-11-26T10:32:19+08:00
Add basic Graph Coloring support

- - - - -
5e4c2950 by Moritz Angermann at 2020-11-26T10:32:27+08:00
Drop debug

- - - - -
b5f4ad2f by Moritz Angermann at 2020-11-26T10:32:27+08:00
Add primops_match.cmm testsuite

- - - - -
ed04b45d by Moritz Angermann at 2020-11-26T10:32:27+08:00
Fix -NaN for real this time.

- - - - -
886c87a7 by Moritz Angermann at 2020-11-26T10:32:28+08:00
Adds nan test.

- - - - -
6fe442d1 by Moritz Angermann at 2020-11-26T10:32:28+08:00
no show

- - - - -
b52e8e3d by Moritz Angermann at 2020-11-26T10:32:28+08:00
Some notes on PIC

- - - - -
aeebd433 by Moritz Angermann at 2020-11-26T10:32:28+08:00
Properly load W32 with bit 31 set.

- - - - -
a911ac0b by Moritz Angermann at 2020-11-26T10:32:28+08:00
better relocation logging

- - - - -
4d18232e by Moritz Angermann at 2020-11-26T10:32:29+08:00
Add AsmOpt Flags

- - - - -
071977f5 by Moritz Angermann at 2020-11-26T10:32:29+08:00
Adds ANN instruction.

I wish I had a `pad n` function for SDoc, that would interact with the
layout, and just pad what ever was printed so far to `n` chars.

- - - - -
c17df046 by Moritz Angermann at 2020-11-26T10:32:29+08:00
Drop dead 32bit logic.

- - - - -
371543b3 by Moritz Angermann at 2020-11-26T10:32:29+08:00
Add Show CmmExpr instances.

Why would we want this, when we have Outputtable CmmExpr? Quite often
when working on Code Generators, we want to structurally match on
a Cmm Expression. Having to recover the Cmm Expression from its
Outputtable text is not always trivial, and requires substantial effort.
By having a Show instance, we can almost copy the definition to match
on.

- - - - -
9d69880d by Moritz Angermann at 2020-11-26T10:32:29+08:00
Drop duplicate show instance for CLabel now.

- - - - -
b44f5789 by Moritz Angermann at 2020-11-26T10:32:30+08:00
Add link, lest I keep forgetting it.

- - - - -
41f4a929 by Moritz Angermann at 2020-11-26T10:32:30+08:00
inline comments with //

- - - - -
76d9eed9 by Moritz Angermann at 2020-11-26T10:32:30+08:00
Some optimizations; not yet sure if safe or not.

- - - - -
defc3bf9 by Moritz Angermann at 2020-11-26T10:32:30+08:00
Add latest opt changes.

- - - - -
6c2a06b0 by Moritz Angermann at 2020-11-26T10:32:30+08:00
Address Takenobu Tani's comments.

Thanks!

- - - - -
d241b467 by Moritz Angermann at 2020-11-26T10:32:31+08:00
Fix gcd :blush:

- - - - -
0e47ccb8 by Moritz Angermann at 2020-11-26T10:32:31+08:00
Overflow guard

- - - - -
1c3dce44 by Moritz Angermann at 2020-11-26T10:32:31+08:00
More annotations.

- - - - -
0eb68c0b by Moritz Angermann at 2020-11-26T10:32:31+08:00
Revert "Overflow guard"

They are Integers not Ints.

This reverts commit 3ef94e593a2848cf2bdc4251f5be34536642675f.

Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com>

- - - - -
d083c640 by Moritz Angermann at 2020-11-26T10:32:32+08:00
Add CmmAssign and CmmStore comments

- - - - -
41cf9597 by Moritz Angermann at 2020-11-26T10:32:32+08:00
Minor address mode changes

- - - - -
21ecf30f by Moritz Angermann at 2020-11-26T10:32:32+08:00
More Amode optimizations

- - - - -
d43f39dc by Moritz Angermann at 2020-11-26T10:32:32+08:00
I think this shoudl work for all Registers, not just CmmGlobal

- - - - -
9f96440c by Moritz Angermann at 2020-11-26T10:32:32+08:00
Opt <<, >>

- - - - -
1df13b8b by Moritz Angermann at 2020-11-26T10:32:33+08:00
Opt &&, ||

- - - - -
669f0cdc by Moritz Angermann at 2020-11-26T10:32:33+08:00
Add branch ANNotations.

- - - - -
b38a1958 by Moritz Angermann at 2020-11-26T10:32:33+08:00
Disable Opt &&, ||, due to mask immediate

- - - - -
b3fe0f6b by Moritz Angermann at 2020-11-26T10:32:33+08:00
Opt: Adds CBZ, CBNZ

- - - - -
33f9f791 by Moritz Angermann at 2020-11-26T10:32:33+08:00
More generic CBZ, CBNZ

- - - - -
b154bf06 by Moritz Angermann at 2020-11-26T10:32:34+08:00
Fixup

- - - - -
b0ac8284 by Moritz Angermann at 2020-11-26T10:32:34+08:00
very rudimentary bitmask support.

- - - - -
5950b537 by Moritz Angermann at 2020-11-26T10:32:34+08:00
Add some more bitmasks

- - - - -
d8326544 by Moritz Angermann at 2020-11-26T10:32:34+08:00
Opt STR

- - - - -
00150171 by Moritz Angermann at 2020-11-26T10:32:34+08:00
Fixup

- - - - -
bd9dda04 by Moritz Angermann at 2020-11-26T10:32:35+08:00
Fix MO_SF_Conv

- - - - -
812c2004 by Moritz Angermann at 2020-11-26T10:32:35+08:00
Add Comment re MO_Memcpy

- - - - -
a1205688 by Moritz Angermann at 2020-11-26T10:32:35+08:00
Always PIC via GOT

- - - - -
14dd4b28 by Moritz Angermann at 2020-11-26T10:32:35+08:00
Fix up generated assembly.

Don't generate identity moves
e.g. mov x18, x18

- - - - -
21eb4ed0 by Moritz Angermann at 2020-11-26T10:32:35+08:00
Drop superfulous alignment generation.

- - - - -
c29df435 by Moritz Angermann at 2020-11-26T10:32:36+08:00
Hadrian :fire:

- - - - -
b771b292 by Moritz Angermann at 2020-11-26T10:32:36+08:00
Address Tekenobus comments.

Thanks!

- - - - -
b225e4ba by Moritz Angermann at 2020-11-26T10:32:36+08:00
Adds J to distinguish jumps from B.

Maybe this would be better handled with a phantom type?

- - - - -
b855d5f0 by Moritz Angermann at 2020-11-26T10:32:36+08:00
Make sp an Operand

- - - - -
a32735b1 by Moritz Angermann at 2020-11-26T10:32:36+08:00
allocMoreStack

This is still broken, as we can't spill into arbitrary ranges. Hence while we can allocate extra space, we can't really spill past 4096 offsets due to the immediat having to be encoded. This leaves us with a max of 512 spill slots.

We *can* work around this if we change the sp though.

- - - - -
72ad0110 by Moritz Angermann at 2020-11-26T10:32:37+08:00
[Spill/Reload] Spill Around :fire:

- - - - -
f60dbd82 by Moritz Angermann at 2020-11-26T10:32:37+08:00
Address Takenobus observations!

Thanks!

- - - - -
59303597 by Moritz Angermann at 2020-11-26T10:32:37+08:00
:sob:

- - - - -
b022e7a9 by Moritz Angermann at 2020-11-26T10:32:37+08:00
Revert the Spill/Reload fix; undo :got: loads.

This breaks dynamic, however we can build a working
stage2 compiler with the following mk/build.mk

BuildFlavour = quick

ifneq "$(BuildFlavour)" ""
include mk/flavours/$(BuildFlavour).mk
endif

STRIP_CMD = :

DYNAMIC_BY_DEFAULT   = NO
DYNAMIC_GHC_PROGRAMS = NO

- - - - -
e9c1def9 by Moritz Angermann at 2020-11-26T10:32:37+08:00
Disable trivial deadlock detection

- - - - -
f9011088 by Moritz Angermann at 2020-11-26T10:32:38+08:00
Adds some annotations

- - - - -
31f2545f by Moritz Angermann at 2020-11-26T10:32:38+08:00
Trying to get PIC right.

- - - - -
23bfce96 by Moritz Angermann at 2020-11-26T10:32:38+08:00
[aarch64] Fix spill/reload

- - - - -
3a386bcc by Moritz Angermann at 2020-11-26T10:32:38+08:00
Try to get PIC right.

- - - - -
8dfd6bd6 by Moritz Angermann at 2020-11-26T10:32:39+08:00
Spill/Reload only need a smaller window

- - - - -
93e2f834 by Moritz Angermann at 2020-11-26T10:32:39+08:00
Drop bad/useless optimisation

This was due to not handling PIC symbols correctly and injecting CmmLoad
as we do on other platforms, but this doesn't translate to aarch64's got lookups.

- - - - -
83d181c6 by Moritz Angermann at 2020-11-26T10:32:39+08:00
B is b

- - - - -
c917632b by Moritz Angermann at 2020-11-26T10:32:39+08:00
Fix CCall

|Now mark used registers properly for the Register Allocator.

- - - - -
3213ddc8 by Moritz Angermann at 2020-11-26T10:32:39+08:00
:sob:

- - - - -
dd1fe55d by Moritz Angermann at 2020-11-26T10:32:40+08:00
:sob: :sob:

- - - - -
4c6763c7 by Moritz Angermann at 2020-11-26T10:32:40+08:00
:sob: Segfault no 3. This showed up in T4114

- - - - -
6f341c48 by Moritz Angermann at 2020-11-26T10:32:40+08:00
Add mkComment to `Instruction`

- - - - -
584d3478 by Moritz Angermann at 2020-11-26T10:32:40+08:00
Use mkComment for debugging

- - - - -
d745f69d by Moritz Angermann at 2020-11-26T10:32:40+08:00
Fix T4114 crashes

T4114 causes this codepath to show up.

- - - - -
7e15dcbf by Moritz Angermann at 2020-11-26T10:32:41+08:00
Cleanup some compiler warnings

- - - - -
fb2206ba by Moritz Angermann at 2020-11-26T10:32:41+08:00
[Aarch64] No div-by-zero; disable test.

- - - - -
1c1538ff by Moritz Angermann at 2020-11-26T10:32:41+08:00
Simplify aarch64 StgRun

We don't need to do the callee save register dance. The compiler will
do this for us already:

0000000000000000 <StgRun>:
   0:   a9b653f3        stp     x19, x20, [sp, #-160]!
   4:   a9015bf5        stp     x21, x22, [sp, #16]
   8:   a90263f7        stp     x23, x24, [sp, #32]
   c:   a9036bf9        stp     x25, x26, [sp, #48]
  10:   a90473fb        stp     x27, x28, [sp, #64]
  14:   f9002bfe        str     x30, [sp, #80]
  18:   6d0627e8        stp     d8, d9, [sp, #96]
  1c:   6d072fea        stp     d10, d11, [sp, #112]
  20:   6d0837ec        stp     d12, d13, [sp, #128]
  24:   6d093fee        stp     d14, d15, [sp, #144]
  28:   a9bf47f0        stp     x16, x17, [sp, #-16]!
  2c:   d14013ff        sub     sp, sp, #0x4, lsl #12
  30:   aa0103f3        mov     x19, x1
  34:   d61f0000        br      x0

0000000000000038 <StgReturn>:
  38:   914013ff        add     sp, sp, #0x4, lsl #12
  3c:   aa1603e0        mov     x0, x22
  40:   a8c147f0        ldp     x16, x17, [sp], #16
  44:   a9415bf5        ldp     x21, x22, [sp, #16]
  48:   a94263f7        ldp     x23, x24, [sp, #32]
  4c:   a9436bf9        ldp     x25, x26, [sp, #48]
  50:   a94473fb        ldp     x27, x28, [sp, #64]
  54:   f9402bfe        ldr     x30, [sp, #80]
  58:   6d4627e8        ldp     d8, d9, [sp, #96]
  5c:   6d472fea        ldp     d10, d11, [sp, #112]
  60:   6d4837ec        ldp     d12, d13, [sp, #128]
  64:   6d493fee        ldp     d14, d15, [sp, #144]
  68:   a8ca53f3        ldp     x19, x20, [sp], #160
  6c:   d65f03c0        ret

- - - - -
2c75c03b by Moritz Angermann at 2020-11-26T10:32:41+08:00
Use ip0 for spills/reloads

- - - - -
34ed36f1 by Moritz Angermann at 2020-11-26T10:33:57+08:00
:broom: Cleanup

- - - - -
6f5776da by Moritz Angermann at 2020-11-26T10:34:22+08:00
Add validate as well.

- - - - -
e4f94ba8 by Moritz Angermann at 2020-11-26T10:34:22+08:00
Revert "Simplify aarch64 StgRun"

This reverts commit f27472c0483db2382344f4a8f4c1b2a192d98725.

- - - - -
f620f0af by Moritz Angermann at 2020-11-26T10:34:22+08:00
Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md
- - - - -
7c85f53a by Moritz Angermann at 2020-11-26T10:34:22+08:00
Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md
- - - - -
53b7f2ec by Moritz Angermann at 2020-11-26T10:34:39+08:00
Add CLabel logic

- - - - -
7078f25d by Moritz Angermann at 2020-11-26T10:35:40+08:00
[configure] make arm64-apple-darwin an LLVM Target

This is required as the llvm toolchain doesn't like
aarch64-apple-darwin, and only accepts arm64-apple-darwin.

- - - - -
291dd625 by Moritz Angermann at 2020-11-26T10:36:29+08:00
[arm64/mach-o] adrp/ldr symbol names

This will break elf. We need to find a better solution for this
symbol naming is platform dependent here.

:got: / @gotpage
:got_lo12: / @gotpageoff

:lo12: / @pageoff

- - - - -
69c88134 by Moritz Angermann at 2020-11-26T10:38:04+08:00
[WIP] symbol garbage

Naming is hard.  Supporting assembler and linker even harder.

L is the assembly local prefix
l is the linker local prefix

L is not relocated at all.
l is relocated, but fails to for conditional branches.

Send help!

- - - - -
455627e4 by Moritz Angermann at 2020-11-26T10:38:16+08:00
[MachO] cleanup compiler warnings

- - - - -
99f823a6 by Moritz Angermann at 2020-11-26T10:38:29+08:00
[Storage/Adjustor] Drop size check in allocExec

This is violated by ghci, in InfoTable.hsc we call
_allocateExec with a size that does not guarantee to
be of ffi_closure size.

Other allocateExec implementations do not have this
check either; I highly doubt it's sensible to have
this check in the presence of ghci's allocateExec calls.

- - - - -
b313ebfc by Moritz Angermann at 2020-11-26T10:38:30+08:00
[linker/elf] better errors (with error message)

- - - - -
6c1f47e0 by Moritz Angermann at 2020-11-26T10:38:41+08:00
[aarch64/codegen] pack ccall arguments on darwin

This is annoying, but the darwinpcs does not match the default aapcs :facepalm:

- - - - -
6ca8a6f4 by Moritz Angermann at 2020-11-26T10:38:41+08:00
[linker:MachO] split PLT logic out.

Why was this missing in the first place? It's now a bit more aligned to the
elf plt logic.

- - - - -
eea02e96 by Moritz Angermann at 2020-11-26T10:39:57+08:00
[configure] fix LLVMTarget when native

uname -p return "arm", hence we can't work with target_cpu,
but need to match on the target triple.

- - - - -
5357f0e5 by Moritz Angermann at 2020-11-26T10:40:00+08:00
[testsuite] fix subsections_via_symbols test

- - - - -
f7c0b975 by Moritz Angermann at 2020-11-26T10:40:00+08:00
[testsuite] FixT11649

- - - - -
3dbace0c by Moritz Angermann at 2020-11-26T10:40:00+08:00
Fix conc059 test

- - - - -
097c3f0a by Moritz Angermann at 2020-11-26T10:40:01+08:00
WIP: fix ghci adjustors on aarch64/arm (infotables)

- - - - -
75891882 by Moritz Angermann at 2020-11-26T10:42:18+08:00
[DWARF] Enable only on elf platforms

- - - - -
731693b8 by Moritz Angermann at 2020-11-26T10:42:27+08:00
[Testsuite/LLVM] Fix T5681, T7571, T8131b

- - - - -
9ee45a21 by Moritz Angermann at 2020-11-26T10:42:27+08:00
[testsuite/darwin] fix tests ghcilink003, ghcilink006

- - - - -
ea1573ce by Moritz Angermann at 2020-11-26T10:45:21+08:00
Fix linker_error2

- - - - -
699cac12 by Moritz Angermann at 2020-11-26T10:46:28+08:00
Sized Hints

- - - - -
f9b81d24 by Moritz Angermann at 2020-11-26T10:46:28+08:00
[Testsuite/arm64] Fix test derefnull

- - - - -
ed09064e by Moritz Angermann at 2020-11-26T10:46:29+08:00
[testsuite/arm64] fix section_alignment

- - - - -
ff0c6f6e by Moritz Angermann at 2020-11-26T10:46:29+08:00
[macOS/arm64] darwinpcs :facepalm:

- - - - -
2c5125c4 by Moritz Angermann at 2020-11-26T10:46:29+08:00
[aarch64/darwin] ifdef for got lables.

This should ideally be some runtime flag, but it would need access to the platform.

- - - - -
588c1701 by Moritz Angermann at 2020-11-26T10:46:29+08:00
[aarch64/rts] fix missing prototypes

- - - - -
13fd1ddc by Moritz Angermann at 2020-11-26T10:46:29+08:00
Int has Word size in Haskell.

- - - - -
7d63f163 by Moritz Angermann at 2020-11-26T10:46:30+08:00
[debug only] warn on hint/arg mismatch

- - - - -
90300544 by Moritz Angermann at 2020-11-26T10:46:30+08:00
[AArch64 NCG] User argument format rather than hint.

- - - - -
d5406765 by Moritz Angermann at 2020-11-26T10:46:30+08:00
[Debug] Fix CmmFloat warnings.

- - - - -
efe4144f by Moritz Angermann at 2020-11-26T10:46:30+08:00
[aarch64/elf] fixup elf symbols

- - - - -
fbec2538 by Moritz Angermann at 2020-11-26T10:46:30+08:00
:facepalm:

- - - - -
d9693ad5 by Moritz Angermann at 2020-11-26T10:46:31+08:00
:facepalm:

- - - - -
8df5d41f by Moritz Angermann at 2020-11-26T10:46:31+08:00
[Adjustors] Proper allocator handling.

- - - - -
a493e703 by Moritz Angermann at 2020-11-26T10:46:31+08:00
Revert "[AArch64] Aarch64 Always PIC"

This reverts commit 921276592218211f441fcf011fc52441e3a2f0a6.

- - - - -
5f86875c by Moritz Angermann at 2020-11-26T10:46:31+08:00
Revert "[Storage/Adjustor] Drop size check in allocExec"

This reverts commit 37a62ae956a25e5832fbe125a4d8ee556fd11042.

- - - - -
fb197813 by Moritz Angermann at 2020-11-26T10:46:31+08:00
[Storage] Reinstate check; add comment.

- - - - -
615d2b26 by Moritz Angermann at 2020-11-26T10:46:32+08:00
[AArch64] Aarch64 Always PIC

- - - - -
81e93c4d by Moritz Angermann at 2020-11-26T10:46:32+08:00
[testsuite] static001 is not broken anymore.

- - - - -
2b95a984 by Moritz Angermann at 2020-11-26T10:46:32+08:00
Revert "Sized Hints"

This reverts commit 65cbfcc10e7ad32dd04ebce011860f5b557eacac.

- - - - -
1dabc1b3 by Moritz Angermann at 2020-11-26T10:47:20+08:00
fix up rebase

- - - - -


18 changed files:

- .gitlab-ci.yml
- .gitlab/ci.sh
- aclocal.m4
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Expr.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs
- + compiler/GHC/CmmToAsm/AArch64.hs
- + compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- + compiler/GHC/CmmToAsm/AArch64/Cond.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc7cdb3645892e98daddfafc56ad1c0b597688c...1dabc1b32f71c5744caea510fca146a70d517863

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc7cdb3645892e98daddfafc56ad1c0b597688c...1dabc1b32f71c5744caea510fca146a70d517863
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/20201125/a4827145/attachment-0001.html>


More information about the ghc-commits mailing list