[Git][ghc/ghc][wip/T18291] 58 commits: DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)

Ben Gamari gitlab at gitlab.haskell.org
Mon Jul 27 17:16:36 UTC 2020



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


Commits:
30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00
DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957)

* add StgPprOpts datatype
* remove Outputable instances for types that need `StgPprOpts` to be
  pretty-printed and explicitly call type specific ppr functions
* add default `panicStgPprOpts` for panic messages (when it's not
  convenient to thread StgPprOpts or DynFlags down to the ppr function
  call)

- - - - -
863c544c by Mark at 2020-07-21T06:39:34-04:00
Fix a typo in existential_quantification.rst
- - - - -
05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00
Add release notes entry for #17816

[skip ci]

- - - - -
a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00
Use a newtype `Code` for the return type of typed quotations (Proposal #195)

There are three problems with the current API:

1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition
   of two type constructors. Doing so in your program involves making your own newtype and
   doing a lot of wrapping/unwrapping.

   For example, if I want to create a language which I can either run immediately or
   generate code from I could write the following with the new API. ::

      class Lang r where
        _int :: Int -> r Int
        _if  :: r Bool -> r a -> r a -> r a

      instance Lang Identity where
        _int = Identity
        _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f)

      instance Quote m => Lang (Code m) where
        _int = liftTyped
        _if cb ct cf = [|| if $$cb then $$ct else $$cf ||]

2. When doing code generation it is common to want to store code fragments in
   a map. When doing typed code generation, these code fragments contain a
   type index so it is desirable to store them in one of the parameterised
   map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from
   ``parameterized-utils``.

   ::

      compiler :: Env -> AST a -> Code Q a

      data AST a where ...
      data Ident a = ...

      type Env = MapF Ident (Code Q)

      newtype Code m a = Code (m (TExp a))

   In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``.
   Using one of these map types currently requires creating your own newtype and constantly
   wrapping every quotation and unwrapping it when using a splice. Achievable, but
   it creates even more syntactic noise than normal metaprogramming.

3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is
   easier. This is a weak reason but one everyone
   can surely agree with.

Updates text submodule.

- - - - -
58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00
users-guide: Fix :rts-flag:`--copying-gc` documentation

It was missing a newline.

- - - - -
19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00
Accumulate Haddock comments in P (#17544, #17561, #8944)

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

- - - - -
4c719460 by David Binder at 2020-07-22T20:17:35-04:00
Fix dead link to haskell prime discussion

- - - - -
f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00
Replace broken links to old haskell-prime site by working links to gitlab instance.
[skip ci]

- - - - -
0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00
Remove length field from FastString

- - - - -
1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use ShortByteString for FastString

There are multiple reasons we want this:

- Fewer allocations: ByteString has 3 fields, ShortByteString just has one.
- ByteString memory is pinned:
  - This can cause fragmentation issues (see for example #13110) but also
  - makes using FastStrings in compact regions impossible.

Metric Decrease:
    T5837
    T12150
    T12234
    T12425

- - - - -
8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance

Currently we're passing a indexWord8OffAddr# type function to
utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one
of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from
the inlining and specialization already done for those.

- - - - -
7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Add comment about tricky ForeignPtr lifetime

- - - - -
5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Use IO constructor instead of `stToIO . ST`

- - - - -
5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Remove redundant use of withForeignPtr

- - - - -
5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00
Encoding: Reformat utf8EncodeShortByteString to be more consistent

- - - - -
9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00
FastString: Reintroduce character count cache

Metric Increase:
    ManyConstructors

Metric Decrease:
    T4029

- - - - -
e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00
get-win32-tarballs: Fix detection of missing tarballs

This fixes the error message given by configure when the user
attempts to configure without first download the win32 tarballs.

- - - - -
9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00
Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default.

This is only for their respective codebases.

- - - - -
0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused "ncg" flag

This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31
in 2011.

- - - - -
bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00
Don't panic if the NCG isn't built (it is always built)

- - - - -
8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00
Remove unused sGhcWithNativeCodeGen

- - - - -
e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Correctly test active backend

Previously we used a platform settings to detect if the native code
generator was used. This was wrong. We need to use the
`DynFlags.hscTarget` field instead.

- - - - -
735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace ghcWithNativeCodeGen with a proper Backend datatype

* Represent backends with a `Backend` datatype in GHC.Driver.Backend

* Don't detect the default backend to use for the target platform at
  compile time in Hadrian/make but at runtime. It makes "Settings"
  simpler and it is a step toward making GHC multi-target.

* The latter change also fixes hadrian which has not been updated to
  take into account that the NCG now supports AIX and PPC64 (cf
  df26b95559fd467abc0a3a4151127c95cb5011b9 and
  d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984)

* Also we don't treat iOS specifically anymore (cf
  cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f)

- - - - -
f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00
Replace HscTarget with Backend

They both have the same role and Backend name is more explicit.

Metric Decrease:
    T3064

Update Haddock submodule

- - - - -
15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00
Deprecate -fdmd-tx-dict-sel.

It's behaviour is now unconditionally enabled as
it's slightly beneficial.

There are almost no benchmarks which benefit from
disabling it, so it's not worth the keep this
configurable.

This fixes #18429.

- - - - -
ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00
Add test for #18064

It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b

- - - - -
cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00
Define type Void# = (# #) (#18441)

There's one backwards compatibility issue: GHC.Prim no longer exports
Void#, we now manually re-export it from GHC.Exts.

- - - - -
02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00
Add regression test for #18478

!3392 backported !2993 to GHC 8.10.2 which most probably is responsible
for fixing #18478, which triggered a pattern match checker performance
regression in GHC 8.10.1 as first observed in #17977.

- - - - -
7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00
Minor refactoring of Unit display

* for consistency, try to always use UnitPprInfo to display units to
  users

* remove some uses of `unitPackageIdString` as it doesn't show the
  component name and it uses String

- - - - -
dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00
[linker] Fix out of range relocations.

mmap may return address all over the place. mmap_next will ensure we get
the next free page after the requested address.

This is especially important for linking on aarch64, where the memory model with PIC
admits relocations in the +-4GB range, and as such we can't work with
arbitrary object locations in memory.

Of note: we map the rts into process space, so any mapped objects must
not be ouside of the 4GB from the processes address space.

- - - - -
cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00
winio: restore console cp on exit

- - - - -
c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00
winio: change memory allocation strategy and fix double free errors.

- - - - -
ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00
Care with occCheckExpand in kind of occurrences

Issue #18451 showed that we could get an infinite type, through
over-use of occCheckExpand in the kind of an /occurrence/ of a
type variable.

See Note [Occurrence checking: look inside kinds] in GHC.Core.Type

This patch fixes the problem by making occCheckExpand less eager
to expand synonyms in kinds.

It also improves pretty printing of kinds, by *not* suppressing
the kind on a tyvar-binder like
    (a :: Const Type b)
where type Const p q = p.  Even though the kind of 'a' is Type,
we don't want to suppress the kind ascription.  Example: the
error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr
Note [Suppressing * kinds].

- - - - -
02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00
Simplify XRec definition
Change `Located X` usage to `XRec pass X`
This increases the scope of the LPat experiment to almost all of GHC.
Introduce UnXRec and MapXRec classes

Fixes #17587 and #18408

Updates haddock submodule

Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com>

- - - - -
e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00
DynFlags: store printer in TraceBinIfaceReading

We don't need to pass the whole DynFlags, just pass the logging
function, if any.

- - - - -
15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00
Rename GHC.Driver.Ways into GHC.Platform.Ways

- - - - -
342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add GHC.Platform.Profile

- - - - -
6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Put PlatformConstants into Platform

- - - - -
9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove platform constant wrappers

Platform constant wrappers took a DynFlags parameter, hence implicitly
used the target platform constants. We removed them to allow support
for several platforms at once (#14335) and to avoid having to pass
the full DynFlags to every function (#17957).

Metric Decrease:
   T4801

- - - - -
73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Remove dead code in utils/derivConstants

- - - - -
7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Move GHC.Platform into the compiler

Previously it was in ghc-boot so that ghc-pkg could use it. However it
wasn't necessary because ghc-pkg only uses a subset of it: reading
target arch and OS from the settings file. This is now done via
GHC.Platform.ArchOS (was called PlatformMini before).

- - - - -
459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Fix build systems

- - - - -
9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00
Bump CountParserDeps

- - - - -
6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00
Add accessors to ArchOS

- - - - -
fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00
Require SMP support in order to build a threaded stage1

Fixes 18266

- - - - -
a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00
Document loadFramework changes. (#18446)

Adds commentary on the rationale for the changes made in merge request
!3689.

- - - - -
da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00
rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails

Since switching to the two-step allocator, the `outofmem` test fails via
`osCommitMemory` failing to commit. However, this was previously exiting
with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter
is a more reasonable exit code for this case and matches the behavior on
POSIX platforms.

- - - - -
f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Update win32 output for parseTree

- - - - -
e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00
testsuite: Normalise WinIO error message differences

Previously the old Windows IO manager threw different errors than WinIO.
We now canonicalise these to the WinIO errors.

- - - - -
9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00
gitlab-ci: Kill ssh-agent after pushing test metrics

Otherwise the Windows builds hang forever waiting for the process to
terminate.

- - - - -
8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00
winio: remove dead argument to stg_newIOPortzh

- - - - -
ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00
winio: fix detection of tty terminals

- - - - -
52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00
winio: update codeowners

- - - - -
aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00
Improve NegativeLiterals (#18022, GHC Proposal #344)

Before this patch, NegativeLiterals used to parse x-1 as x (-1).

This may not be what the user expects, and now it is fixed:
x-1 is parsed as (-) x 1.

We achieve this by the following requirement:

  * When lexing a negative literal,
    it must not be preceded by a 'closing token'.

This also applies to unboxed literals, e.g. -1#.

See GHC Proposal #229 for the definition of a closing token.

A nice consequence of this change is that -XNegativeLiterals becomes a
subset of -XLexicalNegation. In other words, enabling both of those
extensions has the same effect as enabling -XLexicalNegation alone.

- - - - -
667ab69e by leiftw at 2020-07-27T07:07:32-04:00
fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think
- - - - -
6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00
Refactor the parser a little

* Create a dedicated production for type operators
* Create a dedicated type for the UNPACK pragma
* Remove an outdated part of Note [Parsing data constructors is hard]

- - - - -
94be2073 by Ben Gamari at 2020-07-27T13:16:16-04:00
Allow unsaturated runRW# applications

Previously we had a very aggressive Core Lint check which caught
unsaturated applications of runRW#. However, there is nothing
wrong with such applications and they may naturally arise in desugared
Core. For instance, the desugared Core of Data.Primitive.Array.runArray#
from the `primitive` package contains:

    case ($) (runRW# @_ @_) (\s -> ...) of ...

In this case it's almost certain that ($) will be inlined, turning the
application into a saturated application. However, even if this weren't
the case there isn't a problem: CorePrep (after deleting an unnecessary
case) can simply generate code in its usual way, resulting in a call to
the Haskell definition of runRW#.

Fixes #18291.

- - - - -
0f5b3d7e by Ben Gamari at 2020-07-27T13:16:16-04:00
testsuite: Add test for #18291

- - - - -


30 changed files:

- .gitlab/test-metrics.sh
- CODEOWNERS
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Graph.hs
- compiler/GHC/Cmm/Info.hs
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/LayoutStack.hs
- compiler/GHC/Cmm/Monad.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Cmm/Switch.hs
- compiler/GHC/Cmm/Switch/Implement.hs
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Monad.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.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/5bf2cffdb4d36d0c7d49c6d8aaf48d7e961aa210...0f5b3d7e6010c9c302ab9d8a7474ba89f89d3651

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5bf2cffdb4d36d0c7d49c6d8aaf48d7e961aa210...0f5b3d7e6010c9c302ab9d8a7474ba89f89d3651
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/20200727/13c0734e/attachment-0001.html>


More information about the ghc-commits mailing list