Skip to content
Snippets Groups Projects
  1. Mar 05, 2021
  2. Mar 03, 2021
    • Matthew Pickering's avatar
      IPE: Give all constructor and function tables locations · f943edb0
      Matthew Pickering authored
      During testing it was observed that quite a few info tables were not
      being given locations (due to not being assigned source locations,
      because they were not enclosed by a source note). We can at least give
      the module name and type for such closures even if no more accurate
      source information.
      
      Especially for constructors this helps find them in the STG dumps.
      f943edb0
    • Matthew Pickering's avatar
    • Matthew Pickering's avatar
      f121ffe4
    • Matthew Pickering's avatar
    • Matthew Pickering's avatar
      Add test for whereFrom# · db80a5cc
      Matthew Pickering authored
      db80a5cc
    • Matthew Pickering's avatar
      Add whereFrom and whereFrom# primop · 9087899e
      Matthew Pickering authored
      The `whereFrom` function provides a Haskell interface for using the
      information created by `-finfo-table-map`. Given a Haskell value, the
      info table address will be passed to the `lookupIPE` function in order
      to attempt to find the source location information for that particular closure.
      
      At the moment it's not possible to distinguish the absense of the map
      and a failed lookup.
      9087899e
    • Matthew Pickering's avatar
      Add option to give each usage of a data constructor its own info table · a7aac008
      Matthew Pickering authored
      The `-fdistinct-constructor-tables` flag will generate a fresh info
      table for the usage of any data constructor. This is useful for
      debugging as now by inspecting the info table, you can determine which
      usage of a constructor caused that allocation rather than the old
      situation where the info table always mapped to the definition site of
      the data constructor which is useless.
      
      In conjunction with `-hi` and `-finfo-table-map` this gives a more fine
      grained understanding of where constructor allocations arise from in a
      program.
      a7aac008
    • Matthew Pickering's avatar
      Add -finfo-table-map which maps info tables to source positions · 4b297979
      Matthew Pickering authored
      This new flag embeds a lookup table from the address of an info table
      to information about that info table.
      
      The main interface for consulting the map is the `lookupIPE` C function
      
      > InfoProvEnt * lookupIPE(StgInfoTable *info)
      
      The `InfoProvEnt` has the following structure:
      
      > typedef struct InfoProv_{
      >     char * table_name;
      >     char * closure_desc;
      >     char * ty_desc;
      >     char * label;
      >     char * module;
      >     char * srcloc;
      > } InfoProv;
      >
      > typedef struct InfoProvEnt_ {
      >     StgInfoTable * info;
      >     InfoProv prov;
      >     struct InfoProvEnt_ *link;
      > } InfoProvEnt;
      
      The source positions are approximated in a similar way to the source
      positions for DWARF debugging information. They are only approximate but
      in our experience provide a good enough hint about where the problem
      might be. It is therefore recommended to use this flag in conjunction
      with `-g<n>` for more accurate locations.
      
      The lookup table is also emitted into the eventlog when it is available
      as it is intended to be used with the `-hi` profiling mode.
      
      Using this flag will significantly increase the size of the resulting
      object file but only by a factor of 2-3x in our experience.
      4b297979
    • Matthew Pickering's avatar
      Profiling by info table mode (-hi) · 8402ea95
      Matthew Pickering authored
      This profiling mode creates bands by the address of the info table for
      each closure. This provides a much more fine-grained profiling output
      than any of the other profiling modes.
      
      The `-hi` profiling mode does not require a profiling build.
      8402ea95
    • Matthew Pickering's avatar
      Revert "Remove GHC.Types.Unique.Map module" · 2f7e879b
      Matthew Pickering authored
      This reverts commit 1c7c6f1a.
      2f7e879b
    • Ryan Scott's avatar
      User's Guide: document DefaultSignatures' interaction with subsumption · df74e95a
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      As reported in #19432, the rules governing how `DefaultSignatures` are
      typechecked became stricter in GHC 9.0 due to simplified subsumption.
      However, this was far from obvious to me after reading the User's Guide section
      on `DefaultSignatures`. In this patch, I spruce up the documentation in that
      section so that it mentions these nuances.
      
      Resolves #19432.
      df74e95a
    • Andreas Klebinger's avatar
      Build event logging rts in all flavours except GhcinGhci. · ad0c2073
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      This applies the fix for #19033 to all the other flavours as well.
      ad0c2073
    • Sylvain Henry's avatar
      Add a flag to dump the FastString table · 3f9af891
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      3f9af891
    • Sebastian Graf's avatar
      DmdAnal: Better syntax for demand signatures (#19016) · 3630b9ba
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      The update of the Outputable instance resulted in a slew of
      documentation changes within Notes that used the old syntax.
      The most important doc changes are to `Note [Demand notation]`
      and the user's guide.
      
      Fixes #19016.
      3630b9ba
    • Ben Gamari's avatar
      ghc-heap: Fix profiled build · 5c4dcc3e
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously a255b4e3 failed to update the
      non-profiling codepath.
      5c4dcc3e
    • Ben Gamari's avatar
      hadrian: Fix profiled flavour transformer · e81f2e4e
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously the profiled flavour transformer failed to add the profiled
      ways to the library and RTS ways lists, resulting in link failures.
      e81f2e4e
    • Sylvain Henry's avatar
      Fix leaks of the HscEnv with quick flavour (#19356) · 8a433a3c
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Thanks @mpickering for finding them!
      8a433a3c
    • Sylvain Henry's avatar
      Minor simplification for leak indicators · 38748d5f
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      Avoid returning a lazy panic value when leak indicators are disabled.
      38748d5f
    • Sylvain Henry's avatar
      Always INLINE ($!) · fe4202ce
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      ($) is INLINE so there is no reason ($!) shouldn't.
      fe4202ce
    • Matthew Pickering's avatar
      Profiling: Allow heap profiling to be controlled dynamically. · d89deeba
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This patch exposes three new functions in `GHC.Profiling` which allow
      heap profiling to be enabled and disabled dynamically.
      
      1. startHeapProfTimer - Starts heap profiling with the given RTS options
      2. stopHeapProfTimer  - Stops heap profiling
      3. requestHeapCensus  - Perform a heap census on the next context
                              switch, regardless of whether the timer is enabled or not.
      d89deeba
    • Sylvain Henry's avatar
      Fix array and cleanup conversion primops (#19026) · d8dc0f96
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      The first change makes the array ones use the proper fixed-size types,
      which also means that just like before, they can be used without
      explicit conversions with the boxed sized types. (Before, it was Int# /
      Word# on both sides, now it is fixed sized on both sides).
      
      For the second change, don't use "extend" or "narrow" in some of the
      user-facing primops names for conversions.
      
        - Names like `narrowInt32#` are misleading when `Int` is 32-bits.
      
        - Names like `extendInt64#` are flat-out wrong when `Int is
          32-bits.
      
        - `narrow{Int,Word}<N>#` however map a type to itself, and so don't
          suffer from this problem. They are left as-is.
      
      These changes are batched together because Alex happend to use the array
      ops. We can only use released versions of Alex at this time, sadly, and
      I don't want to have to have a release thatwon't work for the final GHC
      9.2. So by combining these we get all the changes for Alex done at once.
      
      Bump hackage state in a few places, and also make that workflow slightly
      easier for the future.
      
      Bump minimum Alex version
      
      Bump Cabal, array, bytestring, containers, text, and binary submodules
      d8dc0f96
    • Daniel Winograd-Cort's avatar
      Add cmpNat, cmpSymbol, and cmpChar · eea96042
      Daniel Winograd-Cort authored and Marge Bot's avatar Marge Bot committed
      Add Data.Type.Ord
      Add and update tests
      Metric Increase:
          MultiLayerModules
      eea96042
    • Sebastian Graf's avatar
      Fix typo in docs [skip ci] · 59e95bdf
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      59e95bdf
  3. Mar 02, 2021
  4. Mar 01, 2021
    • Sebastian Graf's avatar
      Pmc: Implement `considerAccessible` (#18610) · e571eda7
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      Consider (`T18610`):
      ```hs
        f :: Bool -> Int
        f x = case (x, x) of
          (True,  True)  -> 1
          (False, False) -> 2
          (True,  False) -> 3 -- Warning: Redundant
      ```
      The third clause will be flagged as redundant. Nevertheless, the
      programmer might intend to keep the clause in order to avoid bitrot.
      
      After this patch, the programmer can write
      ```hs
        g :: Bool -> Int
        g x = case (x, x) of
          (True,  True)  -> 1
          (False, False) -> 2
          (True,  False) | GHC.Exts.considerAccessible -> 3 -- No warning
      ```
      And won't be bothered any longer. See also `Note [considerAccessible]`
      and the updated entries in the user's guide.
      
      Fixes #18610 and #19228.
      e571eda7
    • Sebastian Graf's avatar
      Fix a bug causing loss of sharing in `UniqSDFM` · 51828c6d
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      While fixing #18610, I noticed that
      ```hs
      f :: Bool -> Int
      f x = case (x, x) of
        (True,  True)  -> 1
        (False, False) -> 2
      ```
      was *not* detected as exhaustive. I tracked it down to `equateUSDFM`,
      where upon merging equality classes of `x` and `y`, we failed to atually
      indirect the *representative* `x'` of the equality class of `x` to the
      representative `y'` of `y`.
      
      The fixed code is much more naturally and would I should have written in
      the first place. I can confirm that the above example now is detected as
      exhaustive. The commit that fixes #18610 comes directly after and it has
      `f` above as a regression test, so I saw no need to open a ticket or
      commit a separate regression test.
      51828c6d
    • Alan Zimmerman's avatar
      Wrap LHsContext in Maybe in the GHC AST · ce85cffc
      Alan Zimmerman authored and Marge Bot's avatar Marge Bot committed
      If the context is missing it is captured as Nothing, rather than
      putting a noLoc in the ParsedSource.
      
      Updates haddock submodule
      ce85cffc
    • Simon Peyton Jones's avatar
      Fix terrible occurrence-analysis bug · 6429943b
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      Ticket #19360 showed up a terrible bug in the occurrence analyser,
      in a situation like this
      
         Rec { f = g
             ; g = ..f...
               {-# RULE g .. = ...f... #-}  }
      
      Then f was postInlineUnconditionally, but not in the RULE (which
      is simplified first), so we had a RULE mentioning a variable that
      was not in scope.
      
      This led me to review (again) the subtle loop-breaker stuff in the
      occurrence analyser. The actual changes are few, and are largely
      simplifications.  I did a /lot/ of comment re-organising though.
      
      There was an unexpected amount of fallout.
      
      * Validation failed when compiling the stage2 compiler with profiling
        on. That turned to tickle a second latent bug in the same OccAnal
        code (at least I think it was always there), which led me to
        simplify still further; see Note [inl_fvs] in GHC.Core.Opt.OccurAnal.
      
      * But that in turn let me to some strange behaviour in CSE when ticks
        are in the picture, which I duly fixed.  See Note [Dealing with ticks]
        in GHC.Core.Opt.CSE.
      
      * Then I got an ASSERT failure in CoreToStg, which again seems to be
        a latent bug.  See Note [Ticks in applications] in GHC.CoreToStg
      
      * I also made one unforced change: I now simplify the RHS of a RULE in
        the same way as the RHS of a stable unfolding. This can allow a
        trivial binding to disappear sooner than otherwise, and I don't
        think it has any downsides.  The change is in
        GHC.Core.Opt.Simplify.simplRules.
      6429943b
    • Krzysztof Gogolewski's avatar
      Infer multiplicity in case expressions · 3b79e8b8
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      This is a first step towards #18738.
      3b79e8b8
    • Simon Peyton Jones's avatar
      Unify result type earlier to improve error messages · 7730713b
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      Ticket #19364 helpfully points out that we do not currently take
      advantage of pushing the result type of an application into the
      arguments.  This makes error messages notably less good.
      
      The fix is rather easy: move the result-type unification step earlier.
      It's even a bit more efficient; in the the checking case we now
      do one less zonk.
      
      See Note [Unify with expected type before typechecking arguments]
      in GHC.Tc.Gen.App
      
      This change generally improves error messages, but it made one worse:
      typecheck/should_fail/T16204c. That led me to the realisation that
      a good error can be replaced by a less-good one, which provoked
      me to change GHC.Tc.Solver.Interact.inertsCanDischarge.  It's
      explained in the new Note [Combining equalities]
      
      One other refactoring: I discovered that KindEqOrigin didn't need a
      Maybe in its type -- a nice simplification.
      7730713b
    • Sebastian Graf's avatar
      Widen acceptance window of `MultiLayerModules` (#19293) [skip ci] · 8c425bd8
      Sebastian Graf authored and Marge Bot's avatar Marge Bot committed
      As #19293 realises, this one keeps on flip flopping by 2.5%
      depending on how many modules there are within the GHC package.
      
      We should revert this once we figured out how to fix what's going on.
      8c425bd8
    • Ben Gamari's avatar
      testsuite: Accept allocations change in T10421 · f512f9e2
      Ben Gamari authored
      Metric Decrease:
          T10421
      f512f9e2
    • Ben Gamari's avatar
      rts/eventlog: Flush MainCapability buffer in non-threaded RTS · e18c430d
      Ben Gamari authored
      Previously flushEventLog failed to flush anything but the global event
      buffer in the non-threaded RTS.
      
      Fixes #19436.
      e18c430d
    • Ben Gamari's avatar
      rts/eventlog: Ensure that all capability buffers are flushed · 2628d61f
      Ben Gamari authored
      The previous approach performed the flush in yieldCapability. However,
      as pointed out in #19435, this is wrong as it idle capabilities will not
      go through this codepath.
      
      The fix is simple: undo the optimisation, flushing in `flushEventLog` by
      calling `flushAllCapsEventsBufs` after acquiring all capabilities.
      
      Fixes #19435.
      2628d61f
Loading