Skip to content
Snippets Groups Projects
  1. Nov 02, 2017
  2. Oct 31, 2017
    • Simon Peyton Jones's avatar
      Tidy up IfaceEqualityTyCon · 29ae8337
      Simon Peyton Jones authored
      This commit
      
        commit 85aa1f42
        Date:   Sun Oct 29 20:48:19 2017 -0400
          Fix #14390 by making toIfaceTyCon aware of equality
      
      was a bit over-complicated. This patch simplifies the (horribly
      ad-hoc) treatement of IfaceEqualityTyCon, and documents it better.
      
      No visible change in behaviour.
      29ae8337
  3. Oct 30, 2017
  4. Oct 29, 2017
    • Joachim Breitner's avatar
      Implement a dedicated exitfication pass #14152 · 0e953da1
      Joachim Breitner authored
      The idea is described in #14152, and can be summarized: Float the exit
      path out of a joinrec, so that the simplifier can do more with it.
      See the test case for a nice example.
      
      The floating goes against what the simplifier usually does, hence we
      need to be careful not inline them back.
      
      The position of exitification in the pipeline was chosen after a small
      amount of experimentation, but may need to be improved. For example,
      exitification can allow rewrite rules to fire, but for that it would
      have to happen before the `simpl_phases`.
      
      Perf.haskell.org reports these nice performance wins:
      
          Nofib allocations
          fannkuch-redux    78446640  - 99.92%      64560
          k-nucleotide     109466384  - 91.32%    9502040
          simple            72424696  -  5.96%   68109560
      
          Nofib instruction counts
          fannkuch-redux  1744331636  -  3.86% 1676999519
          k-nucleotide    2318221965  -  6.30% 2172067260
          scs             1978470869  -  3.35% 1912263779
          simple           669858104  -  3.38%  647206739
          spectral-norm    186423292  -  5.37%  176411536
      
      Differential Revision: https://phabricator.haskell.org/D3903
      0e953da1
    • Joachim Breitner's avatar
      simplNonRecJoinPoint: Handle Shadowing correctly · 97ca0d24
      Joachim Breitner authored
      Previously, (since 33452dfc), simplNonRecJoinPoint would do the wrong
      thing in the presence of shadowing: It analyzed the RHS of a join
      binding with the environment for the body. In particular, with
      
          foo x =
            join x = x * x
            in x
      
      where there is shadowing, it renames the inner x to x1, and should
      produce
      
          foo x =
            join x1 = x * x
            in x1
      
      but because the substitution (x ↦ x1) is also used on the RHS we get the
      bogus
      
          foo x =
            join x1 = x1 * x1
            in x1
      
      Fixed this by adding a `rhs_se` parameter, analogous to `simplNonRecE`
      and `simplLazyBind`.
      
      Differential Revision: https://phabricator.haskell.org/D4130
      97ca0d24
  5. Oct 28, 2017
  6. Oct 27, 2017
    • niteria's avatar
      Make tagForCon non-linear · faf60e85
      niteria authored
      Computing the number of constructors for TyCon is linear
      in the number of constructors.
      That's wasteful if all you want to check is if that
      number is smaller than what fits in tag bits
      (usually 8 things).
      
      What this change does is to use a function that can
      determine the ineqaulity without computing the size.
      
      This improves compile time on a module with a
      data type that has 10k constructors.
      The variance in total time is (suspiciously) high,
      but going by the best of 3 the numbers are 8.186s vs 7.511s.
      For 1000 constructors the difference isn't noticeable:
      0.646s vs 0.624s.
      The hot spots were cgDataCon and cgEnumerationTyCon
      where tagForCon is called in a loop.
      
      One alternative would be to pass down the size.
      
      Test Plan: harbormaster
      
      Reviewers: bgamari, simonmar, austin
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4116
      faf60e85
    • Ben Gamari's avatar
      relnotes: Fix a few minor formatting issues · acd355a8
      Ben Gamari authored
      acd355a8
    • Simon Marlow's avatar
      ApplicativeDo: handle BodyStmt (#12143) · 41f90559
      Simon Marlow authored
      Summary:
      It's simple to treat BodyStmt just like a BindStmt with a wildcard
      pattern, which is enough to fix #12143 without going all the way to
      using `<*` and `*>` (#10892).
      
      Test Plan:
      * new test cases in `ado004.hs`
      * validate
      
      Reviewers: niteria, simonpj, bgamari, austin, erikd
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #12143
      
      Differential Revision: https://phabricator.haskell.org/D4128
      41f90559
    • Simon Peyton Jones's avatar
      Fix an exponential-blowup case in SpecConstr · 7d7d94fb
      Simon Peyton Jones authored
      Trac #14379 showed a case where use of "forcing" to do
      "damn the torpedos" specialisation without resource limits
      (which 'vector' does a lot) led to exponential blowup.
      
      The fix is easy.  Finding it wasn't.  See Note [Forcing
      specialisation] and the one-line change in decreaseSpecCount.
      7d7d94fb
    • Simon Peyton Jones's avatar
      355318c3
  7. Oct 26, 2017
  8. Oct 25, 2017
    • Tobias Dammers's avatar
      Factor out readField (#14364) · dbd81f7e
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      Improves compiler performance of deriving Read instances, as suggested
      in the issue.
      
      Additionally, we introduce `readSymField`, a companion to `readField`
      that parses symbol-type fields (where the field name is a symbol, e.g.
      `(#)`, rather than an alphanumeric identifier. The decision between
      these two functions is made a compile time, because we already know
      which one we need based on the field name.
      
      Reviewers: austin, hvr, bgamari, RyanGlScott
      
      Reviewed By: bgamari
      
      Subscribers: RyanGlScott, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4108
      dbd81f7e
    • Douglas Wilson's avatar
      base: Enable listToMaybe to fuse via foldr/build · 4c06ccb7
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Consider whether this is a good idea.
      
      Reviewers: austin, hvr, bgamari, nomeata
      
      Reviewed By: bgamari, nomeata
      
      Subscribers: nomeata, rwbarton, thomie
      
      GHC Trac Issues: #14387
      
      Differential Revision: https://phabricator.haskell.org/D4126
      4c06ccb7
    • Ben Gamari's avatar
      user-guide: Clarify default optimization flags · 2c23fff2
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Begins to fix #14214.
      
      [skip ci]
      
      Test Plan: Read it.
      
      Reviewers: austin
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14214
      
      Differential Revision: https://phabricator.haskell.org/D4098
      2c23fff2
    • Alec Theriault's avatar
      Fix a bug in 'alexInputPrevChar' · 821adee1
      Alec Theriault authored and Ben Gamari's avatar Ben Gamari committed
      The lexer hacks around unicode by squishing any character into a 'Word8'
      and then storing the actual character in its state. This happens at
      'alexGetByte'.
      
      That is all and well, but we ought to be careful that the characters we
      retrieve via 'alexInputPrevChar' also fit this convention.
      
      In fact, #13986 exposes nicely what can go wrong: the regex in the left
      context of the type application rule uses the '$idchar' character set
      which relies on the unicode hack. However, a left context corresponds
      to a call to 'alexInputPrevChar', and we end up passing full blown
      unicode characters to '$idchar', despite it not being equipped to deal
      with these.
      
      Test Plan: Added a regression test case
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13986
      
      Differential Revision: https://phabricator.haskell.org/D4105
      821adee1
    • Daishi Nakajima's avatar
      Implement `-Wpartial-fields` warning (#7169) · f7f270eb
      Daishi Nakajima authored and Ben Gamari's avatar Ben Gamari committed
      Warning on declaring a partial record selector.
      However, disable warn with field names that start with underscore.
      
      Test Plan: Added 1 test case.
      
      Reviewers: austin, bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: goldfire, simonpj, duog, rwbarton, thomie
      
      GHC Trac Issues: #7169
      
      Differential Revision: https://phabricator.haskell.org/D4083
      f7f270eb
    • Tobias Dammers's avatar
      Performance improvements linear regAlloc (#7258) · df636682
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      When allocating and potentially spilling registers, we need to check
      the desired allocations against current allocations to decide where we
      can spill to, cq. which allocations we can toss and if so, how.
      Previously, this was done by walking the Cartesian product of the
      current allocations (`assig`) and the allocations to keep (`keep`),
      which has quadratic complexity. This patch introduces two improvements:
      
      1. pre-filter the `assig` list, because we are only interested in two
      types of allocations (in register, and in register+memory), which will
      only make up a small and constant portion of the list; and
      2. use set / map operations instead of lists, which reduces algorithmic
      complexity.
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4109
      df636682
    • Douglas Wilson's avatar
      Fix space leak in BinIface.getSymbolTable · 1c15d8ed
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      Replace a call to mapAccumR, which uses linear stack space, with a
      gadget that uses constant space.
      
      Remove an unused parameter from fromOnDiskName.
      
      The tests T1292_imports and T4239 are now reporting imported names in a
      different order. I don't completely understand why, but I presume it is
      because the symbol tables are now read more strictly. The new order
      seems better in T1792_imports, and equally random in T4239.
      
      There are several performance test improvements.
      
      Test Plan: ./validate
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: alexbiehl, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4124
      1c15d8ed
    • Tamar Christina's avatar
      Windows: Update the mirror script to generate hashes and use mirror fallback · 980e1270
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      This fixes the mirror script so it correctly queries haskell.org and if
      packages aren't found check repo.msys2.org.
      
      Also the mirror functionality now generates the md5 hashes after a
      mirror fetch that can be placed in the md5sums file.
      
      Test Plan:
       mk/get-win32-tarballs.sh fetch mirror
      
       and ./validate
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4118
      980e1270
    • Tobias Dammers's avatar
      Make layLeft and reduceDoc stricter (#7258) · 2a4c24e4
      Tobias Dammers authored and Ben Gamari's avatar Ben Gamari committed
      Making the pretty-printer based assembly output stricter in
      strategically chosen locations produces a minor performance improvement
      when compiling large derived Read instance (on the order of 5-10%).
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D4111
      2a4c24e4
    • Andreas Klebinger's avatar
      Add info about Github pull requests. · bd53b488
      Andreas Klebinger authored
      bd53b488
    • Ben Gamari's avatar
      bf83435b
    • Joachim Breitner's avatar
      Make language extensions their own category in the documentation · 61f1b46e
      Joachim Breitner authored
      I.e. instead of
      
          .. ghc-flag:: -XUnboxedTuples
              :shortdesc: Enable the use of unboxed tuple syntax.
              :type: dynamic
              :reverse: -XNoUnboxedTuples
              :category:
      
      one simply writes
      
          .. extension:: UnboxedTuples
              :shortdesc: Enable the use of unboxed tuple syntax.
      
      This allows language extensions to be referenced as
      
          If :extension:`UnboxedTuples` is enabled, then...
      
      This directive still creates the entries for the `-XUnboxedTuples` flag,
      so in particular,
      
          Set :ghc-flag:`-XUnboxedTuples` if you have to.
      
      still works, and lists of flags in general (e.g. for the manpage)
      include these.
      
      I also removed lots of links from the shortdesc of the extensions, when
      this link simply points to the section where the extension is defined.
      
      I removed the list of `-X` flags from the flag reference table, but added a
      table of extension under “10.1. Language options”
      
      Lots of text in the manual now refers to “extension `Foo`” rather than
      “flag `-XFoo`”.
      
      I consider `-XFoo` a historic artifact that stems from when language
      extensions were really just flags. These days, the use of `-XFoo` is
      (IMHO) deprecated: You should be using `LANGUAGE Foo`, or maybe the
      appropriate field in a `.cabal` file. See 9278994a which did this change
      to error messages already.
      
      Differential Revision: https://phabricator.haskell.org/D4112
      61f1b46e
    • Tamar Christina's avatar
      Revert "Update Win32 version for GHC 8.4." · b1ad0bb3
      Tamar Christina authored
      This reverts commit 561bdca1.
      
      submodule
      b1ad0bb3
Loading