Skip to content
Snippets Groups Projects
  1. Jun 05, 2018
    • 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
  2. Jun 03, 2018
  3. May 18, 2018
    • Simon Peyton Jones's avatar
      Orient TyVar/TyVar equalities with deepest on the left · 2bbdd00c
      Simon Peyton Jones authored
      Trac #15009 showed that, for Given TyVar/TyVar equalities, we really
      want to orient them with the deepest-bound skolem on the left. As it
      happens, we also want to do the same for Wanteds, but for a different
      reason (more likely to be touchable).  Either way, deepest wins:
      see TcUnify Note [Deeper level on the left].
      
      This observation led me to some significant changes:
      
      * A SkolemTv already had a TcLevel, but the level wasn't really being
        used.   Now it is!
      
      * I updated added invariant (SkolInf) to TcType
        Note [TcLevel and untouchable type variables], documenting that
        the level number of all the ic_skols should be the same as the
        ic_tclvl of the implication
      
      * FlatSkolTvs and FlatMetaTvs previously had a dummy level-number of
        zero, which messed the scheme up.   Now they get a level number the
        same way as all other TcTyVars, instead of being a special case.
      
      * To make sure that FlatSkolTvs and FlatMetaTvs are untouchable (which
        was previously done via their magic zero level) isTouchableMetaTyVar
        just tests for those two cases.
      
      * TcUnify.swapOverTyVars is the crucial orientation function; see the
        new Note [TyVar/TyVar orientation].  I completely rewrote this function,
        and it's now much much easier to understand.
      
      I ended up doing some related refactoring, of course
      
      * I noticed that tcImplicitTKBndrsX and tcExplicitTKBndrsX were doing
        a lot of useless work in the case where there are no skolems; I
        added a fast-patch
      
      * Elminate the un-used tcExplicitTKBndrsSig; and thereby get rid of
        the higher-order parameter to tcExpliciTKBndrsX.
      
      * Replace TcHsType.emitTvImplication with TcUnify.checkTvConstraints,
        by analogy with TcUnify.checkConstraints.
      
      * Inline TcUnify.buildImplication into its only call-site in
        TcUnify.checkConstraints
      
      * TcS.buildImplication becomes TcS.CheckConstraintsTcS, with a
        simpler API
      
      * Now that we have NoEvBindsVar we have no need of termEvidenceAllowed;
        nuke the latter, adding Note [No evidence bindings] to TcEvidence.
      2bbdd00c
  4. May 16, 2018
    • Ryan Scott's avatar
      Fix #15073 by suggesting UnboxedTuples in an error message · 0c7db226
      Ryan Scott authored
      Under certain circumstances, `GeneralizedNewtypeDeriving`
      can emit code which uses unboxed tuple types, but if `UnboxedTuples`
      wasn't enabled, the error message that GHC gave didn't make it very
      clear that it could be worked around by explicitly enabling the
      extension. Easily fixed.
      
      Test Plan: make test TEST=T15073
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: simonpj, thomie, carter
      
      GHC Trac Issues: #15073
      
      Differential Revision: https://phabricator.haskell.org/D4620
      0c7db226
  5. May 14, 2018
    • Ryan Scott's avatar
      Fix #14875 by introducing PprPrec, and using it · 21e1a00c
      Ryan Scott authored
      Trying to determine when to insert parentheses during TH
      conversion is a bit of a mess. There is an assortment of functions
      that try to detect this, such as:
      
      * `hsExprNeedsParens`
      * `isCompoundHsType`
      * `hsPatNeedsParens`
      * `isCompoundPat`
      * etc.
      
      To make things worse, each of them have slightly different semantics.
      Plus, they don't work well in the presence of explicit type
      signatures, as #14875 demonstrates.
      
      All of these problems can be alleviated with the use of an explicit
      precedence argument (much like what `showsPrec` currently does). To
      accomplish this, I introduce a new `PprPrec` data type, and define
      standard predences for things like function application, infix
      operators, function arrows, and explicit type signatures (that last
      one is new). I then added `PprPrec` arguments to the various
      `-NeedsParens` functions, and use them to make smarter decisions
      about when things need to be parenthesized.
      
      A nice side effect is that functions like `isCompoundHsType` are
      now completely unneeded, since they're simply aliases for
      `hsTypeNeedsParens appPrec`. As a result, I did a bit of refactoring
      to remove these sorts of functions. I also did a pass over various
      utility functions in GHC for constructing AST forms and used more
      appropriate precedences where convenient.
      
      Along the way, I also ripped out the existing `TyPrec`
      data type (which was tailor-made for pretty-printing `Type`s) and
      replaced it with `PprPrec` for consistency.
      
      Test Plan: make test TEST=T14875
      
      Reviewers: alanz, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14875
      
      Differential Revision: https://phabricator.haskell.org/D4688
      21e1a00c
  6. Apr 01, 2018
    • Richard Eisenberg's avatar
      Track type variable scope more carefully. · faec8d35
      Richard Eisenberg authored
      The main job of this commit is to track more accurately the scope
      of tyvars introduced by user-written foralls. For example, it would
      be to have something like this:
      
        forall a. Int -> (forall k (b :: k). Proxy '[a, b]) -> Bool
      
      In that type, a's kind must be k, but k isn't in scope. We had a
      terrible way of doing this before (not worth repeating or describing
      here, but see the old tcImplicitTKBndrs and friends), but now
      we have a principled approach: make an Implication when kind-checking
      a forall. Doing so then hooks into the existing machinery for
      preventing skolem-escape, performing floating, etc. This also means
      that we bump the TcLevel whenever going into a forall.
      
      The new behavior is done in TcHsType.scopeTyVars, but see also
      TcHsType.tc{Im,Ex}plicitTKBndrs, which have undergone significant
      rewriting. There are several Notes near there to guide you. Of
      particular interest there is that Implication constraints can now
      have skolems that are out of order; this situation is reported in
      TcErrors.
      
      A major consequence of this is a slightly tweaked process for type-
      checking type declarations. The new Note [Use SigTvs in kind-checking
      pass] in TcTyClsDecls lays it out.
      
      The error message for dependent/should_fail/TypeSkolEscape has become
      noticeably worse. However, this is because the code in TcErrors goes to
      some length to preserve pre-8.0 error messages for kind errors. It's time
      to rip off that plaster and get rid of much of the kind-error-specific
      error messages. I tried this, and doing so led to a lovely error message
      for TypeSkolEscape. So: I'm accepting the error message quality regression
      for now, but will open up a new ticket to fix it, along with a larger
      error-message improvement I've been pondering. This applies also to
      dependent/should_fail/{BadTelescope2,T14066,T14066e}, polykinds/T11142.
      
      Other minor changes:
       - isUnliftedTypeKind didn't look for tuples and sums. It does now.
      
       - check_type used check_arg_type on both sides of an AppTy. But the left
         side of an AppTy isn't an arg, and this was causing a bad error message.
         I've changed it to use check_type on the left-hand side.
      
       - Some refactoring around when we print (TYPE blah) in error messages.
         The changes decrease the times when we do so, to good effect.
         Of course, this is still all controlled by
         -fprint-explicit-runtime-reps
      
      Fixes #14066 #14749
      
      Test cases: dependent/should_compile/{T14066a,T14749},
                  dependent/should_fail/T14066{,c,d,e,f,g,h}
      faec8d35
  7. 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
    • 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
  8. Mar 23, 2018
    • 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
  9. Feb 18, 2018
    • Ryan Scott's avatar
      Implement stopgap solution for #14728 · 1ede46d4
      Ryan Scott authored
      It turns out that one can produce ill-formed Core by
      combining `GeneralizedNewtypeDeriving`, `TypeInType`, and
      `TypeFamilies`, as demonstrated in #14728. The root of the problem
      is allowing the last parameter of a class to appear in a //kind// of
      an associated type family, as our current approach to deriving
      associated type family instances simply doesn't work well for that
      situation.
      
      Although it might be possible to properly implement this feature
      today (see https://ghc.haskell.org/trac/ghc/ticket/14728#comment:3
      for a sketch of how this might work), there does not currently exist
      a performant implementation of the algorithm needed to accomplish
      this. Until such an implementation surfaces, we will make this corner
      case of `GeneralizedNewtypeDeriving` an error.
      
      Test Plan: make test TEST="T14728a T14728b"
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14728
      
      Differential Revision: https://phabricator.haskell.org/D4402
      1ede46d4
  10. Feb 01, 2018
    • Ryan Scott's avatar
      Sequester deriving-related validity check into cond_stdOK · 1a911f21
      Ryan Scott authored
      Currently, any standalone-derived instance must satisfy the
      property that the tycon of the data type having an instance being
      derived for it must be either a normal ADT tycon or a data family
      tycon. But there are several other primitive tycons—such as `(->)`,
      `Int#`, and others—which cannot have standalone-derived instances
      (via the `anyclass` strategy) as a result of this check! See
      https://ghc.haskell.org/trac/ghc/ticket/13154#comment:8 for an
      example of where this overly conservative restriction bites.
      
      Really, this validity check only makes sense in the context of
      `stock` deriving, where we need the property that the tycon is that
      of a normal ADT or a data family in order to inspect its data
      constructors. Other deriving strategies don't require this validity
      check, so the most sensible way to fix this error is to move the
      logic of this check into `cond_stdOK`, which is specific to
      `stock` deriving.
      
      This makes progress towards fixing (but does not entirely fix)
      
      Test Plan: make test TEST=T13154a
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13154
      
      Differential Revision: https://phabricator.haskell.org/D4337
      1a911f21
  11. Jan 21, 2018
  12. Jan 18, 2018
    • Ryan Scott's avatar
      Fix #14681 and #14682 with precision-aimed parentheses · 575c009d
      Ryan Scott authored
      It turns out that `Convert` was recklessly leaving off
      parentheses in two places:
      
      * Negative numeric literals
      * Patterns in lambda position
      
      This patch fixes it by adding three new functions, `isCompoundHsLit`,
      `isCompoundHsOverLit`, and `isCompoundPat`, and using them in the
      right places in `Convert`. While I was in town, I also sprinkled
      `isCompoundPat` among some `Pat`-constructing functions in `HsUtils`
      to help avoid the likelihood of this problem happening in other
      places. One of these places is in `TcGenDeriv`, and sprinkling
      `isCompountPat` there fixes #14682
      
      Test Plan: make test TEST="T14681 T14682"
      
      Reviewers: alanz, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14681, #14682
      
      Differential Revision: https://phabricator.haskell.org/D4323
      575c009d
  13. Jan 04, 2018
    • Ryan Scott's avatar
      Make typeToLHsType produce kind signatures for tycon applications · 649e7772
      Ryan Scott authored
      Summary:
      `GeneralizedNewtypeDeriving` generates calls to `coerce`
      which take visible type arguments. These types must be produced by
      way of `typeToLHsType`, which converts a `Type` to an `LHsType`.
      However, `typeToLHsType` was leaving off important kind information
      when a `Type` contained a poly-kinded tycon application, leading to
      incorrectly generated code in #14579.
      
      This fixes the issue by tweaking `typeToLHsType` to generate
      explicit kind signatures for tycon applications. This makes the
      generated code noisier, but at least the program from #14579 now
      works correctly.
      
      Test Plan: make test TEST=T14579
      
      Reviewers: simonpj, bgamari
      
      Reviewed By: simonpj
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14579
      
      Differential Revision: https://phabricator.haskell.org/D4264
      649e7772
  14. Dec 21, 2017
    • Ryan Scott's avatar
      Remove hack put in place for #12512 · 9cb289ab
      Ryan Scott authored
      Summary:
      Previously, I added an ad hoc check for unboxed tuples and
      sums in standalone-derived instances to fix #12512, under the
      pretense that polymorphism over `UnboxedTupleRep` and
      `UnboxedSumRep` was a lie. But that is no longer the case, and so
      this ad hoc check can be removed entirely. Less code, and easier to
      understand.
      
      Test Plan: make test TEST=T12512
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4271
      9cb289ab
    • Ryan Scott's avatar
      Fix #14578 by checking isCompoundHsType in more places · 1bd91a7a
      Ryan Scott authored
      Summary:
      The `HsType` pretty-printer does not automatically insert
      parentheses where necessary for type applications, so a function
      `isCompoundHsType` was created in D4056 towards this purpose.
      However, it was not used in as many places as it ought to be,
      resulting in #14578.
      
      Test Plan: make test TEST=T14578
      
      Reviewers: alanz, bgamari, simonpj
      
      Reviewed By: alanz, simonpj
      
      Subscribers: simonpj, rwbarton, thomie, carter
      
      GHC Trac Issues: #14578
      
      Differential Revision: https://phabricator.haskell.org/D4266
      1bd91a7a
  15. Nov 08, 2017
    • Simon Peyton Jones's avatar
      Minimise provided dictionaries in pattern synonyms · 2c2f3cea
      Simon Peyton Jones authored
      Trac #14394 showed that it's possible to get redundant
      constraints in the inferred provided constraints of a pattern
      synonym.  This patch removes the redundancy with mkMinimalBySCs.
      
      To do this I had to generalise the type of mkMinimalBySCs slightly.
      And, to reduce confusing reversal, I made it stable: it now returns
      its result in the same order as its input.  That led to a raft of
      error message wibbles, mostly for the better.
      2c2f3cea
  16. Nov 02, 2017
  17. Oct 19, 2017
    • Ryan Scott's avatar
      Error when deriving instances in hs-boot files · 101a8c77
      Ryan Scott authored
      Summary:
      According to the GHC users' guide, one cannot derive
      instances for data types in `.hs-boot` files.
      However, GHC was not enforcing this in practice, which led to
      #14365.
      
      Fix this by actually throwing an error if a derived instance is
      detected in an `.hs-boot` file (and recommend how to fix it in the
      error message.)
      
      Test Plan: make test TEST=T14365
      
      Reviewers: ezyang, austin, bgamari, simonpj
      
      Reviewed By: simonpj
      
      Subscribers: simonpj, rwbarton, thomie
      
      GHC Trac Issues: #14365
      
      Differential Revision: https://phabricator.haskell.org/D4102
      101a8c77
  18. Oct 12, 2017
    • Simon Peyton Jones's avatar
      Do not quantify over deriving clauses · 82b77ec3
      Simon Peyton Jones authored
      Trac #14331 showed that in a data type decl like
      
         data D = D deriving (C (a :: k))
      
      we were quantifying D over the 'k' in the deriving clause.  Yikes.
      
      Easily fixed, by deleting code in RnTypes.extractDataDefnKindVars
      
      See the discussion on the ticket, esp comment:8.
      82b77ec3
  19. Oct 11, 2017
    • Simon Peyton Jones's avatar
      Add a missing zonk in TcDerivInfer.simplifyDeriv · 13fdca3d
      Simon Peyton Jones authored
      I'm astonished that anything worked without this!
      
      Fixes Trac #14339
      13fdca3d
    • Simon Peyton Jones's avatar
      Remove wc_insol from WantedConstraints · f20cf982
      Simon Peyton Jones authored
      This patch is a pure refactoring, which I've wanted to do for
      some time.  The main payload is
      
      * Remove the wc_insol field from WantedConstraints;
        instead put all the insolubles in wc_simple
      
      * Remove inert_insols from InertCans
        Instead put all the insolubles in inert_irreds
      
      * Add a cc_insol flag to CIrredCan, to record that
        the constraint is definitely insoluble
      
      Reasons
      
      * Quite a bit of code gets slightly simpler
      * Fewer concepts to keep separate
      * Insolubles don't happen at all in production code that is
        just being recompiled, so previously there was a lot of
        moving-about of empty sets
      
      A couple of error messages acutally improved.
      f20cf982
  20. Sep 27, 2017
  21. Aug 17, 2017
    • Ryan Scott's avatar
      Remove unneeded reqlibs for mtl and parsec in the GHC testsuite · 03853475
      Ryan Scott authored
      Now that `mtl` and `parsec` are boot libraries, there's no need to
      qualify various tests in the testsuite with `reqlib('mtl')` or
      `reqlib('parsec')`.
      
      Test Plan: make test TEST="T4809 tcfail126 T4355 tc232 tc223 tc220
      tc217 tc183 T5303 DoParamM qq005 qq006 galois_raytrace T1074 mod133
      T3787 T4316 prog011 drvfail006 drvfail008"
      
      Reviewers: bgamari, austin
      
      Subscribers: rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3855
      03853475
  22. Aug 12, 2017
    • Ryan Scott's avatar
      Don't suppress unimplemented type family warnings with DeriveAnyClass · 3f05e5f6
      Ryan Scott authored
      Summary:
      For some asinine reason, we were suppressing warnings when
      deriving associated type family instances with `DeriveAnyClass`. That seems
      like a bad idea. Let's not do that.
      
      Along the way, I noticed that the error contexts associated with these
      newly emitted warnings were less than ideal, so I did some minor refactoring
      to improve the story there.
      
      Fixes #14094
      
      Test Plan: ./validate
      
      Reviewers: bgamari, austin
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14094
      
      Differential Revision: https://phabricator.haskell.org/D3828
      3f05e5f6
  23. Aug 05, 2017
    • Ryan Scott's avatar
      Remove the deprecated Typeable{1..7} type synonyms · a81b5b00
      Ryan Scott authored
      Summary:
      `Typeable{1..7}` (type synonyms for the poly-kinded `Typeable`) have
      been deprecated since GHC 7.8. They're now causing problems for users who try
      to still work with them in legacy code, since they can no longer be used in
      instances. To avoid this sort of confusion, let's just remove `Typeable{1..7}`
      altogether. Resolves #14047.
      
      Reviewers: bgamari, austin, hvr
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #14047
      
      Differential Revision: https://phabricator.haskell.org/D3817
      a81b5b00
  24. Aug 02, 2017
  25. Jul 26, 2017
    • Simon Peyton Jones's avatar
      Fix binder visiblity for default methods · 75bf11c0
      Simon Peyton Jones authored
      Trac #13998 showed that default methods were getting bogus tyvar
      binder visiblity info; and that it matters in the code genreated
      by the default-method fill-in mechanism
      
      * The actual fix: in TcTyDecls.mkDefaultMethodType, make TyVarBinders
        with the right visibility info by getting TyConBinders from the
        class TyCon.  (Previously we made up visiblity info, but that
        caused #13998.)
      
      * Define TyCon.tyConTyVarBinders :: [TyConBinder] -> [TyVarBinder]
        which can build correct forall binders for
          a) default methods (Trac #13998)
          b) data constructors
        This was originally BuildTyCl.mkDataConUnivTyVarBinders
      
      * Move mkTyVarBinder, mkTyVarBinders from Type to Var
      75bf11c0
  26. Jul 25, 2017
    • Ryan Scott's avatar
      Fix #10684 by processing deriving clauses with finer grain · 6bb32ba7
      Ryan Scott authored
      Summary:
      Previously, one could experience error cascades with deriving clauses
      when one class in a set of many failed to derive, causing the other derived
      classes to be skipped entirely and resulting in other errors down the line.
      The solution is to process each class in a data type's set of deriving clauses
      individually, and engineer it so that failure to derive an individual class
      within that set doesn't cancel out the others.
      
      Test Plan: make test TEST="T10684 T12801"
      
      Reviewers: austin, bgamari, simonpj
      
      Reviewed By: simonpj
      
      Subscribers: simonpj, rwbarton, thomie
      
      GHC Trac Issues: #10684, #12801
      
      Differential Revision: https://phabricator.haskell.org/D3771
      6bb32ba7
  27. Jul 12, 2017
  28. Jul 11, 2017
    • Ryan Scott's avatar
      Suppress unused warnings for selectors for some derived classes · 15fcd9ad
      Ryan Scott authored
      Although derived `Read`, `Show`, and `Generic` instances technically
      don't //use// the record selectors of the data type for which an
      instance is being derived, the derived code is affected by the
      //presence// of record selectors. As a result, we should suppress
      `-Wunused-binds` for those record selectors when deriving these classes.
      This is accomplished by threading through more information from
      `hasStockDeriving`.
      
      Test Plan: make test TEST=T13919
      
      Reviewers: austin, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie
      
      GHC Trac Issues: #13919
      
      Differential Revision: https://phabricator.haskell.org/D3704
      15fcd9ad
  29. Jun 18, 2017
  30. Jun 07, 2017
    • Simon Peyton Jones's avatar
      Stop the specialiser generating loopy code · 2b74bd9d
      Simon Peyton Jones authored
      This patch fixes a bad bug in the specialiser, which showed up as
      Trac #13429.  When specialising an imported DFun, the specialiser could
      generate a recusive loop where none existed in the original program.
      
      It's all rather tricky, and I've documented it at some length in
         Note [Avoiding loops]
      
      We'd encoutered exactly this before (Trac #3591) but I had failed
      to realise that the very same thing could happen for /imported/
      DFuns.
      
      I did quite a bit of refactoring.
      
      The compiler seems to get a tiny bit faster on
         deriving/perf/T10858
      but almost all the gain had occurred before now; this
      patch just pushed it over the line.
      2b74bd9d
  31. May 26, 2017
    • Ryan Scott's avatar
      Add regression test for #13758 · c8231408
      Ryan Scott authored
      c8231408
    • Simon Peyton Jones's avatar
      Re-engineer Given flatten-skolems · 8dc6d645
      Simon Peyton Jones authored
      The big change here is to fix an outright bug in flattening of Givens,
      albeit one that is very hard to exhibit.  Suppose we have the constraint
          forall a. (a ~ F b) => ..., (forall c. ....(F b)...) ...
      
      Then
       - we'll flatten the (F) b to a fsk, say  (F b ~ fsk1)
       - we'll rewrite the (F b) inside the inner implication to 'fsk1'
       - when we leave the outer constraint we are suppose to unflatten;
         but that fsk1 will still be there
       - if we re-simplify the entire outer implication, we'll re-flatten
         the Given (F b) to, say, (F b ~ fsk2)
      Now we have two fsks standing for the same thing, and that is very
      wrong.
      
      Solution: make fsks behave more like fmvs:
       - A flatten-skolem is now a MetaTyVar, whose MetaInfo is FlatSkolTv
       - We "fill in" that meta-tyvar when leaving the implication
       - The old FlatSkol form of TcTyVarDetails is gone completely
       - We track the flatten-skolems for the current implication in
         a new field of InertSet, inert_fsks.
      
      See Note [The flattening story] in TcFlatten.
      
      In doing this I found various other things to fix:
      
      * I removed the zonkSimples from TcFlatten.unflattenWanteds; it wasn't
        needed.   But I added one in TcSimplify.floatEqualities, which does
        the zonk precisely when it is needed.
      
      * Trac #13674 showed up a case where we had
           - an insoluble Given,   e.g.  a ~ [a]
           - the same insoluble Wanted   a ~ [a]
        We don't use the Given to rewwrite the Wanted (obviously), but
        we therefore ended up reporting
            Can't deduce (a ~ [a]) from (a ~ [a])
        which is silly.
      
        Conclusion: when reporting errors, make the occurs check "win"
        See Note [Occurs check wins] in TcErrors
      8dc6d645
  32. Apr 01, 2017
  33. Mar 30, 2017
    • David Feuer's avatar
      Deriving for phantom and empty types · 69f070d8
      David Feuer authored
      Make `Functor`, `Foldable`, and `Traversable` take advantage
      of the case where the type parameter is phantom. In this case,
      
      * `fmap _ = coerce`
      * `foldMap _ _ = mempty`
      * `traverse _ x = pure (coerce x)`
      
      For the sake of consistency and especially simplicity, make other types
      with no data constructors behave the same:
      
      * `fmap _ x = case x of`
      * `foldMap _ _ = mempty`
      * `traverse _ x = pure (case x of)`
      
      Similarly, for `Generic`,
      
      * `to x = case x of`
      * `from x = case x of`
      
      Give all derived methods for types without constructors appropriate
      arities. For example,
      
      ```
          compare _ _ = error ...
      ```
      
      rather than
      
      ```
          compare = error ...
      ```
      
      Fixes #13117 and #13328
      
      Reviewers: austin, bgamari, RyanGlScott
      
      Reviewed By: RyanGlScott
      
      Subscribers: ekmett, RyanGlScott, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3374
      69f070d8
  34. Mar 10, 2017
    • Simon Peyton Jones's avatar
      Improve error messages for skolems · 48d1866e
      Simon Peyton Jones authored
      In error messages like this
          • Couldn't match type ‘c’ with ‘f0 (a -> b)’
            ‘c’ is a rigid type variable bound by
              the type signature for:
                f :: ((a -> b) -> b) -> forall c. c -> a
      
      we need to take case both to actually show that 'forall c',
      and to make sure that its name lines with the 'c' in the
      error message.
      
      This has been shaky for some time, and this commit puts it on solid
      ground.  See TcRnTypes: Note [SigSkol SkolemInfo]
      
      The main changes are
      
      * SigSkol gets an extra field that records the way in which the
        type signature was skolemised.
      
      * The type in SigSkol is now the /un/-skolemised version
      
      * pprSkolemInfo uses the info to make the tidy type line up
        nicely
      
      Lots of error message wibbles!
      48d1866e
  35. Mar 01, 2017
    • Simon Peyton Jones's avatar
      Improve pretty-printing of types · 871b63e4
      Simon Peyton Jones authored and David Feuer's avatar David Feuer committed
      When doing debug-printing it's really important that the free vars
      of a type are printed with their uniques.  The IfaceTcTyVar thing
      was a stab in that direction, but it only worked for TcTyVars, not
      TyVars.
      
      This patch does it properly, by keeping track of the free vars of the
      type when translating Type -> IfaceType, and passing that down through
      toIfaceTypeX.  Then when we find a variable, look in that set, and
      translate it to IfaceFreeTyVar if so.  (I renamed IfaceTcTyVar to
      IfaceFreeTyVar.)
      
      Fiddly but not difficult.
      
      Reviewers: austin, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D3201
      871b63e4
Loading