Skip to content
Snippets Groups Projects
  1. May 16, 2018
    • Simon Marlow's avatar
      Merge FUN_STATIC closure with its SRT · 838b6903
      Simon Marlow authored
      Summary:
      The idea here is to save a little code size and some work in the GC,
      by collapsing FUN_STATIC closures and their SRTs.
      
      This is (4) in a series; see D4632 for more details.
      
      There's a tradeoff here: more complexity in the compiler in exchange
      for a modest code size reduction (probably around 0.5%).
      
      Results:
      * GHC binary itself (statically linked) is 1% smaller
      * -0.2% binary sizes in nofib (-0.5% module sizes)
      
      Full nofib results comparing D4634 with this: P177 (ignore runtimes,
      these aren't stable on my laptop)
      
      Test Plan: validate, nofib
      
      Reviewers: bgamari, niteria, simonpj, erikd
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4637
      838b6903
    • Simon Marlow's avatar
      Save a word in the info table on x86_64 · 2b0918c9
      Simon Marlow authored
      Summary:
      An info table with an SRT normally looks like this:
      
          StgWord64 srt_offset
          StgClosureInfo layout
          StgWord32 layout
          StgWord32 has_srt
      
      But we only need 32 bits for srt_offset on x86_64, because the small
      memory model requires that code segments are at most 2GB. So we can
      optimise this to
      
          StgClosureInfo layout
          StgWord32 layout
          StgWord32 srt_offset
      
      saving a word.  We can tell whether the info table has an SRT or not,
      because zero is not a valid srt_offset, so zero still indicates that
      there's no SRT.
      
      Test Plan:
      * validate
      * For results, see D4632.
      
      Reviewers: bgamari, niteria, osa1, erikd
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4634
      2b0918c9
    • Simon Marlow's avatar
      Allow CmmLabelDiffOff with different widths · fbd28e2c
      Simon Marlow authored
      Summary:
      This change makes it possible to generate a static 32-bit relative label
      offset on x86_64. Currently we can only generate word-sized label
      offsets.
      
      This will be used in D4634 to shrink info tables.  See D4632 for more
      details.
      
      Test Plan: See D4632
      
      Reviewers: bgamari, niteria, michalt, erikd, jrtc27, osa1
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4633
      fbd28e2c
    • Simon Marlow's avatar
      An overhaul of the SRT representation · eb8e692c
      Simon Marlow authored
      Summary:
      - Previously we would hvae a single big table of pointers per module,
        with a set of bitmaps to reference entries within it. The new
        representation is identical to a static constructor, which is much
        simpler for the GC to traverse, and we get to remove the complicated
        bitmap-traversal code from the GC.
      
      - Rewrite all the code to generate SRTs in CmmBuildInfoTables, and
        document it much better (see Note [SRTs]). This has been something
        I've wanted to do since we moved to the new code generator, I
        finally had the opportunity to finish it while on a transatlantic
        flight recently :)
      
      There are a series of 4 diffs:
      
      1. D4632 (this one), which does the bulk of the changes
      
      2. D4633 which adds support for smaller `CmmLabelDiffOff` constants
      
      3. D4634 which takes advantage of D4632 and D4633 to save a word in
         info tables that have an SRT on x86_64. This is where most of the
         binary size improvement comes from.
      
      4. D4637 which makes a further optimisation to merge some SRTs with
         static FUN closures.  This adds some complexity and the benefits
         are fairly modest, so it's not clear yet whether we should do this.
      
      Results (after (3), on x86_64)
      
      - GHC itself (staticaly linked) is 5.2% smaller
      
      - -1.7% binary sizes in nofib, -2.9% module sizes. Full nofib results: P176
      
      - I measured the overhead of traversing all the static objects in a
        major GC in GHC itself by doing `replicateM_ 1000 performGC` as the
        first thing in `Main.main`.  The new version was 5-10% faster, but
        the results did vary quite a bit.
      
      - I'm not sure if there's a compile-time difference, the results are
        too unreliable.
      
      Test Plan: validate
      
      Reviewers: bgamari, michalt, niteria, simonpj, erikd, osa1
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4632
      eb8e692c
    • Simon Marlow's avatar
      Force findPtr to be included in the binary · a18e7dfa
      Simon Marlow authored
      Summary: A better alternative to D4657.
      
      Test Plan:
      ```
      cd testsuite/tests/codeGen/should_run
      ../../../../inplace/bin/ghc-stage2 -debug cgrun001
      nm cgrun001 | grep findPtr
      ```
      
      Reviewers: bgamari, Phyx, erikd
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4683
      a18e7dfa
  2. May 15, 2018
    • Artem Pelenitsyn's avatar
      Less Tc inside simplCore (Phase 1 for #14391) · bb3fa2d1
      Artem Pelenitsyn authored and Ben Gamari's avatar Ben Gamari committed
      Simplifier depends on typechecker in two points: `thNameToGhcName`
      (`lookupThName_maybe`, in particular)  and `lookupGlobal`. We want to
      cut the ties in two steps.
      
      1. (Presented in this commit), reimplement both functions in a way that
      doesn't use typechecker.
      
      2. (Should follow), do code moving: a) `lookupGlobal` should go in some
      typechecker-free place; b) `thNameToGhcName` should leave simplifier,
      because it is not used there at all (probably, it should be placed
      somewhere where `GhcPlugins` can see it -- this is suggested by Joachim
      on Trac).
      
      Details
      =======
      
      We redesigned lookup interface a bit so that it exposes some
      `IO`-equivalents of `Tc`-features in use.
      
      First, `CoreMonad.hs` still calls `lookupGlobal` which is no longer
      bound to the typechecker monad, but still resides in `TcEnv.hs` — it
      should be moved out of Tc-land at some point (“Phase 2”) in the
      future in order to achieve its part of the #14391's goal.
      
      Second, `lookupThName_maybe` is eliminated from `CoreMonad.hs`
      completely; this already achieves its part of the goal of #14391. Its
      client, though, `thNameToGhcName`, is better to be moved in the future
      also, for it is not used in the `CoreMonad.hs` (or anywhere else)
      anyway. Joachim suggested “any module reexported by GhcPlugins (or
      maybe even that module itself)”.
      
      As a side goal, we removed `initTcForLookup` which was instrumental for
      the past version of `lookupGlobal`. This, in turn, called for pushing
      some more parts of the lookup interface from the `Tc`-monad to `IO`,
      most notably, adding `IO`-version of `lookupOrig` and pushing
      `dataConInfoPtrToName` to `IO`. The `lookupOrig` part, in turn,
      triggered a slight redesign of name cache updating interface: we now
      have both, `updNameCacheIO` and `updNameCacheTc`, both accepting `mod`
      and `occ` to force them inside, instead of more error-prone outside
      before. But all these hardly have to do anything with #14391, mere
      refactoring.
      
      Reviewers: simonpj, nomeata, bgamari, hvr
      
      Reviewed By: simonpj, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14391
      
      Differential Revision: https://phabricator.haskell.org/D4503
      bb3fa2d1
    • Sebastian Graf's avatar
      Algebraically simplify add/sub with carry/overflow · bb338f2e
      Sebastian Graf authored and Ben Gamari's avatar Ben Gamari committed
      Previously, the `{add,sub}{Int,Word}C#` PrimOps weren't handled
      in PrelRules (constant folding and algebraic simplification) at all.
      This implements the necessary logic, so that using these primitives
      isn't too punishing compared to their well-optimised, overflow-unaware
      counterparts.
      
      This is so that using these primitives in `enumFromThenTo @Int` can
      be optimized by constant folding, reducing closure sizes.
      
      Reviewers: bgamari, simonpj, hsyl20
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: AndreasK, thomie, carter
      
      GHC Trac Issues: #8763
      
      Differential Revision: https://phabricator.haskell.org/D4605
      bb338f2e
    • Azel's avatar
      Calling GetLastError() on Windows for socket IO (trac issue #12012) · 01b15b88
      Azel authored
      For the threaded RTS, putting a private copy of the throwErrno
      series in GHC.IO.FD which gets if the operation was on a socket,
      so that we can call c_maperrno if need be.
      For the non-threaded RTS, if memory serves we call GetLastError()
      in case of an error on socket IO. However, we don't do the translation
      ErrCode :left_right_arrow:
      
       Errno currently (and besides, it's a primop) so we do it if
      needed through c_maperrno_func in the asynchronous read/write
      functions.
      
      Signed-off-by: default avatarARJANEN Loïc Jean David <arjanen.loic@gmail.com>
      
      Reviewers: ekmett, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie, carter
      
      GHC Trac Issues: #12012
      
      Differential Revision: https://phabricator.haskell.org/D4639
      01b15b88
    • Ben Gamari's avatar
      testsuite: Disable T14697 on Windows · af986f9d
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Validate on Windows
      
      Subscribers: thomie, carter
      
      GHC Trac Issues: #14697, #15072
      
      Differential Revision: https://phabricator.haskell.org/D4619
      af986f9d
    • Kirill Zaborsky's avatar
      More explicit comment on switch in registerDelay · 1154c9b6
      Kirill Zaborsky authored and Ben Gamari's avatar Ben Gamari committed
      1154c9b6
    • Ben Gamari's avatar
      Ensure that RTS cabal file reflects dependency on libnuma · 45ad0c39
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Validate with Hadrian and `libnuma` support
      
      Reviewers: snowleopard, hvr, erikd, simonmar
      
      Subscribers: izgzhen, alpmestan, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4616
      45ad0c39
    • Ben Gamari's avatar
      Revert "Simplify callSiteInline a little" · 9dbf66d7
      Ben Gamari authored
      This lead to some rather significant performance regressions.
      Specifically,
      
          bytes allocated value is too high:
              Expected    T5631(normal) bytes allocated: 1106015512 +/-5%
              Lower bound T5631(normal) bytes allocated: 1050714736
              Upper bound T5631(normal) bytes allocated: 1161316288
              Actual      T5631(normal) bytes allocated: 1164953208
              Deviation   T5631(normal) bytes allocated:        5.3 %
          *** unexpected stat test failure for T5631(normal)
          max_bytes_used value is too high:
              Expected    T9630(normal) max_bytes_used: 35324712 +/-15%
              Lower bound T9630(normal) max_bytes_used: 30026005
              Upper bound T9630(normal) max_bytes_used: 40623419
              Actual      T9630(normal) max_bytes_used: 43490984
              Deviation   T9630(normal) max_bytes_used:     23.1 %
          *** unexpected stat test failure for T9630(normal)
      
      This reverts commit 7271db46.
      This reverts commit b750dcc5.
      This reverts commit 33de71fa.
      9dbf66d7
    • Ben Gamari's avatar
      testsuite: Fix expected allocations of T9020 and T12425 · df6670e7
      Ben Gamari authored
      These were both improved by d92c7556 but the
      changes were lost due to merge silliness.
      df6670e7
    • Simon Peyton Jones's avatar
      Tidy up error suppression · f49f90bb
      Simon Peyton Jones authored
      Trac #15152 showed that when a flag turned an error into a warning, we
      were still (alas) suppressing subequent errors; includign their
      essential addTcEvBind.  That led (rightly) to a Lint error.
      
      This patch fixes it, and incidentally tidies up an ad-hoc special
      case of out-of-scope variables (see the old binding for
      'out_of_scope_killer' in 'tryReporters').
      
      No test, because the problem was only shown up when turning
      inaccessible code into a warning.
      f49f90bb
  3. May 14, 2018
    • Sergei Trofimovich's avatar
      rts: export new absentSumFieldError from base · 79bbb23f
      Sergei Trofimovich authored
      
      commit b2ff5dde "Fix #15038"
      added new stable closure 'absentSumFieldError_closure' to
      base package. This closure is used in rts package.
      
      Unfortunately the symbol was not explicitly exported and build
      failed on windows as:
      
      ```
      "inplace/bin/ghc-stage1" -o ...hsc2hs.exe ...
      rts/dist/build/libHSrts.a(RtsStartup.o): In function `hs_init_ghc':
      
      rts/RtsStartup.c:272:0: error:
           undefined reference to `base_ControlziExceptionziBase_absentSumFieldError_closure'
          |
      272 |     getStablePtr((StgPtr)absentSumFieldError_closure);
          | ^
      
      ```
      
      This change adds 'absentSumFieldError_closure' to explicit export
      into libHSbase.def.
      
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      79bbb23f
    • Tobias Dammers's avatar
      Fix performance regressions from #14737 · d92c7556
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      See #15019. When removing an unnecessary type equality check in #14737,
      several regression tests failed. The cause was that some coercions that
      are actually Refl coercions weren't passed in as such, which made the
      equality check needlessly complex (Refl coercions can be discarded in
      this particular check immediately, without inspecting the types at all).
      
      We fix that, and get additional performance improvements for free.
      
      Reviewers: goldfire, bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: simonpj, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4635
      d92c7556
    • Ben Gamari's avatar
      Revert "rts: Compile with gcc -Og" · 1e272094
      Ben Gamari authored
      This reverts commit d4abd031.
      1e272094
    • Nolan's avatar
      Fix #14973 · e408d03b
      Nolan authored
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4661
      e408d03b
    • Sergei Trofimovich's avatar
      utils/fs: use <sys/stat.h>, not <sys\stat.h> · 6d57a92f
      Sergei Trofimovich authored
      
      Fix cross-compilation failure from linux to windows:
      ```
        CC utils/unlit/dist-install/build/fs.o
      utils/unlit/fs.c:24:10: fatal error: sys\stat.h: No such file or directory
       #include <sys\stat.h>
                ^~~~~~~~~~~~
      ```
      
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      6d57a92f
    • David Feuer's avatar
      Improve some Foldable methods for NonEmpty · b7139869
      David Feuer authored
      * `length` is improved by using the default definition,
        while `foldr1` is improved by using a custom one.
      
      * Several methods had useless lazy pattern matches
        (i.e., the functions were actually strict in those arguments).
        Remove `~`s to clarify.
      
      Reviewers: hvr, bgamari, mpickering, nomeata
      
      Reviewed By: bgamari
      
      Subscribers: ygale, rwbarton, thomie, carter
      
      GHC Trac Issues: #15131
      
      Differential Revision: https://phabricator.haskell.org/D4677
      b7139869
    • Alp Mestanogullari's avatar
      Fix another batch of `./validate --slow` failures · ca3d3039
      Alp Mestanogullari authored and Ben Gamari's avatar Ben Gamari committed
      A rather detailed summary can be found at:
      
          https://gist.github.com/alpmestan/be82b47bb88b7dc9ff84105af9b1bb82
      
      This doesn't fix all expectation mismatches yet, but we're down to about
      20 mismatches with my previous patch and this one, as opposed to ~150
      when I got started.
      
      Test Plan: ./validate --slow
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: thomie, carter
      
      GHC Trac Issues: #14890
      
      Differential Revision: https://phabricator.haskell.org/D4636
      ca3d3039
    • Herbert Valerio Riedel's avatar
      Add support for opting out of package environments · 8f3c149d
      Herbert Valerio Riedel authored and Ben Gamari's avatar Ben Gamari committed
      This implements the first part proposed in #13753:
      
      Define a special magic "null" environment, which instructs GHC to ignore
      any package environment files. To this end, I propose to use the name
      `-` (i.e. a single dash), as that is more portable than using the empty
      string for environment variables. In other words, a
      
      - `-package-env -` CLI flag, or a
      - `GHC_ENVIRONMENT=-` env var (unless a `-package-env` flag is present)
      
      would inhibit GHC from looking up and interpreting any package
      environment files from the filesystem; this is the equivalent of
      `-ignore-dot-ghci` for package environment files.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13753
      
      Differential Revision: https://phabricator.haskell.org/D4690
      8f3c149d
    • Ben Gamari's avatar
      ghc-pkg: Configure handle encodings · cf88c2b1
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This fixes #15021 using a the same approach as was used to fix the issue
      in ghc (#10762).
      
      Test Plan: Validate on Windows as user whose username contains
      non-ASCII characters
      
      Reviewers: simonmar
      
      Reviewed By: simonmar
      
      Subscribers: lehins, thomie, carter
      
      GHC Trac Issues: #15021
      
      Differential Revision: https://phabricator.haskell.org/D4642
      cf88c2b1
    • Ryan Scott's avatar
      Fix #14875 by introducing PprPrec, and using it · 21e1a00c
      Ryan Scott authored
      Trying to determine when to insert parentheses during TH
      conversion is a bit of a mess. There is an assortment of functions
      that try to detect this, such as:
      
      * `hsExprNeedsParens`
      * `isCompoundHsType`
      * `hsPatNeedsParens`
      * `isCompoundPat`
      * etc.
      
      To make things worse, each of them have slightly different semantics.
      Plus, they don't work well in the presence of explicit type
      signatures, as #14875 demonstrates.
      
      All of these problems can be alleviated with the use of an explicit
      precedence argument (much like what `showsPrec` currently does). To
      accomplish this, I introduce a new `PprPrec` data type, and define
      standard predences for things like function application, infix
      operators, function arrows, and explicit type signatures (that last
      one is new). I then added `PprPrec` arguments to the various
      `-NeedsParens` functions, and use them to make smarter decisions
      about when things need to be parenthesized.
      
      A nice side effect is that functions like `isCompoundHsType` are
      now completely unneeded, since they're simply aliases for
      `hsTypeNeedsParens appPrec`. As a result, I did a bit of refactoring
      to remove these sorts of functions. I also did a pass over various
      utility functions in GHC for constructing AST forms and used more
      appropriate precedences where convenient.
      
      Along the way, I also ripped out the existing `TyPrec`
      data type (which was tailor-made for pretty-printing `Type`s) and
      replaced it with `PprPrec` for consistency.
      
      Test Plan: make test TEST=T14875
      
      Reviewers: alanz, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14875
      
      Differential Revision: https://phabricator.haskell.org/D4688
      21e1a00c
    • Matthew Pickering's avatar
      Add note documenting refineDefaultAlt · bf6cad8b
      Matthew Pickering authored
      Reviewers: sjakobi, bgamari
      
      Reviewed By: sjakobi
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4687
      bf6cad8b
    • David Feuer's avatar
      Clarify what the FFI spec says · 48dee7c9
      David Feuer authored
      Section 10.1.1 claimed that
      
      > The FFI addendum stipulates that an implementation is free to
      implement an unsafe call by performing a safe call ...
      
      Reading through the FFI addendum (and the Haskell 2010 Report, which
      integrates it), I see no such stipulation. I think this explains the
      situation a bit better.
      
      [ci skip]
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4656
      48dee7c9
    • Chaitanya Koparkar's avatar
      GHCi: Include a note in the hint to expose a hidden package · 30c887d3
      Chaitanya Koparkar authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: validate
      
      Reviewers: bgamari, RyanGlScott, osa1
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15055
      
      Differential Revision: https://phabricator.haskell.org/D4669
      30c887d3
    • Ben Gamari's avatar
      rts: Compile with gcc -Og · d4abd031
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This optimisation level is specifically designed to provide the benefits
      of optimisation without the obfuscation that sometimes results.
      
      Test Plan: Validate
      
      Reviewers: simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4675
      d4abd031
  4. May 13, 2018
    • David Feuer's avatar
      Remove unused things from utils/Digraph · cdbe00fe
      David Feuer authored
      `utils/Digraph` had a bunch of code that wasn't actually being used,
      much of which wasn't documented at all, some of which was clearly
      ill-considered, and some of which was documented as being inefficient.
      
      Remove all unused code from that module except for the obvious and
      innocuous `emptyG`.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4676
      cdbe00fe
    • David Feuer's avatar
      Fix changelog message for asinh · 2828dbf4
      David Feuer authored
      Reviewers: bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4678
      2828dbf4
    • Michal Terepeta's avatar
      Fix a few GCC warnings · eb39f988
      Michal Terepeta authored and Ben Gamari's avatar Ben Gamari committed
      
      GCC 8 now generates warnings for incompatible function pointer casts
      [-Werror=cast-function-type]. Apparently there are a few of those in rts
      code, which makes `./validate` unhappy (since we compile with `-Werror`)
      
      This commit tries to fix these issues by changing the functions to have
      the correct type (and, if necessary, moving the casts into those
      functions).
      
      For instance, hash/comparison function are declared (`Hash.h`) to take
      `StgWord` but we want to use `StgWord64[2]` in `StaticPtrTable.c`.
      Instead of casting the function pointers, we can cast the `StgWord`
      parameter to `StgWord*`. I think this should be ok since `StgWord`
      should be the same size as a pointer.
      
      Signed-off-by: default avatarMichal Terepeta <michal.terepeta@gmail.com>
      
      Test Plan: ./validate
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4673
      eb39f988
    • Sylvain Henry's avatar
      Refactor LitString · 7c665f9c
      Sylvain Henry authored
      Refactor LitString so that the string length is computed at most once
      and then stored.
      
      Also remove strlen and memcmp wrappers (it seems like they were a
      workaround for a very old GCC when using -fvia-C).
      
      Bumps haddock submodule.
      
      Reviewers: bgamari, dfeuer, nickkuk
      
      Reviewed By: bgamari, nickkuk
      
      Subscribers: nickkuk, dfeuer, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4630
      7c665f9c
    • Ben Gamari's avatar
      Bump array submodule · 21884270
      Ben Gamari authored
      21884270
    • Ben Gamari's avatar
      TcInteract: Ensure that tycons have representations before solving for Typeable · f0212a93
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Summary: This fixes #15067.
      
      Test Plan: Validate
      
      Subscribers: thomie, carter, RyanGlScott
      
      GHC Trac Issues: #15067
      
      Differential Revision: https://phabricator.haskell.org/D4623
      f0212a93
    • Ben Gamari's avatar
      base: Fix handling of showEFloat (Just 0) · 9039f847
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Previously `showEFloat (Just 0) pi ""` would produce `3.0e0`. Of
      course, this
      blatantly disrespects the user's request to print with zero digits of
      precision.
      Fix this.
      
      This is tested by base's `num008` testcase.
      
      Test Plan: Validate
      
      Reviewers: hvr
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15115
      
      Differential Revision: https://phabricator.haskell.org/D4665
      9039f847
    • Matthew Pickering's avatar
      Simplify -ddump-json implementation · 6ab7cf99
      Matthew Pickering authored and Ben Gamari's avatar Ben Gamari committed
      This patch takes the much simpler route of whenever the compiler tries
      to output something. We just dump a JSON document there and then.
      
      I think this should be sufficient to work with and anything more refined
      quickly got complicated as it was necessary to demarcate message scopes
      and so on.
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: bgamari
      
      Subscribers: Phyx, dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #14078
      
      Differential Revision: https://phabricator.haskell.org/D4532
      6ab7cf99
    • Herbert Valerio Riedel's avatar
      Emit info-level log message when package envs are loaded · 00049e2d
      Herbert Valerio Riedel authored
      A common complaint with the new package environment files feature is
      that it's not obvious when package environments have been picked up.
      This patch applies the same strategy that was already used for `.ghci` files
      (which exhibit similar potential for confusion, c.f. #11389) to package
      environment files.
      
      For instance, this new notification looks like below for a GHCi invocation which
      loads both, a GHCi configuration as well as a package environment:
      
        GHCi, version 8.5.20180512: http://www.haskell.org/ghc/  :? for help
        Loaded package environment from /tmp/parsec-3.1.13.0/.ghc.environment.x86_64-linux-8.5.20180512
        Loaded GHCi configuration from /home/hvr/.ghci
        Prelude>
      
      Addresses #15145
      
      Reviewed By: bgamari, angerman
      
      GHC Trac Issues: #15145
      
      Differential Revision: https://phabricator.haskell.org/D4689
      00049e2d
  5. May 12, 2018
Loading