Skip to content
Snippets Groups Projects
  1. Mar 25, 2018
    • Ryan Scott's avatar
      Fix #14916 with an additional validity check in deriveTyData · 20f14b4f
      Ryan Scott authored
      Manually-written instances and standalone-derived instances
      have the benefit of having the `checkValidInstHead` function run over
      them, which catches manual instances of built-in types like `(~)` and
      `Coercible`. However, instances generated from `deriving` clauses
      weren't being passed through `checkValidInstHead`, leading to
      confusing results as in #14916.
      
      `checkValidInstHead` also has additional validity checks for language
      extensions like `FlexibleInstances` and `MultiParamTypeClasses`. Up
      until now, GHC has never required these language extensions for
      `deriving` clause, so to avoid unnecessary breakage, I opted to
      suppress these language extension checks for `deriving` clauses, just
      like we currently suppress them for `SPECIALIZE instance` pragmas.
      
      Test Plan: make test TEST=T14916
      
      Reviewers: goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14916
      
      Differential Revision: https://phabricator.haskell.org/D4501
      20f14b4f
    • Ben Gamari's avatar
      testsuite: Add test for #14925 · 0703c00f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Validate
      
      Reviewers: alpmestan
      
      Reviewed By: alpmestan
      
      Subscribers: alpmestan, leftaroundabout, rwbarton, thomie, carter
      
      GHC Trac Issues: #14925
      
      Differential Revision: https://phabricator.haskell.org/D4512
      0703c00f
    • Ryan Scott's avatar
      rts/RetainerProfile: Dump closure type if push() fails · 9a00bfba
      Ryan Scott authored
      While investigating #14947, I noticed that the `barf`ed
      error message in `push()` doesn't print out the closure type that
      causes it to crash. Let's do so.
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: alexbiehl, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4525
      9a00bfba
    • voanhduy1512's avatar
      document: fix trac issue #14229 · c16df606
      voanhduy1512 authored and Ben Gamari's avatar Ben Gamari committed
      Accroding to
      https://git.haskell.org/ghc.git/commitdiff/49672659113371c3bee691e6d913d
      f8e6f60a1d8,
      `-Wredundant-constraints` is no longer turn on by default.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4528
      c16df606
    • Adam Gundry's avatar
      Fix panic on module re-exports of DuplicateRcordFields · fb462f94
      Adam Gundry authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: new test overloadedrecflds/should_fail/T14953
      
      Reviewers: mpickering, simonpj, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14953
      
      Differential Revision: https://phabricator.haskell.org/D4527
      fb462f94
    • Simon Marlow's avatar
      Run C finalizers incrementally during mutation · f7bbc343
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      With a large heap it's possible to build up a lot of finalizers
      between GCs.  We've observed GC spending up to 50% of its time running
      finalizers.  But there's no reason we have to run finalizers during
      GC, and especially no reason we have to block *all* the mutator
      threads while *one* GC thread runs finalizers one by one.
      
      I thought about a bunch of alternative ways to handle this, which are
      documented along with runSomeFinalizers() in Weak.c.  The approach I
      settled on is to have a capability run finalizers if it is idle.  So
      running finalizers is like a low-priority background thread. This
      requires some minor scheduler changes, but not much.  In the future we
      might be able to move more GC work into here (I have my eye on freeing
      large blocks, for example).
      
      Test Plan:
      * validate
      * tested on our system and saw reductions in GC pauses of 40-50%.
      
      Reviewers: bgamari, niteria, osa1, erikd
      
      Reviewed By: bgamari, osa1
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4521
      f7bbc343
    • Simon Marlow's avatar
      Add Note [BLACKHOLE points to IND] · cf809950
      Simon Marlow authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: ci
      
      Reviewers: osa1, bgamari, erikd
      
      Reviewed By: osa1
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4517
      cf809950
    • Ryan Scott's avatar
      Fix two pernicious bugs in DeriveAnyClass · 98930426
      Ryan Scott authored
      The way GHC was handling `DeriveAnyClass` was subtly wrong
      in two notable ways:
      
      * In `inferConstraintsDAC`, we were //always// bumping the `TcLevel`
        of newly created unification variables, under the assumption that
        we would always place those unification variables inside an
        implication constraint. But #14932 showed precisely the scenario
        where we had `DeriveAnyClass` //without// any of the generated
        constraints being used inside an implication, which made GHC
        incorrectly believe the unification variables were untouchable.
      * Even worse, we were using the generated unification variables from
        `inferConstraintsDAC` in every single iteration of `simplifyDeriv`.
        In #14933, however, we have a scenario where we fill in a
        unification variable with a skolem in one iteration, discard it,
        proceed on to another iteration, use the same unification variable
        (still filled in with the old skolem), and try to unify it with
        a //new// skolem! This results in an utter disaster.
      
      The root of both these problems is `inferConstraintsDAC`. This patch
      fixes the issue by no longer generating unification variables
      directly in `inferConstraintsDAC`. Instead, we store the original
      variables from a generic default type signature in `to_metas`, a new
      field of `ThetaOrigin`, and in each iteration of `simplifyDeriv`, we
      generate fresh meta tyvars (avoiding the second issue). Moreover,
      this allows us to more carefully fine-tune the `TcLevel` under which
      we create these meta tyvars, fixing the first issue.
      
      Test Plan: make test TEST="T14932 T14933"
      
      Reviewers: simonpj, bgamari
      
      Reviewed By: simonpj
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14932, #14933
      
      Differential Revision: https://phabricator.haskell.org/D4507
      98930426
    • John Ericson's avatar
      Support iOS variants elsewhere when configuring · 10566a81
      John Ericson authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: hvr, bgamari, angerman
      
      Reviewed By: angerman
      
      Subscribers: rwbarton, thomie, erikd, carter, angerman
      
      Differential Revision: https://phabricator.haskell.org/D4513
      10566a81
    • Ben Gamari's avatar
      testsuite: Add test for #14931 · 7bb1fde1
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: alpmestan
      
      Reviewed By: alpmestan
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14931
      
      Differential Revision: https://phabricator.haskell.org/D4518
      7bb1fde1
    • Alec Theriault's avatar
      Support adding objects from TH · ceb91477
      Alec Theriault authored and Ben Gamari's avatar Ben Gamari committed
      The user facing TH interface changes are:
      
        * 'addForeignFile' is renamed to 'addForeignSource'
        * 'qAddForeignFile'/'addForeignFile' now expect 'FilePath's
        * 'RawObject' is now a constructor for 'ForeignSrcLang'
        * 'qAddTempFile'/'addTempFile' let you request a temporary file
          from the compiler.
      
      Test Plan: unsure about this, added a TH test
      
      Reviewers: goldfire, bgamari, angerman
      
      Reviewed By: bgamari, angerman
      
      Subscribers: hsyl20, mboes, carter, simonmar, bitonic, ljli, rwbarton, thomie
      
      GHC Trac Issues: #14298
      
      Differential Revision: https://phabricator.haskell.org/D4217
      ceb91477
  2. Mar 23, 2018
    • Ryan Scott's avatar
      Allow PartialTypeSignatures in standalone deriving contexts · affdea82
      Ryan Scott authored
      Summary:
      At its core, this patch is a simple tweak that allows a user
      to write:
      
      ```lang=haskell
      deriving instance _ => Eq (Foo a)
      ```
      
      Which is functionally equivalent to:
      
      ```lang=haskell
      data Foo a = ...
        deriving Eq
      ```
      
      But with the added flexibility that `StandaloneDeriving` gives you
      (namely, the ability to use it anywhere, not just in the same module
      that `Foo` was declared in). This fixes #13324, and should hopefully
      address a use case brought up in #10607.
      
      Currently, only the use of a single, extra-constraints wildcard is
      permitted in a standalone deriving declaration. Any other wildcard
      is rejected, so things like
      `deriving instance (Eq a, _) => Eq (Foo a)` are currently forbidden.
      
      There are quite a few knock-on changes brought on by this change:
      
      * The `HsSyn` type used to represent standalone-derived instances
        was previously `LHsSigType`, which isn't sufficient to hold
        wildcard types. This needed to be changed to `LHsSigWcType` as a
        result.
      
      * Previously, `DerivContext` was a simple type synonym for
        `Maybe ThetaType`, under the assumption that you'd only ever be in
        the `Nothing` case if you were in a `deriving` clause. After this
        patch, that assumption no longer holds true, as you can also be
        in this situation with standalone deriving when an
        extra-constraints wildcard is used.
      
        As a result, I changed `DerivContext` to be a proper datatype that
        reflects the new wrinkle that this patch adds, and plumbed this
        through the relevant parts of `TcDeriv` and friends.
      
      * Relatedly, the error-reporting machinery in `TcErrors` also assumed
        that if you have any unsolved constraints in a derived instance,
        then you should be able to fix it by switching over to standalone
        deriving. This was always sound advice before, but with this new
        feature, it's possible to have unsolved constraints even when
        you're standalone-deriving something!
      
        To rectify this, I tweaked some constructors of `CtOrigin` a bit
        to reflect this new subtlety.
      
      This requires updating the Haddock submodule. See my fork at
      https://github.com/RyanGlScott/haddock/commit/067d52fd4be15a1842cbb05f42d9d482de0ad3a7
      
      Test Plan: ./validate
      
      Reviewers: simonpj, goldfire, bgamari
      
      Reviewed By: simonpj
      
      Subscribers: goldfire, rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #13324
      
      Differential Revision: https://phabricator.haskell.org/D4383
      affdea82
    • Ryan Scott's avatar
      Special-case record fields ending with hash when deriving Read · d5577f44
      Ryan Scott authored
      Summary:
      In commit dbd81f7e, a
      regression was inadvertently introduced which caused derived `Read`
      instances for record data types with fields ending in a `#` symbol
      (using `MagicHash`) would no longer parse on valid output. This
      is ultimately due to the same reasons as #5041, as we cannot parse
      a field name like `foo#` as a single identifier. We fix this issue
      by employing the same workaround as in #5041: first parse the
      identifier name `foo`, then then symbol `#`.
      
      This is accomplished by the new `readFieldHash` function in
      `GHC.Read`. This will likely warrant a `base-4.11.1.0` release.
      
      Test Plan: make test TEST=T14918
      
      Reviewers: tdammers, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14918
      
      Differential Revision: https://phabricator.haskell.org/D4502
      d5577f44
  3. Mar 22, 2018
    • Simon Peyton Jones's avatar
      Improve shortOutIndirections slightly · 034c32f6
      Simon Peyton Jones authored
      I found (when investigating Trac #14955) a binding looking like
      
         Rec { exported_id = ....big...lcl_id...
             ; lcl_id = exported_id }
      
      but bizarrely 'lcl_id' was chosen as the loop breaker, and never
      inlined.  It turned out to be an unintended consequence of the
      shortOutIndirections code in SimplCore.  Easily fixed.
      034c32f6
    • Simon Peyton Jones's avatar
      Fix over-eager constant folding in bitInteger · efc844f5
      Simon Peyton Jones authored
      The RULE for bitInteger was trying to constant-fold
      
          bitInteger 9223372036854775807#
      
      which meant constructing a gigantic Integer at compile
      time.  Very bad idea!  Easily fixed.
      
      Fixes Trac #14959, #14962.
      efc844f5
  4. Mar 21, 2018
    • Simon Peyton Jones's avatar
      Fix two obscure bugs in rule matching · 3446cee0
      Simon Peyton Jones authored
      This patch fixes Trac #14777, a compiler crash.
      
      There were actually two bugs.
      
      1. In Rules.matchN, I was (consciously) not rename the template binders
         of the rule. Sadly, in rare cases an accidental coincidence of
         uniques could mean that a term variable was mapped to a type
         variable, utterly bogusly.  See "Historical note" in
         Note [Cloning the template binders] in Rules.
      
         This was hard to find, but easy to fix.
      
      2. The fix to (1) showed up a bug in Unify.hs.  The test in
         Unify.tvBindFlag was previously using the domain of the RnEnv2
         to detect locally-bound variables (e.g. when unifying under
         a forall).  That's fine when teh RnEnv2 starts empty, as it
         does in most entry points.  But the tcMatchTyKisX entry point,
         used from the rule matcher, passes in a non-empty RnEnv2 (by
         design).  Now the domain of the RnEnv doesn't idenfity those
         locally-bound variables any more :-(.
      
         Solution: extend UmEnv with a new field um_skols, to capture
         the skolems directly.  Simple, easy, works.
      3446cee0
    • Simon Peyton Jones's avatar
      Allow as-patterns in unidirectional patttern synonyms · 411a97e2
      Simon Peyton Jones authored
      This patch implements GHC Proposal #94, described here
         https://github.com/ghc-proposals/ghc-proposals/pull/94
      
      The effect is simply to lift a totally-undocumented restriction to
      unidirecional pattern synonyms, namely that they can't have as-patterns
      or n+k patterns.
      
      The fix is easy: just remove the checks.
      
      I also took the opportunity to improve the manual entry for
      the semantics of pattern matching for pattern synonyms.
      411a97e2
    • Ryan Scott's avatar
      Fix #14869 by being more mindful of Type vs. Constraint · 49ac3f0f
      Ryan Scott authored
      Summary:
      Before, we were using `isLiftedTypeKind` in `reifyType`
      before checking if a type was `Constraint`. But as it turns out,
      `isLiftedTypeKind` treats `Constraint` the same as `Type`, so every
      occurrence of `Constraint` would be reified as `Type`! To make things
      worse, the documentation for `isLiftedTypeKind` stated that it
      treats `Constraint` //differently// from `Type`, which simply isn't
      true.
      
      This revises the documentation for `isLiftedTypeKind` to reflect
      reality, and defers the `isLiftedTypeKind` check in `reifyType` so
      that it does not accidentally swallow `Constraint`.
      
      Test Plan: make test TEST=T14869
      
      Reviewers: goldfire, bgamari
      
      Reviewed By: goldfire
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14869
      
      Differential Revision: https://phabricator.haskell.org/D4474
      49ac3f0f
  5. Mar 20, 2018
  6. Mar 19, 2018
    • Ben Gamari's avatar
      configure: Accept version suffix in solaris name · 60aa53d9
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Summary: OpenIndiana apparently reports a triple of i386-pc-solaris2.11.
      
      Reviewers: hvr
      
      Subscribers: rwbarton, thomie, erikd, carter
      
      Differential Revision: https://phabricator.haskell.org/D4487
      60aa53d9
    • Ben Gamari's avatar
      relnotes: Fix parsing of Version: field from Cabal file · d718023e
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4491
      d718023e
    • Ben Gamari's avatar
      Bump autoconf version bound to >= 2.69 · 6a71ef79
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: hvr
      
      Subscribers: rwbarton, thomie, erikd, carter
      
      GHC Trac Issues: #14910
      
      Differential Revision: https://phabricator.haskell.org/D4495
      6a71ef79
    • Matthew Pickering's avatar
      Add -flate-specialise which runs a later specialisation pass · afad5561
      Matthew Pickering authored and Ben Gamari's avatar Ben Gamari committed
      Runs another specialisation pass towards the end of the optimisation
      pipeline. This can catch specialisation opportunities which arose from
      the previous specialisation pass or other inlining.
      
      You might want to use this if you are you have a type class method
      which returns a constrained type. For example, a type class where one
      of the methods implements a traversal.
      
      It is not enabled by default or any optimisation level. Only by
      manually enabling the flag `-flate-specialise`.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4457
      afad5561
    • Douglas Wilson's avatar
      rts, base: Refactor stats.c to improve --machine-readable report · 2d4bda2e
      Douglas Wilson authored and Ben Gamari's avatar Ben Gamari committed
      There should be no change in the output of the '+RTS -s' (summary)
      report, or the 'RTS -t' (one-line) report.
      
      All data shown in the summary report is now shown in the machine
      readable report.
      
      All data in RTSStats is now shown in the machine readable report.
      
      init times are added to RTSStats and added to GHC.Stats.
      
      Example of the new output:
      ```
       [("bytes allocated", "375016384")
       ,("num_GCs", "113")
       ,("average_bytes_used", "148348")
       ,("max_bytes_used", "206552")
       ,("num_byte_usage_samples", "2")
       ,("peak_megabytes_allocated", "6")
       ,("init_cpu_seconds", "0.001642")
       ,("init_wall_seconds", "0.001027")
       ,("mut_cpu_seconds", "3.020166")
       ,("mut_wall_seconds", "0.757244")
       ,("GC_cpu_seconds", "0.037750")
       ,("GC_wall_seconds", "0.009569")
       ,("exit_cpu_seconds", "0.000890")
       ,("exit_wall_seconds", "0.002551")
       ,("total_cpu_seconds", "3.060452")
       ,("total_wall_seconds", "0.770395")
       ,("major_gcs", "2")
       ,("allocated_bytes", "375016384")
       ,("max_live_bytes", "206552")
       ,("max_large_objects_bytes", "159344")
       ,("max_compact_bytes", "0")
       ,("max_slop_bytes", "59688")
       ,("max_mem_in_use_bytes", "6291456")
       ,("cumulative_live_bytes", "296696")
       ,("copied_bytes", "541024")
       ,("par_copied_bytes", "493976")
       ,("cumulative_par_max_copied_bytes", "104104")
       ,("cumulative_par_balanced_copied_bytes", "274456")
       ,("fragmentation_bytes", "2112")
       ,("alloc_rate", "124170795")
       ,("productivity_cpu_percent", "0.986838")
       ,("productivity_wall_percent", "0.982935")
       ,("bound_task_count", "1")
       ,("sparks_count", "5836258")
       ,("sparks_converted", "237")
       ,("sparks_overflowed", "1990408")
       ,("sparks_dud ", "0")
       ,("sparks_gcd", "3455553")
       ,("sparks_fizzled", "390060")
       ,("work_balance", "0.555606")
       ,("n_capabilities", "4")
       ,("task_count", "10")
       ,("peak_worker_count", "9")
       ,("worker_count", "9")
       ,("gc_alloc_block_sync_spin", "162")
       ,("gc_alloc_block_sync_yield", "0")
       ,("gc_alloc_block_sync_spin", "162")
       ,("gc_spin_spin", "18840855")
       ,("gc_spin_yield", "10355")
       ,("mut_spin_spin", "70331392")
       ,("mut_spin_yield", "61700")
       ,("waitForGcThreads_spin", "241")
       ,("waitForGcThreads_yield", "2797")
       ,("whitehole_gc_spin", "0")
       ,("whitehole_lockClosure_spin", "0")
       ,("whitehole_lockClosure_yield", "0")
       ,("whitehole_executeMessage_spin", "0")
       ,("whitehole_threadPaused_spin", "0")
       ,("any_work", "1667")
       ,("no_work", "1662")
       ,("scav_find_work", "1026")
       ,("gen_0_collections", "111")
       ,("gen_0_par_collections", "111")
       ,("gen_0_cpu_seconds", "0.036126")
       ,("gen_0_wall_seconds", "0.036126")
       ,("gen_0_max_pause_seconds", "0.036126")
       ,("gen_0_avg_pause_seconds", "0.000081")
       ,("gen_0_sync_spin", "21")
       ,("gen_0_sync_yield", "0")
       ,("gen_1_collections", "2")
       ,("gen_1_par_collections", "1")
       ,("gen_1_cpu_seconds", "0.001624")
       ,("gen_1_wall_seconds", "0.001624")
       ,("gen_1_max_pause_seconds", "0.001624")
       ,("gen_1_avg_pause_seconds", "0.000272")
       ,("gen_1_sync_spin", "3")
       ,("gen_1_sync_yield", "0")
       ]
      ```
      
      Test Plan: Ensure that one-line and summary reports are unchanged.
      
      Reviewers: bgamari, erikd, simonmar, hvr
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14660
      
      Differential Revision: https://phabricator.haskell.org/D4303
      2d4bda2e
    • John Ericson's avatar
      gen-data-layout.sh: Use bash array for readability · b3b394b4
      John Ericson authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: angerman, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4511
      b3b394b4
    • Gabor Greif's avatar
      Fix typo · 82e8d1fb
      Gabor Greif authored
      82e8d1fb
    • Frank Steffahn's avatar
      Fix typo in user guide about ConstraintKinds · 960cd424
      Frank Steffahn authored and Ben Gamari's avatar Ben Gamari committed
      The backslash currently in this type signature makes no sense. Without it, the example is fine.
      960cd424
    • Ben Gamari's avatar
      Bump array submodule · 98c1f222
      Ben Gamari authored
      98c1f222
    • Andreas Klebinger's avatar
      Update tests for #12870 to pass with a slow run of the testsuite. · fdec06a2
      Andreas Klebinger authored
      Test Plan: make slow
      
      Reviewers: bgamari, erikd, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #12870
      
      Differential Revision: https://phabricator.haskell.org/D4486
      fdec06a2
    • Ryan Scott's avatar
      Don't permit data types with return kind Constraint · f748c529
      Ryan Scott authored
      Previously, GHC allowed all of the following:
      
      ```lang=haskell
      data Foo1 :: Constraint
      data family Foo2 :: Constraint
      data family Foo3 :: k
      data instance Foo3 :: Constraint
      ```
      
      Yikes! This is because GHC was confusing `Type` with `Constraint`
      due to careless use of the `isLiftedTypeKind` function. To respect
      this distinction, I swapped `isLiftedTypeKind` out for
      `tcIsStarKind`—which does respect this distinction—in the right
      places.
      
      Test Plan: make test TEST="T14048a T14048b T14048c"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: goldfire, rwbarton, thomie, carter
      
      GHC Trac Issues: #14048
      
      Differential Revision: https://phabricator.haskell.org/D4479
      f748c529
    • Ryan Scott's avatar
      Fix #14934 by including axSub0R in typeNatCoAxiomRules · c3aea396
      Ryan Scott authored
      For some reason, `axSub0R` was left out of `typeNatCoAxiomRules` in
      `TcTypeNats`, which led to disaster when trying to look up `Sub0R` from
      an interface file, as demonstrated in #14934.
      
      The fix is simple—just add `axSub0R` to that list. To help prevent
      an issue like this happening in the future, I added a
      `Note [Adding built-in type families]` to `TcTypeNats`, which
      contains a walkthrough of all the definitions in `TcTypeNats` you
      need to update when adding a new built-in type family.
      
      Test Plan: make test TEST=T14934
      
      Reviewers: bgamari, simonpj
      
      Reviewed By: simonpj
      
      Subscribers: simonpj, rwbarton, thomie, carter
      
      GHC Trac Issues: #14934
      
      Differential Revision: https://phabricator.haskell.org/D4508
      c3aea396
    • Joachim Breitner's avatar
      Require GHC 8.2 to bootstrap GHC · e3588547
      Joachim Breitner authored and Ben Gamari's avatar Ben Gamari committed
      Reviewers: bgamari, hvr, RyanGlScott
      
      Reviewed By: RyanGlScott
      
      Subscribers: RyanGlScott, rwbarton, thomie, erikd, carter
      
      Differential Revision: https://phabricator.haskell.org/D4509
      e3588547
    • Chaitanya Koparkar's avatar
      Turn a TH Name for built-in syntax into an unqualified RdrName · 9868f91f
      Chaitanya Koparkar authored and Ben Gamari's avatar Ben Gamari committed
      Previously, the Renamer would turn any fully qualified Template Haskell
      name into a corresponding fully qualified `RdrName`. But this is not
      what we want for built-in syntax, as it produces unnecessarily qualified
      names (eg. GHC.Types.[], GHC.Tuple.(,) etc.).
      
      Test Plan: ./validate
      
      Reviewers: RyanGlScott, bgamari, goldfire
      
      Reviewed By: RyanGlScott, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13776
      
      Differential Revision: https://phabricator.haskell.org/D4506
      9868f91f
    • David Feuer's avatar
      Implement equalKeysUFM the right way · fbd9b886
      David Feuer authored
      Originally, we compared the key lists, which was kind of silly.
      Then I changed it to something fancier ... and also silly.
      This is much more reasonable, should be faster, and is nice and
      clear.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4500
      fbd9b886
    • Michal Terepeta's avatar
      CmmUtils: get rid of insertBlock · 256577fb
      Michal Terepeta authored and Ben Gamari's avatar Ben Gamari committed
      
      `Hoopl.Graph` has almost exactly the same function, so let's use that.
      Also, use `IntMap.alter` to make it more efficient.
      
      Also switch `Hoopl` to use strict maps.
      
      Signed-off-by: default avatarMichal Terepeta <michal.terepeta@gmail.com>
      
      Test Plan: ./validate
      
      Reviewers: bgamari, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: dfeuer, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4493
      256577fb
    • Ben Gamari's avatar
      Improve accuracy of get/setAllocationCounter · 20cbb016
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Summary:
      get/setAllocationCounter didn't take into account allocations in the
      current block. This was known at the time, but it turns out to be
      important to have more accuracy when using these in a fine-grained
      way.
      
      Test Plan:
      New unit test to test incrementally larger allocaitons.  Before I got
      results like this:
      
      ```
      +0
      +0
      +0
      +0
      +0
      +4096
      +0
      +0
      +0
      +0
      +0
      +4064
      +0
      +0
      +4088
      +4056
      +0
      +0
      +0
      +4088
      +4096
      +4056
      +4096
      ```
      
      Notice how the results aren't always monotonically increasing.  After
      this patch:
      
      ```
      +344
      +416
      +488
      +560
      +632
      +704
      +776
      +848
      +920
      +992
      +1064
      +1136
      +1208
      +1280
      +1352
      +1424
      +1496
      +1568
      +1640
      +1712
      +1784
      +1856
      +1928
      +2000
      +2072
      +2144
      ```
      
      Reviewers: hvr, erikd, simonmar, jrtc27, trommler
      
      Reviewed By: simonmar
      
      Subscribers: trommler, jrtc27, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4363
      20cbb016
    • Ben Gamari's avatar
      [RFC] nativeGen: Add support for MO_SS_Conv_W32_W64 on i386 · d27336ed
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This is required by D4288. However, this only handles i386; we will
      likely also need to do the same for PPC and SPARC, lest they break when
      D4288 is re-merged.
      
      Test Plan: Validate
      
      Reviewers: simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4362
      d27336ed
    • Peter Trommler's avatar
      SPARC nativeGen: Support for MO_SS_Conv_W32_W64 · 5241f298
      Peter Trommler authored and Ben Gamari's avatar Ben Gamari committed
      Support for signed conversion from 32 bit to 64 bit
      integers is required by D4363.
      
      Test Plan: validate (perhaps also on SPARC)
      
      Reviewers: simonmar, bgamari, kgardas, jrtc27
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4489
      5241f298
Loading