Skip to content
Snippets Groups Projects
  1. Apr 29, 2017
  2. Apr 28, 2017
    • Simon Peyton Jones's avatar
      Improve code generation for conditionals · 6d14c148
      Simon Peyton Jones authored and David Feuer's avatar David Feuer committed
      This patch in in preparation for the fix to Trac #13397
      
      The code generator has a special case for
        case tagToEnum (a>#b) of
          False -> e1
          True  -> e2
      
      but it was not doing nearly so well on
        case a>#b of
          DEFAULT -> e1
          1#      -> e2
      
      This patch arranges to behave essentially identically in
      both cases.  In due course we can eliminate the special
      case for tagToEnum#, once we've completed Trac #13397.
      
      The changes are:
      
      * Make CmmSink swizzle the order of a conditional where necessary;
        see Note [Improving conditionals] in CmmSink
      
      * Hack the general case of StgCmmExpr.cgCase so that it use
        NoGcInAlts for conditionals.  This doesn't seem right, but it's
        the same choice as the tagToEnum version. Without it, code size
        increases a lot (more heap checks).
      
        There's a loose end here.
      
      * Add comments in CmmOpt.cmmMachOpFoldM
      6d14c148
    • Simon Peyton Jones's avatar
      Re-engineer caseRules to add tagToEnum/dataToTag · 193664d4
      Simon Peyton Jones authored and David Feuer's avatar David Feuer committed
      See Note [Scrutinee Constant Folding] in SimplUtils
      
      * Add cases for tagToEnum and dataToTag. This is the main new
        bit.  It allows the simplifier to remove the pervasive uses
        of     case tagToEnum (a > b) of
                  False -> e1
                  True  -> e2
        and replace it by the simpler
               case a > b of
                  DEFAULT -> e1
                  1#      -> e2
        See Note [caseRules for tagToEnum]
        and Note [caseRules for dataToTag] in PrelRules.
      
      * This required some changes to the API of caseRules, and hence
        to code in SimplUtils.  See Note [Scrutinee Constant Folding]
        in SimplUtils.
      
      * Avoid duplication of work in the (unusual) case of
           case BIG + 3# of b
             DEFAULT -> e1
             6#      -> e2
      
        Previously we got
           case BIG of
             DEFAULT -> let b = BIG + 3# in e1
             3#      -> let b = 6#       in e2
      
        Now we get
           case BIG of b#
             DEFAULT -> let b = b' + 3# in e1
             3#      -> let b = 6#      in e2
      
      * Avoid duplicated code in caseRules
      
      A knock-on refactoring:
      
      * Move Note [Word/Int underflow/overflow] to Literal, as
        documentation to accompany mkMachIntWrap etc; and get
        rid of PrelRuls.intResult' in favour of mkMachIntWrap
      193664d4
    • Simon Peyton Jones's avatar
      Move dataConTagZ to DataCon · 1cae73aa
      Simon Peyton Jones authored and David Feuer's avatar David Feuer committed
      Just a simple refactoring to remove duplication
      1cae73aa
    • Ben Gamari's avatar
      nativeGen: Use SSE2 SQRT instruction · 9ac22183
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: austin, dfeuer
      
      Subscribers: dfeuer, rwbarton, thomie
      
      GHC Trac Issues: #13629
      
      Differential Revision: https://phabricator.haskell.org/D3508
      9ac22183
    • Ben Gamari's avatar
      CSE: Fix cut and paste error · 9f9b90f1
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      extendCSRecEnv took the map to be extended from cs_map instead of
      cs_rec_map.  Oops!
      
      Test Plan: Validate
      
      Reviewers: simonpj, austin
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3510
      9f9b90f1
    • Ben Gamari's avatar
      Use memcpy in cloneArray · 228d4670
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      While looking at #13615 I noticed that there was this strange open-coded
      memcpy in the definition of the cloneArray macro. I don't see why this
      should be preferable to memcpy.
      
      Test Plan: Validate, particularly focusing on array operations
      
      Reviewers: simonmar, tibbe, austin, alexbiehl
      
      Reviewed By: tibbe, alexbiehl
      
      Subscribers: alexbiehl, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3504
      228d4670
    • Ryan Scott's avatar
      Make the tyvars in TH-reified data family instances uniform · b2c38d6b
      Ryan Scott authored
      It turns out we were using two different sets of type variables when
      reifying data family instances in Template Haskell. We were using the
      tyvars quantifying over the instance itself for the LHS, but using the
      tyvars quantifying over the data family instance constructor for the
      RHS. This commit uses the instance tyvars for both the LHS and the RHS,
      fixing #13618.
      
      Test Plan: make test TEST=T13618
      
      Reviewers: goldfire, austin, bgamari
      
      Reviewed By: goldfire, bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13618
      
      Differential Revision: https://phabricator.haskell.org/D3505
      b2c38d6b
    • Ryan Scott's avatar
      Add regression test for #12104 · 69b9b853
      Ryan Scott authored
      Commit 2f9f1f86
      (#13487) fixes #12104 as well. This adds a regression test for the
      program reported in #12104 to keep it fixed.
      
      Test Plan: make test TEST=T12104
      
      Reviewers: bgamari, austin
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #12104
      
      Differential Revision: https://phabricator.haskell.org/D3495
      69b9b853
    • Ben Gamari's avatar
      get-win32-tarballs: Grab perl tarball from haskell.org, not GitHub · ba597c1d
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: austin, dfeuer
      
      Reviewed By: dfeuer
      
      Subscribers: Phyx, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3509
      ba597c1d
    • Simon Peyton Jones's avatar
      Be a bit more eager to inline in a strict context · 29d88ee1
      Simon Peyton Jones authored
      If we see f (g x), and f is strict, we want to be a bit more eager to
      inline g, because it may well expose an eval (on x perhaps) that can
      be eliminated or shared.
      
      I saw this in nofib boyer2, function RewriteFuns.onewayunify1.  It
      showed up as a consequence of the preceding patch that makes the
      simplifier do less work (Trac #13379).  We had
      
         f d (g x)
      
      where f was a class-op. Previously we simplified both d and
      (g x) with a RuleArgCtxt (making g a bit more eager to inline).
      But now we simplify only d that way, then fire the rule, and
      only then simplify (g x).  Firing the rule produces a strict
      funciion, so we want to make a strict function encourage
      inlining a bit.
      29d88ee1
    • Simon Peyton Jones's avatar
      Cure exponential behaviour in the simplifier · a1b753e8
      Simon Peyton Jones authored
      This patch nails a Bad Bug exposed in Trac #13379. Roughly,
      a deeply-nested application like
         f (f (f ....) ) )
      could make the simplifier go exponential -- without producing
      an exponential-sized result!
      
      The reason was that we
        - simplified a (big) function argument
        - then decided to inline the function
        - then preInilneUnconditionally the argument
        - and then re-simplified the big argument
      
      And if the "big argument" itself had a similar structure
      things could get very bad.
      
      Once I'd understood, it was easy to fix:
      
      * See Note Note [Avoiding exponential behaviour] for an overview
      
      * The key change is that Simplify.simplLam now as a case for
        (isSimplified dup). This is what removes the perf bug.
      
      * But I also made simplCast more parsimonious about simplifying,
        avoiding doing so when the coercion is Refl
      
      * And similarly I now try to avoid simplifying arguments
        where possible before applying rules.
        See Note [Trying rewrite rules]
      
      The latter two points tackle common cases, and in those cases make the
      simplifier take fewer iterations.
      a1b753e8
    • Simon Peyton Jones's avatar
      Eta expansion and join points · 25754c83
      Simon Peyton Jones authored
      CoreArity.etaExpand tried to deal with eta-expanding expressions
      with join points.  For example
          let j x = e in \y. b
      
      But it is hard to eta-expand this in the "no-crap" way described in
      Note [No crap in eta-expanded code], becuase it would mean pushing
      the "apply to y" into the join RHS, and changing its type. And the
      join might be recursive, and it might have an unfolding.
      
      Moreover in elaborate cases like this I don't think we need the
      no-crap thing.  So for now I'm simplifying the code by generating
         \z. (let j x = e in \y. b) z
      
      Let's see if that gives rise to any problems.
      See Note [Eta expansion for join points]
      25754c83
    • Simon Peyton Jones's avatar
      Comments only · 03ec7927
      Simon Peyton Jones authored
      03ec7927
    • Simon Peyton Jones's avatar
      Comments only · 4d5ab1f8
      Simon Peyton Jones authored
      4d5ab1f8
    • Simon Peyton Jones's avatar
      A bit more tcTrace · 6c2d9175
      Simon Peyton Jones authored
      6c2d9175
    • Simon Peyton Jones's avatar
      Comments and tiny refactoring · 7f6674d6
      Simon Peyton Jones authored
      7f6674d6
  3. Apr 27, 2017
  4. Apr 26, 2017
  5. Apr 25, 2017
    • adam's avatar
      Add instances for Data.Ord.Down · 47be6444
      adam authored and Ben Gamari's avatar Ben Gamari committed
      Namely `Num`, `Functor`, `Applicative`, `Monad`, `Semigroup` and
      `Monoid` for `Data.Ord.Down` (#13097).
      
      Reviewers: austin, hvr, bgamari, RyanGlScott
      
      Reviewed By: bgamari, RyanGlScott
      
      Subscribers: RyanGlScott, rwbarton, thomie
      
      GHC Trac Issues: #13097
      
      Differential Revision: https://phabricator.haskell.org/D3500
      47be6444
    • Ben Gamari's avatar
      Document mkWeak# · 24460269
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: simonmar, austin
      
      Reviewed By: simonmar
      
      Subscribers: RyanGlScott, rwbarton, thomie
      
      GHC Trac Issues: #10640, #13611
      
      Differential Revision: https://phabricator.haskell.org/D3498
      24460269
    • Ryan Scott's avatar
      Only pretty-print binders in closed type families with -fprint-explicit-foralls · da792e47
      Ryan Scott authored
      Previously, we were unconditionally pretty-printing all type variable
      binders when pretty-printing closed type families (e.g., in the output
      of `:info` in GHCi). This threw me for a loop, so let's guard this behind
      the `-fprint-explicit-foralls` flag.
      
      Test Plan: make test TEST=T13420
      
      Reviewers: goldfire, austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13420
      
      Differential Revision: https://phabricator.haskell.org/D3497
      da792e47
    • Tamar Christina's avatar
      Add backup url and sync support for Win32 tarball script · 71c3cea6
      Tamar Christina authored and Ben Gamari's avatar Ben Gamari committed
      This imports @bgamari's sync script into the mirror script
      and adds a backup url for packages.
      
      The idea is that the URLs won't need updating when updating
      the tarballs from now on.
      
      It will first try haskell.org,
      failing that it'll try repo.msys2.org
      
      Test Plan: try new command `mk/get-win32-tarballs.sh sync`
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, bgamari
      
      Differential Revision: https://phabricator.haskell.org/D3488
      71c3cea6
    • Peter Trommler's avatar
      PPC NCG: Implement callish prim ops · 89a3241f
      Peter Trommler authored and Ben Gamari's avatar Ben Gamari committed
      Provide PowerPC optimised implementations of callish prim ops.
      
      MO_?_QuotRem
      The generic implementation of quotient remainder prim ops uses
      a division and a remainder operation. There is no remainder on
      PowerPC and so we need to implement remainder "by hand" which
      results in a duplication of the divide operation when using the
      generic code.
      
      Avoid this duplication by implementing the prim op in the native
      code generator.
      
      MO_U_Mul2
      Use PowerPC's instructions for long multiplication.
      
      Addition and subtraction
      Use PowerPC add/subtract with carry/overflow instructions
      
      MO_Clz and MO_Ctz
      Use PowerPC's CNTLZ instruction and implement count trailing
      zeros using count leading zeros
      
      MO_QuotRem2
      Implement an algorithm given by Henry Warren in "Hacker's Delight"
      using PowerPC divide instruction. TODO: Use long division instructions
      when available (POWER7 and later).
      
      Test Plan: validate on AIX and 32-bit Linux
      
      Reviewers: simonmar, erikd, hvr, austin, bgamari
      
      Reviewed By: erikd, hvr, bgamari
      
      Subscribers: trofi, kgardas, thomie
      
      Differential Revision: https://phabricator.haskell.org/D2973
      89a3241f
    • Ben Gamari's avatar
      configure: Kill off FP_ARG_WITH_* · 9373994a
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This replaces the --with-* configure flags with the usual autoconf
      environment variables, as suggested by #13583.
      
      Test Plan: Configure on various platforms
      
      Reviewers: hvr, trofi, thomie, austin
      
      Reviewed By: trofi
      
      Subscribers: rwbarton, erikd
      
      GHC Trac Issues: #13583
      
      Differential Revision: https://phabricator.haskell.org/D3499
      9373994a
    • Ben Gamari's avatar
      Revert "Remove special casing of Windows in generic files" · 66108864
      Ben Gamari authored
      This commit didn't consider the fact that binary distributions on Windows must
      have relative toolchain paths. This caused #13560.
      
      This reverts commit 48385cb2 (except for a
      helpful comment).
      66108864
    • Chris Martin's avatar
      Don't describe tuple sections as "Python-style" · 688272ba
      Chris Martin authored and Ben Gamari's avatar Ben Gamari committed
      (cherry picked from commit 960589e89da3dbf60e88042d7e064ad4a98fb2ff)
      688272ba
    • Simon Marlow's avatar
      Don't setProgramDynFlags on every :load · 914842e5
      Simon Marlow authored
      Summary:
      setProgramDynFlags invalidates the whole module graph, forcing
      everything to be re-summarised (including preprocessing) on every
      :reload.
      
      Looks like this was a bad regression in 8.0, but we didn't notice
      because there was no test for it.  Now there is!
      
      Test Plan:
      * validate
      * new unit test
      
      Reviewers: bgamari, triple, austin, niteria, erikd, jme
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3398
      914842e5
  6. Apr 24, 2017
  7. Apr 23, 2017
Loading