<!DOCTYPE html PUBLIC "-//W3C//DTD HTML 4.0 Transitional//EN" "http://www.w3.org/TR/REC-html40/loose.dtd">
<html lang="en">
<head>
<meta content="text/html; charset=US-ASCII" http-equiv="Content-Type">
<title>
GitLab
</title>



<style>img {
max-width: 100%; height: auto;
}
</style>
</head>
<body>
<div class="content">

<h3>
Ömer Sinan Ağacan pushed to branch wip/osa1/std_string_thunks
at <a href="https://gitlab.haskell.org/ghc/ghc">Glasgow Haskell Compiler / GHC</a>
</h3>
<h4>
Commits:
</h4>
<ul>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/57b888c0e90be7189285a6b078c30b26d0923809">57b888c0</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-03-31T10:54:20-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Require GHC 8.8 as the minimum compiler for bootstrapping

This allows us to remove several bits of CPP that are either always
true or no longer reachable. As an added bonus, we no longer need to
worry about importing `Control.Monad.Fail.fail` qualified to avoid
clashing with `Control.Monad.fail`, since the latter is now the same
as the former.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/33f095511a8fce4c945bbcd4feb3910c854dcb61">33f09551</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-03-31T10:54:57-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add regression test for #17963

The panic in #17963 happened to be fixed by commit
e3c374cc5bd7eb49649b9f507f9f7740697e3f70. This patch adds a
regression test to ensure that it remains fixed.

Fixes #17963.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/09a36e80ecaefcfb60eccda98bd06461d0aeca70">09a36e80</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-03-31T10:55:37-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Simplify stderrSupportsAnsiColors

The combinator andM is used only once, and the code is shorter and
simpler if you inline it.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/95bccdd034ce4dd2d1bc36db9f1ba5e172550249">95bccdd0</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-03-31T10:56:19-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">base: Ensure that encoding global variables aren't inlined

As noted in #17970, these (e.g. `getFileSystemEncoding` and
`setFileSystemEncoding`) previously had unfoldings, which would
break their global-ness.

While not strictly necessary, I also add a NOINLINE on
`initLocaleEncoding` since it is used in `System.IO`, ensuring that we
only system's query the locale encoding once.

Fixes #17970.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/982aaa837aed564ae9b418cda8e97d4facff8fb8">982aaa83</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-03-31T10:56:55-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update hadrian index revision.

Required in order to build hadrian using ghc-8.10
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4b9c586472bf99425f7bbcf346472d7c54f05028">4b9c5864</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-03-31T10:57:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">integer-gmp: Bump version and add changelog entry
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9b39f2e6f63ae50cedd96eaf49146de8ed00fbc8">9b39f2e6</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-01T01:20:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Clean up "Eta reduction for data families" Notes

Before, there were two distinct Notes named
"Eta reduction for data families". This renames one of them to
"Implementing eta reduction for data families" to disambiguate the
two and fixes references in other parts of the codebase to ensure
that they are pointing to the right place.

Fixes #17313.

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7627eab5dd882eb6f1567e3ae95c6c770830a5eb">7627eab5</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-01T01:20:38-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix the changelog/@since information for hGetContents'/getContents'/readFile'

Fixes #17979.

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0002db1bf436cbd32f97b659a52b1eee4e8b21db">0002db1b</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-01T01:21:27-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Kill wORDS_BIGENDIAN and replace it with platformByteOrder (#17957)

Metric Decrease:
    T13035
    T1969
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/7b21717907a741b56513f5e1fa1ebceecf971613">7b217179</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-04-01T15:03:24-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">PmCheck: Adjust recursion depth for inhabitation test

In #17977, we ran into the reduction depth limit of the typechecker.
That was only a symptom of a much broader issue: The recursion depth
of the coverage checker for trying to instantiate strict fields in the
`nonVoid` test was far too high (100, the `defaultMaxTcBound`).

As a result, we were performing quite poorly on `T17977`.
Short of a proper termination analysis to prove emptyness of a type,
we just arbitrarily default to a much lower recursion limit of 3.

Fixes #17977.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3c09f636a459f50119bfbb5bf798b9a9e19eb464">3c09f636</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-04-01T15:03:59-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make hadrian pass on the no-colour setting to GHC.

Fixes #17983.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/b943b25d0786da64031ac63ddf9b4574182057bb">b943b25d</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-02T01:45:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Re-engineer the binder-swap transformation

The binder-swap transformation is implemented by the occurrence
analyser -- see Note [Binder swap] in OccurAnal. However it had
a very nasty corner in it, for the case where the case scrutinee
was a GlobalId.  This led to trouble and hacks, and ultimately
to #16296.

This patch re-engineers how the occurrence analyser implements
the binder-swap, by actually carrying out a substitution rather
than by adding a let-binding.  It's all described in
Note [The binder-swap substitution].

I did a few other things along the way

* Fix a bug in StgCse, which could allow a loop breaker to be CSE'd
  away.  See Note [Care with loop breakers] in StgCse.  I think it can
  only show up if occurrence analyser sets up bad loop breakers, but
  still.

* Better commenting in SimplUtils.prepareAlts

* A little refactoring in CoreUnfold; nothing significant
  e.g. rename CoreUnfold.mkTopUnfolding to mkFinalUnfolding

* Renamed CoreSyn.isFragileUnfolding to hasCoreUnfolding

* Move mkRuleInfo to CoreFVs

We observed respectively 4.6% and 5.9% allocation decreases for the following
tests:

Metric Decrease:
    T9961
    haddock.base
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/42d68364f66846969edf029f878875c10cdfe0b2">42d68364</a></strong>
<div>
<span>by Sebastian Graf</span>
<i>at 2020-04-02T01:46:34-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Preserve precise exceptions in strictness analysis

Fix #13380 and #17676 by

1. Changing `raiseIO#` to have `topDiv` instead of `botDiv`
2. Give it special treatment in `Simplifier.Util.mkArgInfo`, treating it
   as if it still had `botDiv`, to recover dead code elimination.

This is the first commit of the plan outlined in
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2525#note_260886.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/0a88dd11594b8d8fd20500d026e657a5f99dfdd2">0a88dd11</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-02T01:47:25-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix a pointer format string in RTS
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/5beac042b995b055a66bc16be536d9e920f6864d">5beac042</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-02T01:48:05-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Remove unused closure stg_IND_direct
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/88f38b03025386f0f1e8f5861eed67d80495168a">88f38b03</a></strong>
<div>
<span>by Ben Gamari</span>
<i>at 2020-04-02T01:48:42-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Session: Memoize stderrSupportsAnsiColors

Not only is this a reasonable efficiency measure but it avoids making
reentrant calls into ncurses, which is not thread-safe. See #17922.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/27740f24cb70fc14b00c1212c06642a144a6117d">27740f24</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-02T01:49:21-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Make Hadrian build with Cabal-3.2

GHC 8.10 ships with `Cabal-3.2.0.0`, so it would be convenient to
make Hadrian supporting building against 3.2.* instead of having to
rebuild the entirety of `Cabal-3.0.0.0`. There is one API change in
`Cabal-3.2.*` that affects Hadrian: the `synopsis` and `description`
functions now return `ShortText` instead of `String`. Since Hadrian
manipulates these `String`s in various places, I found that the
simplest fix was to use CPP to convert `ShortText` to `String`s
where appropriate.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4980200255dabf59ae537f10c55d19ef1a00bbdd">49802002</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-02T01:50:00-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Update Stack resolver for hadrian/build-stack

Broken by 57b888c0e90be7189285a6b078c30b26d0923809
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/30a63e79c65b023497af4fe2347149382c71829d">30a63e79</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-02T01:50:36-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix two ASSERT buglets in reifyDataCon

Two `ASSERT`s in `reifyDataCon` were always using `arg_tys`, but
`arg_tys` is not meaningful for GADT constructors. In fact, it's
worse than non-meaningful, since using `arg_tys` when reifying a
GADT constructor can lead to failed `ASSERT`ions, as #17305
demonstrates.

This patch applies the simplest possible fix to the immediate
problem. The `ASSERT`s now use `r_arg_tys` instead of `arg_tys`, as
the former makes sure to give something meaningful for GADT
constructors. This makes the panic go away at the very least. There
is still an underlying issue with the way the internals of
`reifyDataCon` work, as described in
https://gitlab.haskell.org/ghc/ghc/issues/17305#note_227023, but we
leave that as future work, since fixing the underlying issue is
much trickier (see
https://gitlab.haskell.org/ghc/ghc/issues/17305#note_227087).
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/ef7576c40f8de391ed8b1c81c38156202e6d17cf">ef7576c4</a></strong>
<div>
<span>by Zubin Duggal</span>
<i>at 2020-04-03T06:24:56-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add outputable instances for the types in GHC.Iface.Ext.Types, add -ddump-hie
flag to dump pretty printed contents of the .hie file

Metric Increase:
   hie002

Because of the regression on i386:

compile_time/bytes allocated increased from i386-linux-deb9 baseline @ HEAD~10:
    Expected    hie002 (normal) compile_time/bytes allocated: 583014888.0 +/-10%
    Lower bound hie002 (normal) compile_time/bytes allocated:   524713399
    Upper bound hie002 (normal) compile_time/bytes allocated:   641316377
    Actual      hie002 (normal) compile_time/bytes allocated:   877986292
    Deviation   hie002 (normal) compile_time/bytes allocated:        50.6 %
*** unexpected stat test failure for hie002(normal)
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9462452a4843a2c42fe055a0a7e274d5164d1dc0">9462452a</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-04-03T06:25:33-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Improve and refactor StgToCmm codegen for DataCons.

We now differentiate three cases of constructor bindings:

1)Bindings which we can "replace" with a reference to
  an existing closure. Reference the replacement closure
  when accessing the binding.
2)Bindings which we can "replace" as above. But we still
  generate a closure which will be referenced by modules
  importing this binding.
3)For any other binding generate a closure. Then reference
  it.

Before this patch 1) did only apply to local bindings and we
didn't do 2) at all.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a214d2142c1bafa71fe52cb3823351ff9322d336">a214d214</a></strong>
<div>
<span>by Moritz Bruder</span>
<i>at 2020-04-03T06:26:11-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Add singleton to NonEmpty in libraries/base

This adds a definition to construct a singleton non-empty list
(Data.List.NonEmpty) according to issue #17851.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/f7597aa0c028ced898ac97e344754dd961b70c57">f7597aa0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-03T06:26:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Testsuite: measure compiler stats for T16190

We were mistakenly measuring program stats
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/a485c3c4049fff09e989bfd7d2ba47035c92a69b">a485c3c4</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-03T06:26:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Move blob handling into StgToCmm

Move handling of big literal strings from CmmToAsm to StgToCmm. It
avoids the use of `sdocWithDynFlags` (cf #10143). We might need to move
this handling even higher in the pipeline in the future (cf #17960):
this patch will make it easier.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/cc2918a0407e1581e824ebd90a1fcbb0637d5744">cc2918a0</a></strong>
<div>
<span>by Sylvain Henry</span>
<i>at 2020-04-03T06:26:54-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Refactor CmmStatics

In !2959 we noticed that there was some redundant code (in GHC.Cmm.Utils
and GHC.Cmm.StgToCmm.Utils) used to deal with `CmmStatics` datatype
(before SRT generation) and `RawCmmStatics` datatype (after SRT
generation).

This patch removes this redundant code by using a single GADT for
(Raw)CmmStatics.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/9e60273db47364fc08aeb5a389caf67559e0d353">9e60273d</a></strong>
<div>
<span>by Maxim Koltsov</span>
<i>at 2020-04-03T06:27:32-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix haddock formatting in Control.Monad.ST.Lazy.Imp.hs
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/1b7e8a94cb3334fc0e513dec2db323f32c3a0713">1b7e8a94</a></strong>
<div>
<span>by Andreas Klebinger</span>
<i>at 2020-04-03T06:28:08-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Turn newlines into spaces for hadrian/ghci.

The newlines break the command on windows.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/4291bddaea3148908c55f235ee8978e1d9aa6f20">4291bdda</a></strong>
<div>
<span>by Simon Peyton Jones</span>
<i>at 2020-04-03T06:28:44-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Major improvements to the specialiser

This patch is joint work of Alexis King and Simon PJ.  It does some
significant refactoring of the type-class specialiser.  Main highlights:

* We can specialise functions with types like
     f :: Eq a => a -> Ord b => b => blah
  where the classes aren't all at the front (#16473).  Here we can
  correctly specialise 'f' based on a call like
     f @Int @Bool dEqInt x dOrdBool
  This change really happened in an earlier patch
     commit 2d0cf6252957b8980d89481ecd0b79891da4b14b
     Author: Sandy Maguire <sandy@sandymaguire.me>
     Date:   Thu May 16 12:12:10 2019 -0400
  work that this new patch builds directly on that work, and refactors
  it a bit.

* We can specialise functions with implicit parameters (#17930)
     g :: (?foo :: Bool, Show a) => a -> String
  Previously we could not, but now they behave just like a non-class
  argument as in 'f' above.

* We can specialise under-saturated calls, where some (but not all of
  the dictionary arguments are provided (#17966).  For example, we can
  specialise the above 'f' based on a call
     map (f @Int dEqInt) xs
  even though we don't (and can't) give Ord dictionary.

  This may sound exotic, but #17966 is a program from the wild, and
  showed significant perf loss for functions like f, if you need
  saturation of all dictionaries.

* We fix a buglet in which a floated dictionary had a bogus demand
  (#17810), by using zapIdDemandInfo in the NonRec case of specBind.

* A tiny side benefit: we can drop dead arguments to specialised
  functions; see Note [Drop dead args from specialisations]

* Fixed a bug in deciding what dictionaries are "interesting"; see
  Note [Keep the old dictionaries interesting]

This is all achieved by by building on Sandy Macguire's work in
defining SpecArg, which mkCallUDs uses to describe the arguments of
the call. Main changes:

* Main work is in specHeader, which marched down the [InBndr] from the
  function definition and the [SpecArg] from the call site, together.

* specCalls no longer has an arity check; the entire mechanism now
  handles unders-saturated calls fine.

* mkCallUDs decides on an argument-by-argument basis whether to
  specialise a particular dictionary argument; this is new.
  See mk_spec_arg in mkCallUDs.

It looks as if there are many more lines of code, but I think that
all the extra lines are comments!
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/40a85563a46c682eaab5fdf970f7c46afca78cb3">40a85563</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-03T18:26:19+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Revert accidental change in 9462452

[ci skip]
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/bd75e5da0f1f05f107325733b570bf28b379d2f2">bd75e5da</a></strong>
<div>
<span>by Ryan Scott</span>
<i>at 2020-04-04T07:07:58-04:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Enable ImpredicativeTypes internally when typechecking selector bindings

This is necessary for certain record selectors with higher-rank
types, such as the examples in #18005. See
`Note [Impredicative record selectors]` in `TcTyDecls`.

Fixes #18005.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/27bd807bf378af8976a7dad3c47e69acba38cf75">27bd807b</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-06T09:25:16+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Introduce a standard thunk for allocating strings

Currently for a top-level closure in the form

    hey = unpackCString# x

we generate code like this:

    Main.hey_entry() //  [R1]
             { info_tbls: [(c2T4,
                            label: Main.hey_info
                            rep: HeapRep static { Thunk }
                            srt: Nothing)]
               stack_info: arg_space: 8 updfr_space: Just 8
             }
         {offset
           c2T4: // global
               _rqm::P64 = R1;
               if ((Sp + 8) - 24 < SpLim) (likely: False) goto c2T5; else goto c2T6;
           c2T5: // global
               R1 = _rqm::P64;
               call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8;
           c2T6: // global
               (_c2T1::I64) = call "ccall" arg hints:  [PtrHint,
                                                        PtrHint]  result hints:  [PtrHint] newCAF(BaseReg, _rqm::P64);
               if (_c2T1::I64 == 0) goto c2T3; else goto c2T2;
           c2T3: // global
               call (I64[_rqm::P64])() args: 8, res: 0, upd: 8;
           c2T2: // global
               I64[Sp - 16] = stg_bh_upd_frame_info;
               I64[Sp - 8] = _c2T1::I64;
               R2 = hey1_r2Gg_bytes;
               Sp = Sp - 16;
               call GHC.CString.unpackCString#_info(R2) args: 24, res: 0, upd: 24;
         }
     }

This code is generated for every string literal. Only difference between
top-level closures like this is the argument for the bytes of the string
(hey1_r2Gg_bytes in the code above).

With this patch we introduce a standard thunk in the RTS, called
stg_MK_STRING_info, that does what `unpackCString# x` does, except it
gets the bytes address from the payload. Using this, for the closure
above, we generate this:

    Main.hey_closure" {
        Main.hey_closure:
            const stg_MK_STRING_info;
            const hey1_r1Gg_bytes;
            const 0;
            const 0;
    }

This is much smaller in code.
</pre>
</li>
<li>
<strong><a href="https://gitlab.haskell.org/ghc/ghc/-/commit/3c85c406977f018fba790b7fb7c1e14c1d6e0608">3c85c406</a></strong>
<div>
<span>by Ömer Sinan Ağacan</span>
<i>at 2020-04-06T10:00:17+03:00</i>
</div>
<pre class="commit-message" style="white-space: pre-wrap; margin: 0;">Fix std unpackCString# info tbl symbol, comment-out special case for non-top-lvl
</pre>
</li>
</ul>
<h4>30 changed files:</h4>
<ul>
<li class="file-stats">
<a href="#587d266bb27a4dc3022bbed44dfa19849df3044c">
.gitlab-ci.yml
</a>
</li>
<li class="file-stats">
<a href="#f73a4fa90a8eb153bccdcfcc9f63c15edcd66785">
compiler/GHC/Cmm.hs
</a>
</li>
<li class="file-stats">
<a href="#db697f6aea9f93f1583f1d5c62d25570a1e07f73">
compiler/GHC/Cmm/CLabel.hs
</a>
</li>
<li class="file-stats">
<a href="#92b713d88390e6ea489e24b6cff8a3960384c0d0">
compiler/GHC/Cmm/DebugBlock.hs
</a>
</li>
<li class="file-stats">
<a href="#47cba74ae8965f1665cd11bf2b023760ea27594e">
compiler/GHC/Cmm/Info.hs
</a>
</li>
<li class="file-stats">
<a href="#2d3721ad8de95e1144493ca545db846672cb109f">
compiler/GHC/Cmm/Info/Build.hs
</a>
</li>
<li class="file-stats">
<a href="#71e696f452eb493722d70306c6f304fc9b2f6a95">
compiler/GHC/Cmm/Parser.y
</a>
</li>
<li class="file-stats">
<a href="#00d7e888201d1d21d9b428cc9fd4aea68631c109">
compiler/GHC/Cmm/Ppr/Decl.hs
</a>
</li>
<li class="file-stats">
<a href="#f9f29a5a64a0b66967f0a7c538dbf8ad06a9f5bb">
compiler/GHC/Cmm/Utils.hs
</a>
</li>
<li class="file-stats">
<a href="#f71fa75baa7807186473f09c45a9ada1b72f4c6c">
compiler/GHC/CmmToAsm/PPC/CodeGen.hs
</a>
</li>
<li class="file-stats">
<a href="#3022d7d8a06ba257d13bbd18a3347522287aa684">
compiler/GHC/CmmToAsm/PPC/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#99b1dfe8e0e3d0c174cd8552df7d2ae70d35800a">
compiler/GHC/CmmToAsm/PPC/RegInfo.hs
</a>
</li>
<li class="file-stats">
<a href="#1684e8db5c0d415248dabe224ffe70205adc6b0f">
compiler/GHC/CmmToAsm/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#e76eae04dea432f874db91c25e4a5725d7cc127b">
compiler/GHC/CmmToAsm/SPARC/CodeGen.hs
</a>
</li>
<li class="file-stats">
<a href="#d021ec82e5a3150376cf05ea98f89bcf0daa611e">
compiler/GHC/CmmToAsm/SPARC/CodeGen/Gen32.hs
</a>
</li>
<li class="file-stats">
<a href="#90616aa9a81a082a329014ed30f6e887c8c55be7">
compiler/GHC/CmmToAsm/SPARC/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#13521cd94ac37285ab80cca8b3993ba32433db90">
compiler/GHC/CmmToAsm/SPARC/ShortcutJump.hs
</a>
</li>
<li class="file-stats">
<a href="#2bae5947e9412f6deebf4db7dcb89d780913130f">
compiler/GHC/CmmToAsm/X86/CodeGen.hs
</a>
</li>
<li class="file-stats">
<a href="#7b360ca84c1b9aaecc0f9de207a7698dc36514fe">
compiler/GHC/CmmToAsm/X86/Instr.hs
</a>
</li>
<li class="file-stats">
<a href="#335d279236d65dcf13f2bab3891e515cb803203c">
compiler/GHC/CmmToAsm/X86/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#76664ab267df4fc0bec2465efd78bf0afacfe3a7">
compiler/GHC/CmmToC.hs
</a>
</li>
<li class="file-stats">
<a href="#1aff3a222f2ec5c5498930c3d145b401cc300028">
compiler/GHC/CmmToLlvm.hs
</a>
</li>
<li class="file-stats">
<a href="#c74cd867f4159f4c755af854485b9cc98fbc55fe">
compiler/GHC/CmmToLlvm/Data.hs
</a>
</li>
<li class="file-stats">
<a href="#41223cea954a6fb02becb6018d5d7ff7467b31fc">
compiler/GHC/CmmToLlvm/Ppr.hs
</a>
</li>
<li class="file-stats">
<a href="#182d6a315e784018aa9c8b2ad736036b97bd5d48">
compiler/GHC/Core.hs
</a>
</li>
<li class="file-stats">
<a href="#783e5dae6e86931f06700fc088fb7d48c8a07386">
compiler/GHC/Core/Coercion.hs
</a>
</li>
<li class="file-stats">
<a href="#f10ed7a2470454dfdd8691a08beba67d8b78ee70">
compiler/GHC/Core/Coercion/Axiom.hs
</a>
</li>
<li class="file-stats">
<a href="#448d7f6e0151c2014de38dead3a902f511c45b75">
compiler/GHC/Core/FVs.hs
</a>
</li>
<li class="file-stats">
<a href="#91648438362e5a35363d2bb7abb04016dedd7d7e">
compiler/GHC/Core/FamInstEnv.hs
</a>
</li>
<li class="file-stats">
<a href="#36a42448a83a9d1f6df8475f03ead2eed199dd8e">
compiler/GHC/Core/Lint.hs
</a>
</li>
</ul>
<h5>The diff was not included because it is too large.</h5>

</div>
<div class="footer" style="margin-top: 10px;">
<p style="font-size: small; color: #777;">

<br>
<a href="https://gitlab.haskell.org/ghc/ghc/-/compare/2899512ac1489ae8208dbe44e01762bb852f3e49...3c85c406977f018fba790b7fb7c1e14c1d6e0608">View it on GitLab</a>.
<br>
You're receiving this email because of your account on gitlab.haskell.org.
If you'd like to receive fewer emails, you can
adjust your notification settings.



</p>
</div>
</body>
</html>