Skip to content
Snippets Groups Projects
  1. Jun 08, 2018
    • Moritz Angermann's avatar
      Move `iserv` into `utils` and change package name from `iserv-bin` to `iserv` · 6fbe5f27
      Moritz Angermann authored and Ben Gamari's avatar Ben Gamari committed
      This is done for consistency. We usually call the package file the same name the
      folder has.  The move into `utils` is done so that we can move the library into
      `libraries/iserv` and the proxy into `utils/iserv-proxy` and then break the
      `iserv.cabal` apart.  This will make building the cross compiler with TH
      simpler, because we can build the library and proxy as separate packages.
      
      Test Plan: ./validate
      
      Reviewers: bgamari, goldfire, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4436
      6fbe5f27
  2. Jun 07, 2018
    • Iavor S. Diatchki's avatar
      Allow Haddock comments before function arguments. · 200c8e04
      Iavor S. Diatchki authored
      Currently, documentation strings on function arguments has to be written
      after the argument (i.e., using `{-^ -}` comments).  This patch allows
      us to use `{-| -}` comments to put the comment string before an
      argument.   The same works for the results of functions.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, mpickering, carter
      
      Differential Revision: https://phabricator.haskell.org/D4767
      200c8e04
    • Matthew Pickering's avatar
      Run typeCheckResultAction and renamedResultAction in TcM rather than Hsc · dc8c03b2
      Matthew Pickering authored
      The primary motivation for this is that this allows users to access
      the warnings and error machinery present in TcM. However, it also allows
      users to use TcM actions which means they can typecheck GhcPs which
      could be significantly easier than constructing GhcTc.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15229
      
      Differential Revision: https://phabricator.haskell.org/D4792
      dc8c03b2
    • Matthew Pickering's avatar
      Rename dataConRepNameUnique to dataConTyRepNameUnique · fa34ced5
      Matthew Pickering authored
      The `DataCon` rep also applies to the worker. For example, see
      `MkId.mkDataConRep`.  `dataConTyRepNameUnique` is for the type
      representation, so we rename it to make this distinction clear.
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4797
      fa34ced5
    • Ben Gamari's avatar
      rts: Fix reference to srt_bitmap in ASSERT in RetainerProfile · 838cb53a
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: Validate
      
      Reviewers: erikd, simonmar
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4798
      838cb53a
    • Ryan Scott's avatar
      Fix #15236 by removing parentheses from funTyConName · 3397396a
      Ryan Scott authored
      Currently, `funTyConName` is defined as:
      
      ```lang=haskell
      funTyConName = mkPrimTyConName (fsLit "(->)") funTyConKey funTyCon
      ```
      
      What's strange about this definition is that there are extraneous
      parentheses around `->`, which is quite unlike every other infix
      `Name`. As a result, the `:info (->)` output is totally garbled (see
      Trac #15236).
      
      It's quite straightforward to fix that particular bug by removing the
      extraneous parentheses. However, it turns out that this makes some
      test output involving `Show` instances for `TypeRep` look less
      appealing, since `->` is no longer surrounded with parentheses when
      applied prefix. But neither were any /other/ infix type constructors!
      The right fix there was to change `showTypeable` to put parentheses
      around prefix applications of infix tycons.
      
      Test Plan: ./validate
      
      Reviewers: bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15236
      
      Differential Revision: https://phabricator.haskell.org/D4799
      3397396a
    • Ryan Scott's avatar
      Don't expose (~#), (~R#), (~P#) from GHC.Prim · 5926b6ed
      Ryan Scott authored
      Currently, the primitive `(~#)`, `(~R#)`, and `(~P#)` type
      constructors are wired in to be exported from `GHC.Prim`. This has
      some unfortunate consequences, however. It turns out that `(~#)` is
      actually a legal infix identifier, so users can make use of unboxed
      equalities in strange ways in user code (see #15209). The other two,
      `(~R#)` and `(~P#)`, can't be used in source code, but they can be
      observed with GHCi's `:browse` command, which is somewhat unnerving.
      
      The fix for both of these problems is simple: just don't wire them
      to be exported from `GHC.Prim`.
      
      Test Plan: make test TEST="T12023 T15209"
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: bgamari, dfeuer
      
      Subscribers: rwbarton, thomie, carter, dfeuer
      
      GHC Trac Issues: #12023, #15209
      
      Differential Revision: https://phabricator.haskell.org/D4801
      5926b6ed
    • Ben Gamari's avatar
      testsuite: Skip T13838 in ghci way · 04e29fc6
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Test Plan: `make slowtest TEST=T13838`
      
      Reviewers: alpmestan, dfeuer
      
      Reviewed By: dfeuer
      
      Subscribers: dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #15238
      
      Differential Revision: https://phabricator.haskell.org/D4802
      04e29fc6
    • Ryan Scott's avatar
      Document #15079 in the users' guide · bc9a838a
      Ryan Scott authored
      Trac #15079 revealed an interesting limitation in the interaction
      between variable visibility and higher-rank kinds. We (Richard and I)
      came to the conclusion that this is an acceptable (albeit surprising)
      limitation, so this documents in the users' guide to hopefully eliminate
      some confusion for others in the future.
      
      Test Plan: Read it
      
      Reviewers: goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15079
      
      Differential Revision: https://phabricator.haskell.org/D4803
      bc9a838a
    • Ryan Scott's avatar
      Fix #15243 by fixing incorrect uses of NotPromoted · 569c16a7
      Ryan Scott authored
      In `Convert`, we were incorrectly using `NotPromoted` to
      denote type constructors that were actually intended to be promoted,
      resulting in poor `-ddump-splices` output (as seen in #15243).
      Easily fixed.
      
      Test Plan: make test TEST=T15243
      
      Reviewers: bgamari, goldfire
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15243
      
      Differential Revision: https://phabricator.haskell.org/D4809
      569c16a7
    • Ben Gamari's avatar
      testsuite: Add test for #15232 · 5026840f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15232
      
      Differential Revision: https://phabricator.haskell.org/D4807
      5026840f
    • Alec Theriault's avatar
      Move 'HsBangTy' out in constructor arguments · 0361fc03
      Alec Theriault authored and Ben Gamari's avatar Ben Gamari committed
      When run with -haddock, a constructor argument can have both a a
      strictness/unpackedness annotation and a docstring. The parser binds
      'HsBangTy' more tightly than 'HsDocTy', yet for constructor arguments we
      really need the 'HsBangTy' on the outside.
      
      This commit does this shuffling in the 'mkConDeclH98' and 'mkGadtDecl'
      smart constructors.
      
      Test Plan: haddockA038, haddockC038
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: bgamari
      
      Subscribers: dfeuer, rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4727
      0361fc03
    • Andreas Klebinger's avatar
      Check if both branches of an Cmm if have the same target. · efea32cf
      Andreas Klebinger authored
      This for some reason or the other and makes it into the final
      binary. I've added the check to ContFlowOpt as that seems
      like a logical place for this.
      
      In a regular nofib run there were 30 occurences of this pattern.
      
      Test Plan: ci
      
      Reviewers: bgamari, simonmar, dfeuer, jrtc27, tdammers
      
      Reviewed By: bgamari, simonmar
      
      Subscribers: tdammers, dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #15188
      
      Differential Revision: https://phabricator.haskell.org/D4740
      efea32cf
    • Andreas Herrmann's avatar
      Fix unparseable pretty-printing of promoted data cons · 767536cc
      Andreas Herrmann authored and Ben Gamari's avatar Ben Gamari committed
      Previously we would print code which would not round-trip:
      ```
      > :set -XDataKinds
      > :set -XPolyKinds
      > data Proxy k = Proxy
      > _ :: Proxy '[ 'True ]
      error:
        Found hole: _ :: Proxy '['True]
      > _ :: Proxy '['True]
      error:
          Invalid type signature: _ :: ...
          Should be of form <variable> :: <type>
      ```
      
      Test Plan: Validate with T14343
      
      Reviewers: RyanGlScott, goldfire, bgamari, tdammers
      
      Reviewed By: RyanGlScott, bgamari
      
      Subscribers: tdammers, rwbarton, thomie, carter
      
      GHC Trac Issues: #14343
      
      Differential Revision: https://phabricator.haskell.org/D4746
      767536cc
    • David Feuer's avatar
      Index arrays more eagerly · e7678d6a
      David Feuer authored
      Many basic functions in `GHC.Arr` were unreasonably lazy about
      performing array lookups. This could lead to useless thunks
      at best and memory leaks at worst. Use eager lookups where
      they're obviously appropriate.
      
      Reviewers: bgamari, hvr
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4773
      e7678d6a
    • Ben Gamari's avatar
      WorkWrap: Rip out unsafeGlobalDynFlags usage in mkWwInlineRule · db4f064e
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4775
      db4f064e
    • Ben Gamari's avatar
      Don't use unsafeGlobalDynFlags in optCoercion · 64c71ce9
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This plumbs DynFlags through CoreOpt so optCoercion can finally
      eliminate its usage of `unsafeGlobalDynFlags`.
      
      Note that this doesn't completely eliminate `unsafeGlobalDynFlags`
      usage from this bit of the compiler. A few uses are introduced in
      call-sites where we don't (yet) have ready access to `DynFlags`.
      
      Test Plan: Validate
      
      Reviewers: goldfire
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4774
      64c71ce9
    • Ben Gamari's avatar
      Update hadrian submodule · f7417118
      Ben Gamari authored
      f7417118
    • Ben Gamari's avatar
      testsuite: Fix dynamic-paper stderr file · 1508600c
      Ben Gamari authored
      The stderr file was empty, yet GHC fails with an error.
      1508600c
    • Simon Peyton Jones's avatar
      Remove ad-hoc special case in occAnal · c16382d5
      Simon Peyton Jones authored
      Back in 1999 I put this ad-hoc code in the Case-handling
      code for occAnal:
      
        occAnal env (Case scrut bndr ty alts)
         = ...
              -- Note [Case binder usage]
              -- ~~~~~~~~~~~~~~~~~~~~~~~~
              -- The case binder gets a usage of either "many" or "dead", never "one".
              -- Reason: we like to inline single occurrences, to eliminate a binding,
              -- but inlining a case binder *doesn't* eliminate a binding.
              -- We *don't* want to transform
              --      case x of w { (p,q) -> f w }
              -- into
              --      case x of w { (p,q) -> f (p,q) }
          tag_case_bndr usage bndr
            = (usage', setIdOccInfo bndr final_occ_info)
            where
              occ_info       = lookupDetails usage bndr
              usage'         = usage `delDetails` bndr
              final_occ_info = case occ_info of IAmDead -> IAmDead
                                                _       -> noOccInfo
      
      But the comment looks wrong -- the bad inlining will not happen -- and
      I think it relates to some long-ago version of the simplifier.
      
      So I simply removed the special case, which gives more accurate
      occurrence-info to the case binder.  Interestingly I got a slight
      improvement in nofib binary sizes.
      
      --------------------------------------------------------------------------------
              Program           Size    Allocs   Runtime   Elapsed  TotalMem
      --------------------------------------------------------------------------------
            cacheprof          -0.1%     +0.2%     -0.7%     -1.2%     +8.6%
      --------------------------------------------------------------------------------
                  Min          -0.2%      0.0%    -14.5%    -30.5%      0.0%
                  Max          -0.1%     +0.2%    +10.0%    +10.0%    +25.0%
       Geometric Mean          -0.2%     +0.0%     -1.9%     -5.4%     +0.3%
      
      I have no idea if the improvement in runtime is real.  I did look at the
      tiny increase in allocation for cacheprof and concluded that it was
      unimportant (I forget the details).
      
      Also the more accurate occ-info for the case binder meant that some
      inlining happens in one pass that previously took successive passes
      for the test dependent/should_compile/dynamic-paper (which has a
      known Russel-paradox infinite loop in the simplifier).
      
      In short, a small win: less ad-hoc complexity and slightly smaller
      binaries.
      c16382d5
    • Simon Peyton Jones's avatar
      Comments only · 7f459064
      Simon Peyton Jones authored
      7f459064
    • Ömer Sinan Ağacan's avatar
      Do not scavenge SMALL_MUT_ARR_PTRS_CLEAN in mut_lists · 635a59a5
      Ömer Sinan Ağacan authored
      For the same reason with MUT_ARR_PTRS_CLEAN we don't need to scavenge
      SMALL_MUT_ARR_PTRS_CLEAN in mut_lists.
      
      Because SMALL_MUT_ARR_PTRS doesn't have a card table we don't have a
      special case when scavenging SMALL_MUT_ARR_PTRS_DIRTY in a mut_list.
      
      Test Plan: this validates
      
      Reviewers: simonmar, bgamari, erikd
      
      Reviewed By: simonmar, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4800
      635a59a5
  3. Jun 06, 2018
  4. Jun 05, 2018
    • Ömer Sinan Ağacan's avatar
      rts: Reuse dbl_link_remove in a few places · 455477a3
      Ömer Sinan Ağacan authored
      Test Plan: this validates
      
      Reviewers: simonmar, bgamari, erikd
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4795
      455477a3
    • Ömer Sinan Ağacan's avatar
      Rename some mutable closure types for consistency · 4075656e
      Ömer Sinan Ağacan authored
      SMALL_MUT_ARR_PTRS_FROZEN0 -> SMALL_MUT_ARR_PTRS_FROZEN_DIRTY
      SMALL_MUT_ARR_PTRS_FROZEN  -> SMALL_MUT_ARR_PTRS_FROZEN_CLEAN
      MUT_ARR_PTRS_FROZEN0       -> MUT_ARR_PTRS_FROZEN_DIRTY
      MUT_ARR_PTRS_FROZEN        -> MUT_ARR_PTRS_FROZEN_CLEAN
      
      Naming is now consistent with other CLEAR/DIRTY objects (MVAR, MUT_VAR,
      MUT_ARR_PTRS).
      
      (alternatively we could rename MVAR_DIRTY/MVAR_CLEAN etc. to MVAR0/MVAR)
      
      Removed a few comments in Scav.c about FROZEN0 being on the mut_list
      because it's now clear from the closure type.
      
      Reviewers: bgamari, simonmar, erikd
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4784
      4075656e
    • Ryan Scott's avatar
      Introduce DerivingVia · 8ed8b037
      Ryan Scott authored
      This implements the `DerivingVia` proposal put forth in
      https://github.com/ghc-proposals/ghc-proposals/pull/120.
      
      This introduces the `DerivingVia` deriving strategy. This is a
      generalization of `GeneralizedNewtypeDeriving` that permits the user
      to specify the type to `coerce` from.
      
      The major change in this patch is the introduction of the
      `ViaStrategy` constructor to `DerivStrategy`, which takes a type
      as a field. As a result, `DerivStrategy` is no longer a simple
      enumeration type, but rather something that must be renamed and
      typechecked. The process by which this is done is explained more
      thoroughly in section 3 of this paper
      ( https://www.kosmikus.org/DerivingVia/deriving-via-paper.pdf ),
      although I have inlined the relevant parts into Notes where possible.
      
      There are some knock-on changes as well. I took the opportunity to
      do some refactoring of code in `TcDeriv`, especially the
      `mkNewTypeEqn` function, since it was bundling all of the logic for
      (1) deriving instances for newtypes and
      (2) `GeneralizedNewtypeDeriving`
      into one huge broth. `DerivingVia` reuses much of part (2), so that
      was factored out as much as possible.
      
      Bumps the Haddock submodule.
      
      Test Plan: ./validate
      
      Reviewers: simonpj, bgamari, goldfire, alanz
      
      Subscribers: alanz, goldfire, rwbarton, thomie, mpickering, carter
      
      GHC Trac Issues: #15178
      
      Differential Revision: https://phabricator.haskell.org/D4684
      8ed8b037
  5. Jun 04, 2018
    • Simon Jakobi's avatar
      Serialize docstrings to ifaces, display them with new GHCi :doc command · 85309a3c
      Simon Jakobi authored and Ben Gamari's avatar Ben Gamari committed
      If `-haddock` is set, we now extract docstrings from the renamed ast
      and serialize them in the .hi-files.
      
      This includes some of the changes from D4749 with the notable
      exceptions of the docstring lexing and renaming.
      
      A currently limited and experimental GHCi :doc command can be used
      to display docstrings for declarations.
      
      The formatting of pretty-printed docstrings is changed slightly,
      causing some changes in testsuite/tests/haddock.
      
      Test Plan: ./validate
      
      Reviewers: alexbiehl, hvr, gershomb, harpocrates, bgamari
      
      Reviewed By: alexbiehl
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4758
      85309a3c
    • Andreas Klebinger's avatar
      Also suppress uniques in cmm dumps with `-dsuppress-uniques`. · aa77c602
      Andreas Klebinger authored
      Allows easier structural comparison of Cmm code.
      
      Before:
      ```
             cxCH: // global
                 _suEU::P64 = R1;
                 if ((Sp + -16) < SpLim) (likely: False) goto cxCI; else goto
      cxCJ;
      ```
      
      After
      ```
             _lbl_: // global
                 __locVar_::P64 = R1;
                 if ((Sp + -16) < SpLim) (likely: False) goto cxBf; else goto
      cxBg;
      ```
      
      Test Plan: Looking at dumps, ci
      
      Reviewers: bgamari, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4786
      aa77c602
    • Matthew Pickering's avatar
      Improve extendTvSubst assertion · 97cea315
      Matthew Pickering authored
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4790
      97cea315
    • Matthew Pickering's avatar
      Add Outputable instance for HsArg · 1a61c6b8
      Matthew Pickering authored
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4791
      1a61c6b8
    • Simon Peyton Jones's avatar
      Implement QuantifiedConstraints · 7df58960
      Simon Peyton Jones authored
      We have wanted quantified constraints for ages and, as I hoped,
      they proved remarkably simple to implement.   All the machinery was
      already in place.
      
      The main ticket is Trac #2893, but also relevant are
        #5927
        #8516
        #9123 (especially!  higher kinded roles)
        #14070
        #14317
      
      The wiki page is
        https://ghc.haskell.org/trac/ghc/wiki/QuantifiedConstraints
      which in turn contains a link to the GHC Proposal where the change
      is specified.
      
      Here is the relevant Note:
      
      Note [Quantified constraints]
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      The -XQuantifiedConstraints extension allows type-class contexts like
      this:
      
        data Rose f x = Rose x (f (Rose f x))
      
        instance (Eq a, forall b. Eq b => Eq (f b))
              => Eq (Rose f a)  where
          (Rose x1 rs1) == (Rose x2 rs2) = x1==x2 && rs1 >= rs2
      
      Note the (forall b. Eq b => Eq (f b)) in the instance contexts.
      This quantified constraint is needed to solve the
       [W] (Eq (f (Rose f x)))
      constraint which arises form the (==) definition.
      
      Here are the moving parts
        * Language extension {-# LANGUAGE QuantifiedConstraints #-}
          and add it to ghc-boot-th:GHC.LanguageExtensions.Type.Extension
      
        * A new form of evidence, EvDFun, that is used to discharge
          such wanted constraints
      
        * checkValidType gets some changes to accept forall-constraints
          only in the right places.
      
        * Type.PredTree gets a new constructor ForAllPred, and
          and classifyPredType analyses a PredType to decompose
          the new forall-constraints
      
        * Define a type TcRnTypes.QCInst, which holds a given
          quantified constraint in the inert set
      
        * TcSMonad.InertCans gets an extra field, inert_insts :: [QCInst],
          which holds all the Given forall-constraints.  In effect,
          such Given constraints are like local instance decls.
      
        * When trying to solve a class constraint, via
          TcInteract.matchInstEnv, use the InstEnv from inert_insts
          so that we include the local Given forall-constraints
          in the lookup.  (See TcSMonad.getInstEnvs.)
      
        * topReactionsStage calls doTopReactOther for CIrredCan and
          CTyEqCan, so they can try to react with any given
          quantified constraints (TcInteract.matchLocalInst)
      
        * TcCanonical.canForAll deals with solving a
          forall-constraint.  See
             Note [Solving a Wanted forall-constraint]
             Note [Solving a Wanted forall-constraint]
      
        * We augment the kick-out code to kick out an inert
          forall constraint if it can be rewritten by a new
          type equality; see TcSMonad.kick_out_rewritable
      
      Some other related refactoring
      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
      
      * Move SCC on evidence bindings to post-desugaring, which fixed
        #14735, and is generally nicer anyway because we can use
        existing CoreSyn free-var functions.  (Quantified constraints
        made the free-vars of an ev-term a bit more complicated.)
      
      * In LookupInstResult, replace GenInst with OneInst and NotSure,
        using the latter for multiple matches and/or one or more
        unifiers
      7df58960
    • Andreas Klebinger's avatar
      Document the fact that cmm dumps won't show unreachable blocks. · 36091ec9
      Andreas Klebinger authored
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4788
      36091ec9
    • Tao He's avatar
      Fix broken test T14547. · d8efb098
      Tao He authored
      Phab:D4571 lags behind HEAD for too many commits. The commit of
      Phab:4571 1f88f541 brought some
      unintentional changes (not belong to [Phab:4571's Diff
      16314](https://phabricator.haskell.org/differential/diff/16314/)) into
      ghc-head, breaking T14557.
      
      Let's fix that.
      
      Test Plan: make test TEST="T14547"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15222
      
      Differential Revision: https://phabricator.haskell.org/D4778
      d8efb098
    • Ben Gamari's avatar
      Bump stm and haskeline submodules · c560f382
      Ben Gamari authored
      c560f382
    • Simon Peyton Jones's avatar
      Refactor SetLevels.abstractVars · a1a507a1
      Simon Peyton Jones authored
      This patch is pure refactoring: using utility functions
      rather than special-purpose code, especially for closeOverKinds
      a1a507a1
    • Simon Peyton Jones's avatar
      Expand type synonyms when Linting a forall · 9d600ea6
      Simon Peyton Jones authored
      Trac #14939 showed a type like
         type Alg cls ob = ob
         f :: forall (cls :: * -> Constraint) (b :: Alg cls *). b
      
      where the kind of the forall looks like (Alg cls *), with a
      free cls. This tripped up Core Lint.
      
      I fixed this by making Core Lint a bit more forgiving, expanding
      type synonyms if necessary.
      
      I'm worried that this might not be the whole story; notably
      typeKind looks suspect.  But it certainly fixes this problem.
      9d600ea6
    • Simon Peyton Jones's avatar
      Do a late CSE pass · 0e5d2b74
      Simon Peyton Jones authored
      When investigating something else I found that a condition
      was being re-evaluated in wheel-seive1.  Why, when CSE should
      find it?  Because the opportunity only showed up after
      LiberateCase
      
      This patch adds a late CSE pass. Rather than give it an extra
      flag I do it when (cse && (spec_constr || liberate_case)), so
      roughly speaking it happense with -O2.
      
      In any case, CSE is very cheap.
      
      Nofib results are minor but in the right direction:
      
              Program           Size    Allocs   Runtime   Elapsed  TotalMem
      --------------------------------------------------------------------------------
                 anna          -0.1%     -0.0%     0.163     0.163      0.0%
                eliza          -0.1%     -0.4%     0.001     0.001      0.0%
                 fft2          -0.1%      0.0%     0.087     0.087      0.0%
                 mate          -0.0%     -1.3%     -0.8%     -0.8%      0.0%
            paraffins          -0.0%     -0.1%     +0.9%     +0.9%      0.0%
                  pic          -0.0%     -0.1%     0.009     0.009      0.0%
         wheel-sieve1          -0.2%     -0.0%     -0.1%     -0.1%      0.0%
      --------------------------------------------------------------------------------
                  Min          -0.6%     -1.3%     -2.4%     -2.4%      0.0%
                  Max          +0.0%     +0.0%     +3.8%     +3.8%    +23.8%
       Geometric Mean          -0.0%     -0.0%     +0.2%     +0.2%     +0.2%
      0e5d2b74
    • Matthew Pickering's avatar
      Provide `getWithUserData` and `putWithUserData` · 554bc7fc
      Matthew Pickering authored
      Summary:
      This makes it possible to serialise Names and FastStrings in user
      programs, for example, when writing a source plugin.
      
      When writing my first source plugin, I wanted to serialise names but it
      wasn't possible easily without exporting additional constructors. This
      interface is sufficient and abstracts nicely over the symbol table and
      dictionary.
      
      Reviewers: alpmestan, bgamari
      
      Reviewed By: alpmestan
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15223
      
      Differential Revision: https://phabricator.haskell.org/D4782
      554bc7fc
  6. Jun 03, 2018
Loading