[Git][ghc/ghc][wip/haddock-accum] 48 commits: pretty-printer: Properly parenthesise LastStmt

Vladislav Zavialov gitlab at gitlab.haskell.org
Thu Mar 19 10:42:18 UTC 2020



Vladislav Zavialov pushed to branch wip/haddock-accum at Glasgow Haskell Compiler / GHC


Commits:
1f9db3e7 by Kirill Elagin at 2020-03-12T13:45:51Z
pretty-printer: Properly parenthesise LastStmt

After ApplicatveDo strips the last `return` during renaming, the pretty
printer has to restore it. However, if the return was followed by `$`,
the dollar was stripped too and not restored.

For example, the last stamement in:

```
  foo = do
    x <- ...
    ...
    return $ f x
```

would be printed as:

```
    return f x
```

This commit preserved the dolar, so it becomes:

```
    return $ f x
```

- - - - -
5cb93af7 by Kirill Elagin at 2020-03-12T13:45:51Z
pretty-printer: Do not print ApplicativeDo join

* Do not print `join` in ApplictiveStmt, unless ppr-debug
* Print parens around multiple parallel binds

When ApplicativeDo is enabled, the renamer analyses the statements of a
`do` block and in certain cases marks them as needing to be rewritten
using `join`.

For example, if you have:

```
foo = do
  a <- e1
  b <- e2
  doSomething a b
```

it will be desugared into:

```
foo = join (doSomething <$> e1 <*> e2)
```

After renaming but before desugaring the expression is stored
essentially as:

```
foo = do
  [will need join] (a <- e1 | b <- e2)
  [no return] doSomething a b
```

Before this change, the pretty printer would print a call to `join`,
even though it is not needed at this stage at all. The expression will be
actually rewritten into one using join only at desugaring, at which
point a literal call to join will be inserted.

- - - - -
3a259092 by Simon Peyton Jones at 2020-03-12T13:46:29Z
Expose compulsory unfoldings always

The unsafeCoerce# patch requires that unsafeCoerce# has
a compulsory unfolding that is always available.  So we have
to be careful to expose compulsory unfoldings unconditionally
and consistently.

We didn't get this quite right: #17871.  This patch fixes
it.  No real surprises here.

See Note [Always expose compulsory unfoldings] in GHC.Iface.Tidy

- - - - -
6a65b8c2 by Alp Mestanogullari at 2020-03-13T06:29:20Z
hadrian: improve dependency tracking for the check-* programs

The code in Rules.Register responsible for finding all the build artifacts
that Cabal installs when registering a library (static/shared libs, .hi files,
...) was looking in the wrong place. This patch fixes that logic and makes sure
we gather all those artifacts in a list to declare that the rule for a given
`.conf` file, our proxy for "Hadrian, please install this package in the package
db for this stage", also produces those artifacts under the said package
database.

We also were completely missing some logic to declare that the check-* programs
have dependencies besides their source code, at least when testing an in-tree
compiler.

Finally, this patch also removes redundant packages from 'testsuitePackages',
since they should already be covered by the stage<N>Packages lists from
Settings.Default.

With this patch, after a complete build and freezing stage 1, a change to
`compiler/parser/Parser.y` results in rebuilding the ghc lib, reinstalling it,
and rebuilding the few programs that depend on it, _including_ `check-ppr` and
`check-api-annotations` (therefore fixing #17273).

- - - - -
44fad4a9 by Sylvain Henry at 2020-03-13T06:30:22Z
Rename isDllName

I wanted to fix the dangling comment in `isDllName` ("This is the cause
of #", #8696 is already mentioned earlier). I took the opportunity to
change the function name to better reflect what it does.

- - - - -
2f292db8 by Paavo at 2020-03-13T06:31:03Z
Update documentation for closureSize

- - - - -
f124ff0d by Ben Gamari at 2020-03-13T06:31:40Z
gitlab-ci: Rework triggering of release builds

Use a push option instead of tagging.

- - - - -
7f25557a by Ben Gamari at 2020-03-13T14:38:09Z
gitlab-ci: Distinguish integer-simple test envs

Previously two integer-simple jobs declared the same test environment. One (the nightly job) was built in the perf way, the other in the validate way. Consequently they had appreciably different performance characteristics, causing in the nightly job to spuriously fail with performance changes.
- - - - -
c12a2ec5 by Simon Peyton Jones at 2020-03-14T09:25:30Z
Fix Lint

Ticket #17590 pointed out a bug in the way the linter dealt with
type lets, exposed by the new uniqAway story.

The fix is described in Note [Linting type lets]. I ended up
putting the in-scope Ids in a different env field, le_ids,
rather than (as before) sneaking them into the TCvSubst.

Surprisingly tiresome, but done.

Metric Decrease:
    hie002

- - - - -
b989845e by Sylvain Henry at 2020-03-14T09:26:11Z
Hadrian: fix absolute buildroot support (#17822)

Shake's "**" wildcard doesn't match absolute root. We must use "//" instead.

- - - - -
4f117135 by Sylvain Henry at 2020-03-14T09:26:49Z
Make: refactor GMP rules

Document and use simpler rules for the ghc-gmp.h header.

- - - - -
7432b327 by Sylvain Henry at 2020-03-14T09:27:28Z
Use correct option name (-opti) (fix #17314)

s/pgmo/opti

- - - - -
8f7dd571 by Judah Jacobson at 2020-03-14T09:28:07Z
Allow overriding LD_STAGE0 and AR_STAGE0 in the configure script.

Previously it was possible to override the stage0 C compiler via `CC_STAGE0`,
but you couldn't override `ld` or `ar` in stage0.  This change allows overriding them
by setting `LD_STAGE0` or `AR_STAGE0`, respectively.

Our team uses this feature internally to take more control of our GHC build
and make it run more hermetically.

- - - - -
7c3e39a9 by Judah Jacobson at 2020-03-14T09:28:07Z
Use AC_ARG_VAR for LD_STAGE0 and AR_STAGE0.

- - - - -
20d4d676 by Ben Gamari at 2020-03-14T09:28:43Z
nonmoving: Don't traverse filled segment list in pause

The non-moving collector would previously walk the entire filled segment
list during the preparatory pause. However, this is far more work than
is strictly necessary. We can rather get away with merely collecting the
allocators' filled segment list heads and process the lists themselves
during the concurrent phase. This can significantly reduce the maximum
gen1 GC pause time in programs with high rates of long-lived allocations.

- - - - -
fdfa2d01 by Ben Gamari at 2020-03-14T09:29:18Z
nonmoving: Remove redundant bitmap clearing

nonmovingSweep already clears the bitmap in the sweep loop. There is no
reason to do so a second time.

- - - - -
2f8c7767 by Simon Peyton Jones at 2020-03-14T09:29:55Z
Simple refactor of cheapEqExpr

No change in functionality.  Just seems tidier (and signficantly more
efficient) to deal with ticks directly than to call stripTicksTopE.

- - - - -
88f7a762 by Simon Peyton Jones at 2020-03-14T09:29:55Z
Improve CSE.combineAlts

This patch improves the way that CSE combines identical
alternatives.  See #17901.

I'm still not happy about the duplication between CSE.combineAlts
and GHC.Core.Utils.combineIdenticalAlts; see the Notes with those
functions.  But this patch is a step forward.

Metric Decrease:
    T12425
    T5642

- - - - -
8b95ddd3 by Ben Gamari at 2020-03-14T09:30:31Z
gitlab-ci: Add integer-simple release build for Windows

Closes #16144.

- - - - -
e3c374cc by Simon Peyton Jones at 2020-03-14T09:31:07Z
Wrap an implication around class-sig kind errors

Ticket #17841 showed that we can get a kind error
in a class signature, but lack an enclosing implication
that binds its skolems.

This patch

* Adds the wrapping implication: the new call to
  checkTvConstraints in tcClassDecl1

* Simplifies the API to checkTvConstraints, which
  was not otherwise called at all.

* Simplifies TcErrors.report_unsolved by *not*
  initialising the TidyEnv from the typechecker lexical
  envt.  It's enough to do so from the free vars of the
  unsolved constraints; and we get silly renamings if
  we add variables twice: once from the lexical scope
  and once from the implication constraint.

- - - - -
73133a3b by Simon Peyton Jones at 2020-03-14T09:31:07Z
Refactoring in TcSMonad

This patch is just refactoring: no change in
behaviour.

I removed the rather complicated
    checkConstraintsTcS
    checkTvConstraintsTcS

in favour of simpler functions
    emitImplicationTcS
    emitTvImplicationTcS
    pushLevelNoWorkList

The last of these is a little strange, but overall
it's much better I think.

- - - - -
93c88c26 by Ben Gamari at 2020-03-14T09:31:42Z
base: Make `open` calls interruptible

As noted in #17912, `open` system calls were `safe` rather than
`interruptible`. Consequently, the program could not be interrupted with
SIGINT if stuck in a slow open operation. Fix this by marking
`c_safe_open` as interruptible.

- - - - -
bee4cdad by Vladislav Zavialov at 2020-03-14T09:32:18Z
Remove second tcLookupTcTyCon in tcDataDefn

Before this patch, tcDataDefn used to call tcLookupTcTyCon twice in a row:
	1. in bindTyClTyVars itself
	2. in the continuation passed to it

Now bindTyClTyVars passes the TcTyCon to the continuation, making
the second lookup unnecessary.

- - - - -
3f116d35 by Cale Gibbard at 2020-03-14T23:34:42Z
Enable stage1 build of haddock

The submodule has already been bumped to contain the fix.

- - - - -
49e9d739 by Ömer Sinan Ağacan at 2020-03-14T23:35:24Z
rts: Fix printClosure when printing fwd ptrs

- - - - -
1de3ab4a by Krzysztof Gogolewski at 2020-03-14T23:36:04Z
Remove unused field var_inline (#17915)

- - - - -
d30aeb4b by Krzysztof Gogolewski at 2020-03-15T07:57:41Z
Document restriction on SCC pragma syntax

Currently, the names of cost centres must be quoted or
be lowercase identifiers.

Fixes #17916.

- - - - -
b4774598 by Brian Foley at 2020-03-15T07:58:18Z
Remove some dead code

>From the notes.ghc.drop list found using weeder in #17713

- - - - -
dd6ffe6b by Viktor Dukhovni at 2020-03-15T07:58:55Z
Note platform-specific Foreign.C.Types in context

Also fix the markup in the general note at the top of the module.  Haddock
(usability trade-off), does not support multi-line emphasised text.

- - - - -
2e82465f by Sylvain Henry at 2020-03-15T14:57:10Z
Refactor CmmToAsm (disentangle DynFlags)

This patch disentangles a bit more DynFlags from the native code
generator (CmmToAsm).

In more details:

- add a new NCGConfig datatype in GHC.CmmToAsm.Config which contains the
  configuration of a native code generation session
- explicitly pass NCGConfig/Platform arguments when necessary
- as a consequence `sdocWithPlatform` is gone and there are only a few
  `sdocWithDynFlags` left
- remove the use of `unsafeGlobalDynFlags` from GHC.CmmToAsm.CFG
- remove `sdocDebugLevel` (now we pass the debug level via NCGConfig)

There are still some places where DynFlags is used, especially because
of pretty-printing (CLabel), because of Cmm helpers (such as
`cmmExprType`) and because of `Outputable` instance for the
instructions. These are left for future refactoring as this patch is
already big.

- - - - -
c35c545d by Judah Jacobson at 2020-03-15T14:57:48Z
Add a -no-haddock flag.

This flag undoes the effect of a previous "-haddock" flag.  Having both flags makes it easier
for build systems to enable Haddock parsing in a set of global flags, but then disable it locally for
specific targets (e.g., third-party packages whose comments don't pass the validation in the latest GHC).

I added the flag to expected-undocumented-flags.txt since `-haddock` was alreadyin that list.

- - - - -
cfcc3c9a by Ömer Sinan Ağacan at 2020-03-15T14:58:27Z
Fix global_link of TSOs for threads reachable via dead weaks

Fixes #17785

Here's how the problem occurs:

- In generation 0 we have a TSO that is finished (i.e. it has no more
  work to do or it is killed).

- The TSO only becomes reachable after collectDeadWeakPtrs().

- After collectDeadWeakPtrs() we switch to WeakDone phase where we don't
  move TSOs to different lists anymore (like the next gen's thread list
  or the resurrected_threads list).

- So the TSO will never be moved to a generation's thread list, but it
  will be promoted to generation 1.

- Generation 1 collected via mark-compact, and because the TSO is
  reachable it is marked, and its `global_link` field, which is bogus at
  this point (because the TSO is not in a list), will be threaded.

- Chaos ensues.

In other words, when these conditions hold:

- A TSO is reachable only after collectDeadWeakPtrs()
- It's finished (what_next is ThreadComplete or ThreadKilled)
- It's retained by mark-compact collector (moving collector doesn't
  evacuate the global_list field)

We end up doing random mutations on the heap because the TSO's
global_list field is not valid, but it still looks like a heap pointer
so we thread it during compacting GC.

The fix is simple: when we traverse old_threads lists to resurrect
unreachable threads the threads that won't be resurrected currently
stays on the old_threads lists. Those threads will never be visited
again by MarkWeak so we now reset the global_list fields. This way
compacting GC does not thread pointers to nowhere.

Testing
-------

The reproducer in #17785 is quite large and hard to build, because of
the dependencies, so I'm not adding a regression test.

In my testing the reproducer would take a less than 5 seconds to run,
and once in every ~5 runs would fail with a segfault or an assertion
error. In other cases it also fails with a test failure. Because the
tests never fail with the bug fix, assuming the code is correct, this
also means that this bug can sometimes lead to incorrect runtime
results.

After the fix I was able to run the reproducer repeatedly for about an
hour, with no runtime crashes or test failures.

To run the reproducer clone the git repo:

    $ git clone https://github.com/osa1/streamly --branch ghc-segfault

Then clone primitive and atomic-primops from their git repos and point
to the clones in cabal.project.local. The project should then be
buildable using GHC HEAD. Run the executable `properties` with `+RTS -c
-DZ`.

In addition to the reproducer above I run the test suite using:

    $ make slowtest EXTRA_HC_OPTS="-debug -with-rtsopts=-DS \
        -with-rtsopts=-c +RTS -c -RTS" SKIPWAY='nonmoving nonmoving_thr'

This enables compacting GC always in both GHC when building the test
programs and when running the test programs, and also enables sanity
checking when running the test programs. These set of flags are not
compatible for all tests so there are some failures, but I got the same
set of failures with this patch compared to GHC HEAD.

- - - - -
818b3c38 by Lysxia at 2020-03-17T03:52:42Z
base: add strict IO functions: readFile', getContents', hGetContents'

- - - - -
18a346a4 by Sylvain Henry at 2020-03-17T03:53:24Z
Modules: Core (#13009)

Update submodule: haddock

- - - - -
92327e3a by Ömer Sinan Ağacan at 2020-03-17T03:54:04Z
Update sanity checking for TSOs:

- Remove an invalid assumption about GC checking what_next field. The GC
  doesn't care about what_next at all, if a TSO is reachable then all
  its pointers are followed (other than global_tso, which is only
  followed by compacting GC).

- Remove checkSTACK in checkTSO: TSO stacks will be visited in
  checkHeapChain, or checkLargeObjects etc.

- Add an assertion in checkTSO to check that the global_link field is
  sane.

- Did some refactor to remove forward decls in checkGlobalTSOList and
  added braces around single-statement if statements.

- - - - -
e1aa4052 by PHO at 2020-03-17T11:36:09Z
Don't use non-portable operator "==" in configure.ac

The test operator "==" is a Bash extension and produces a wrong result
if /bin/sh is not Bash.

- - - - -
89f034dd by Maximilian Tagher at 2020-03-17T11:36:48Z
Document the units of -ddump-timings

Right now, in the output of -ddump-timings to a file, you can't tell what the units are:

```
CodeGen [TemplateTestImports]: alloc=22454880 time=14.597
```

I believe bytes/milliseconds are the correct units, but confirmation would be appreciated. I'm basing it off of this snippet from `withTiming'`:

```
when (verbosity dflags >= 2 && prtimings == PrintTimings)
  $ liftIO $ logInfo dflags (defaultUserStyle dflags)
      (text "!!!" <+> what <> colon <+> text "finished in"
       <+> doublePrec 2 time
       <+> text "milliseconds"
       <> comma
       <+> text "allocated"
       <+> doublePrec 3 (realToFrac alloc / 1024 / 1024)
       <+> text "megabytes")
```

which implies time is in milliseconds, and allocations in bytes (which divided by 1024 would be KB, and again would be MB)

- - - - -
beffa147 by Simon Peyton Jones at 2020-03-17T11:37:25Z
Implement mapTyCo like foldTyCo

This patch makes mapType use the successful idiom described
in TyCoRep
   Note [Specialising foldType]

I have not yet changed any functions to use mapType, though there
may be some suitable candidates.

This patch should be a no-op in terms of functionality but,
because it inlines the mapper itself, I'm hoping that there may
be some modest perf improvements.

Metric Decrease:
    T5631
    T5642
    T3064
    T9020
    T14683
    hie002
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -
5800ebfe by Ömer Sinan Ağacan at 2020-03-17T11:38:08Z
Don't update ModDetails with CafInfos when opts are disabled

This is consistent with the interface file behavior where we omit
HsNoCafRefs annotations with -fomit-interface-pragmas (implied by -O0).

ModDetails and ModIface are just different representations of the same
thing, so they really need to be in sync. This patch does the right
thing and does not need too much explanation, but here's an example of a
problem not doing this causes in !2842:

    -- MyInteger.hs
    module MyInteger
      ( MyInteger (MyInteger)
      , ToMyInteger (toMyInteger)
      ) where

    newtype MyInteger = MyInteger Integer

    class ToMyInteger a where
      toMyInteger :: a -> MyInteger

    instance ToMyInteger Integer where
      toMyInteger = MyInteger {- . succ -}

    -- Main.hs
    module Main
      ( main
      ) where

    import MyInteger (MyInteger (MyInteger), toMyInteger)

    main :: IO ()
    main = do
      let (MyInteger i) = (id . toMyInteger) (41 :: Integer)
      print i

If I build this with -O0, without this fix, we generate a ModDetails with
accurate LFInfo for toMyInteger (MyInteger.$fToMyIntegerInteger) which says that
it's a LFReEntrant with arity 1. This means in the use site (Main) we tag the
value:

    R3 = MyInteger.$fToMyIntegerInteger_closure + 1;
    R2 = GHC.Base.id_closure;
    R1 = GHC.Base.._closure;
    Sp = Sp - 16;
    call stg_ap_ppp_fast(R4, R3, R2, R1) args: 24, res: 0, upd: 24;

Now we change the definition by uncommenting the `succ` part and it becomes a thunk:

    MyInteger.$fToMyIntegerInteger [InlPrag=INLINE (sat-args=0)]
      :: MyInteger.ToMyInteger GHC.Integer.Type.Integer
    [GblId[DFunId(nt)]] =
        {} \u [] $ctoMyInteger_rEA;

and its LFInfo is now LFThunk. This change in LFInfo makes a difference in the
use site: we can no longer tag it.

But becuase the interface fingerprint does not change (because ModIface does not
change) we don't rebuild Main and tag the thunk.

(1.2% increase in allocations when building T12545 on armv7 because we
generate more code without CafInfos)

Metric Increase:
    T12545

- - - - -
5b632dad by Paavo at 2020-03-17T11:38:48Z
Add example for Data.Semigroup.diff

- - - - -
4d85d68b by Paavo at 2020-03-17T11:38:48Z
Clean up

- - - - -
75168d07 by Paavo at 2020-03-17T11:38:48Z
Make example collapsible

- - - - -
53ff2cd0 by Richard Eisenberg at 2020-03-17T13:46:57Z
Fix #17021 by checking more return kinds

All the details are in new Note [Datatype return kinds] in
TcTyClsDecls.

Test case: typecheck/should_fail/T17021{,b}
           typecheck/should_compile/T17021a

Updates haddock submodule

- - - - -
528df8ec by Sylvain Henry at 2020-03-18T14:06:43Z
Modules: Core operations (#13009)

- - - - -
4e8a71c1 by Richard Eisenberg at 2020-03-18T14:07:19Z
Add release note about fix to #16502.

We thought we needed to update the manual, but the fix for #16502
actually brings the implementation in line with the manual. So we
just alert users of how to update their code.

- - - - -
5cbf9934 by Andreas Klebinger at 2020-03-19T04:39:27Z
Update "GHC differences to the FFI Chapter" in user guide.

The old entry had a heavy focus on how things had been. Which is
not what I generally look for in a user guide.

I also added a small section on behaviour of nested safe ffi calls.

[skip-ci]

- - - - -
b03fd3bc by Sebastian Graf at 2020-03-19T04:40:06Z
PmCheck: Use ConLikeSet to model negative info

In #17911, Simon recognised many warnings stemming from over-long list
unions while coverage checking Cabal's `LicenseId` module.

This patch introduces a new `PmAltConSet` type which uses a `UniqDSet`
instead of an association list for `ConLike`s. For `PmLit`s, it will
still use an assocation list, though, because a similar map data
structure would entail a lot of busy work.

Fixes #17911.

- - - - -
2029a899 by Vladislav Zavialov at 2020-03-19T10:41:57Z
Accumulate Haddock comments in P (#17544, #17561)

Haddock comments are, first and foremost, comments. It's very annoying
to incorporate them into the grammar. We can take advantage of an
important property: adding a Haddock comment does not change the parse
tree in any way other than wrapping some nodes in HsDocTy and the like
(and if it does, that's a bug).

This patch implements the following:

* Accumulate Haddock comments with their locations in the P monad.
  This is handled in the lexer.

* After parsing, do a pass over the AST to associate Haddock comments
  with AST nodes using location info.

* Report the leftover comments to the user as a warning (-Winvalid-haddock).

Metric Increase:
    T13719
    ManyConstructors
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Dataflow/Block.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/CFG.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/Instr.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/Regs.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph.hs
- compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/e1f98f735adf2a49277084532be9ebdbcc4f98e6...2029a8999fb6c76656b25495e0bb9bb15bd00cea

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/e1f98f735adf2a49277084532be9ebdbcc4f98e6...2029a8999fb6c76656b25495e0bb9bb15bd00cea
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/20200319/8b6ad45b/attachment-0001.html>


More information about the ghc-commits mailing list