Skip to content
Snippets Groups Projects
  1. May 24, 2018
    • Ryan Scott's avatar
      Check for mismatched class methods during typechecking · 1879d9d2
      Ryan Scott authored
      Summary:
      Template Haskell provides a wormhole through which you can
      sneak methods that don't belong to a class into an instance for that
      class, bypassing the renamer's validity checks. The solution adopted
      here is to mirror the treatment for associated type family instances,
      which have an additional check in the typechecker which catch
      mismatched associated type families that were snuck through using
      Template Haskell. I've put a similar check for class methods into
      `tcMethods`.
      
      Test Plan: make test TEST=T12387
      
      Reviewers: bgamari, simonpj
      
      Reviewed By: bgamari, simonpj
      
      Subscribers: simonpj, rwbarton, thomie, carter
      
      GHC Trac Issues: #12387
      
      Differential Revision: https://phabricator.haskell.org/D4710
      1879d9d2
    • Ben Gamari's avatar
      testsuite: Bump OS X performance numbers · 49691c4f
      Ben Gamari authored
      Sadly I can't easily determine the cause of T13701's regression since the tree
      was broken.
      49691c4f
  2. May 23, 2018
    • Ben Gamari's avatar
      Disable the SRT offset optimisation on MachO platforms · bf10456e
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      Unfortunately, this optimisation is infeasible on MachO platforms (e.g.
      Darwin) due to an object format limitation. Specifically, linking fails
      with errors of the form:
      
           error: unsupported relocation with subtraction expression, symbol
           '_integerzmgmp_GHCziIntegerziType_quotInteger_closure' can not be
           undefined in a subtraction expression
      
      Apparently MachO does not permit relocations' subtraction expressions to
      refer to undefined symbols. As far as I can tell this means that it is
      essentially impossible to express an offset between symbols living in
      different compilation units. This means that we lively can't use this
      optimisation on MachO platforms.
      
      Test Plan: Validate on Darwin
      
      Reviewers: simonmar, erikd
      
      Subscribers: rwbarton, thomie, carter, angerman
      
      GHC Trac Issues: #15169
      
      Differential Revision: https://phabricator.haskell.org/D4715
      bf10456e
    • Simon Marlow's avatar
      Fix a bug in SRT generation · d424d4a4
      Simon Marlow authored
      Summary:
      I had good intentions, but they were not being followed. In particular,
      this comment:
      
      ```
      ---  - we never resolve a reference to a CAF to the contents of its SRT, since
      ---    the point of SRTs is to keep CAFs alive.
      ```
      
      was not true, because we updated the srtMap after generating the SRT
      for a CAF. Therefore it was possible for another CAF to refer to an
      earlier CAF, and the reference to the earlier CAF would be shortcutted
      to refer to its SRT instead of pointing to the CAF itself.
      
      The fix is just to not update the srtMap when generating the SRT for a
      CAF, but I also refactored the code and comments around this to be a bit
      better organised.
      
      Test Plan: Harbourmaster
      
      Reviewers: bgamari, michalt, simonpj, erikd
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15173, #15168
      
      Differential Revision: https://phabricator.haskell.org/D4721
      d424d4a4
    • Simon Peyton Jones's avatar
      Use dischargeFunEq consistently · a32c8f75
      Simon Peyton Jones authored
      Trac #15122 turned out to be interesting.
      
      * Were calling dischargeFmv in three places.
      
      * In all three cases we dealt with the Given case
        separately.
      
      * In two of the three cases the Given code was right,
        (albeit duplicated).
      
      * In the third case (in TcCanonical.canCFunEqCan), we had
           ; case flav of
               Given -> return () -- nothing more to do.
        which was utterly wrong.
      
      The solution is easy: move the Given-case handling into
      dischargeFmv (now reenamed dischargeFunEq), and delete it
      from the call sites.
      
      Result: less code, easier to understand (dischargeFunEq handles
      all three cases, not just two out of three), and Trac #15122 is fixed.
      a32c8f75
    • Simon Peyton Jones's avatar
      Don't expose strictness when sm_inline is False · d191db48
      Simon Peyton Jones authored
      This is very much a corner case, but Trac #15163 showed
      that if you have a RULE like
          forall x. f (g x) = ..x..
      
      and g = undefined, then the simplifier is likely to discard
      that 'x' argument. It is usually right to do so; but not here
      because then x is used on the right but not bound on the left.
      
      The fix is a narrow one, aimed at this rather pathalogical case.
      See Note [Do not expose strictness if sm_inline=False] in
      SimplUtils.
      d191db48
    • Simon Peyton Jones's avatar
      Add missing check to isReflCoVar_maybe · 86bba7d5
      Simon Peyton Jones authored
      isReflCoVar_maybe is called, by CoreLint, on all sorts of
      Vars (tyvars, term vars, coercion vars).  But it was silently
      assuming that it was always called on a CoVar, and as a result
      could crash fatally.  This is the immediate cause of the panic
      in Trac #15163.
      
      It's easy to fix.
      
      NB: this does not completely fix Trac #15163; more to come
      86bba7d5
    • Simon Peyton Jones's avatar
      Remove special case from TcTyVar level check · 49a832dd
      Simon Peyton Jones authored
      In TcMType.writeMetaTyVarRef we have an assertion
      check, level_check_ok, that the type being written
      to a unification variable is not deeper than the level
      of the unification varaible itself.
      
      This check used to have a special case for fmv/fsk
      flatten vars, but this commit changed fmv/fsks to have
      an ordinary level number:
      
          commit 2bbdd00c
          Author: Simon Peyton Jones <simonpj@microsoft.com>
          Date:   Fri May 18 08:43:11 2018 +0100
      
          Orient TyVar/TyVar equalities with deepest on the left
      
      So we can delete the isFlattenTyVar special case from
      the level_check_ok assertion.  Simpler, less ad hoc.
      49a832dd
    • Gabor Greif's avatar
      Typo in comments · 928f606b
      Gabor Greif authored
      928f606b
  3. May 22, 2018
  4. May 21, 2018
    • Simon Peyton Jones's avatar
      Check for type families in an instance context · af0757de
      Simon Peyton Jones authored
      This patch adds a check for type families to the instance-decl
      termination check.  See Note [Type families in instance contexts]
      and Trac #15172.
      af0757de
    • Simon Peyton Jones's avatar
      Make dischargeFmv handle Deriveds · 57858fc8
      Simon Peyton Jones authored
      A Derived CFunEqCan does not "own" its FlatMetaTv (fmv), and should not
      update it.  But one caller (canCFunEqCan) was failing to satisfy the
      precondition to dischargeFmv, which led to a crash (Trac #15170).
      
      I fixed this by making dischargeFmv handle Deriveds (to avoid forcing
      each caller to do so separately).
      
      NB: this does not completely fix the original #15170 bug, but I'll
      explain that on the ticket.  The test case for this patch is actually
      the program in comment:1.
      57858fc8
    • Simon Peyton Jones's avatar
      Remove TcType.toTcType · b7e80ae0
      Simon Peyton Jones authored
      In the olden days we insisted that only TcTyVars could appear
      in a TcType.  But now we are more accommodating; see TcType
        Note [TcTyVars and TyVars in the typechecker]
      
      This patch removes a function that converted a Type to a TcType.
      It didn't do anything useful except statisfy an invariant that
      we no longer have.  Now it's gone.
      b7e80ae0
    • Simon Peyton Jones's avatar
      Fix perf numbers for #15164 · 5f3fb712
      Simon Peyton Jones authored
      5f3fb712
    • Simon Peyton Jones's avatar
      Do better sharing in the short-cut solver · f2ce86c2
      Simon Peyton Jones authored
      Trac #15164 showed that it sometimes really matters to share
      sub-proofs when solving constraints.  Without it, we can get
      exponentialy bad behaviour.
      
      Fortunately, it's easily solved.
      Note [Shortcut try_solve_from_instance] explains.
      
      I did some minor assocaited refactoring.
      f2ce86c2
    • Austin Seipp's avatar
      ghc-pkg: recompute `abi-depends` for updated packages · 1cdc14f9
      Austin Seipp authored and Ben Gamari's avatar Ben Gamari committed
      
      See `Note [Recompute abi-depends]` for more information.
      
      Signed-off-by: default avatarAustin Seipp <aseipp@pobox.com>
      
      Test Plan: `./validate`
      
      Reviewers: bgamari, ezyang
      
      Reviewed By: bgamari
      
      Subscribers: tdammers, juhp, carter, alexbiehl, shlevy, cocreature,
      rwbarton, thomie
      
      GHC Trac Issues: #14381
      
      Differential Revision: https://phabricator.haskell.org/D4159
      1cdc14f9
    • Ben Gamari's avatar
      ghc-prim: Bump version · e1fd9461
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      unpackClosure#'s behavior and type has changed. This caused a CPP guard
      in the new ghc-heap package to fail when bootstrapping with GHC 8.4.
      
      Test Plan: Validate bootstrapping with GHC 8.4
      
      Reviewers: RyanGlScott
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4716
      e1fd9461
  5. May 20, 2018
    • patrickdoc's avatar
      Add HeapView functionality · ec22f7dd
      patrickdoc authored and Ben Gamari's avatar Ben Gamari committed
      This pulls parts of Joachim Breitner's ghc-heap-view library inside GHC.
      The bits added are the C hooks into the RTS and a basic Haskell wrapper
      to these C hooks. The main reason for these to be added to GHC proper
      is that the code needs to be kept in sync with the closure types
      defined by the RTS. It is expected that the version of HeapView shipped
      with GHC will always work with that version of GHC and that extra
      functionality can be layered on top with a library like ghc-heap-view
      distributed via Hackage.
      
      Test Plan: validate
      
      Reviewers: simonmar, hvr, nomeata, austin, Phyx, bgamari, erikd
      
      Reviewed By: bgamari
      
      Subscribers: carter, patrickdoc, tmcgilchrist, rwbarton, thomie
      
      Differential Revision: https://phabricator.haskell.org/D3055
      ec22f7dd
    • Ben Gamari's avatar
      rts: Fix compaction of SmallMutArrPtrs · 12deb9a9
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This was blatantly wrong due to copy-paste blindness:
      
       * labels were shadowed, which GHC doesn't warn about(!), resulting in
         plainly wrong behavior
       * the sharing check was omitted
       * the wrong closure layout was being used
      
      Moreover, the test wasn't being run due to its primitive dependency, so
      I didn't even notice. Sillyness.
      
      Test Plan: install `primitive`, `make test TEST=compact_small_array`
      
      Reviewers: simonmar, erikd
      
      Reviewed By: simonmar
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13857.
      
      Differential Revision: https://phabricator.haskell.org/D4702
      12deb9a9
    • Alp Mestanogullari's avatar
      Another batch of './validation --slow' tweaks · c4219d9f
      Alp Mestanogullari authored and Ben Gamari's avatar Ben Gamari committed
      This finally gets us to a green ./validate --slow on linux for a ghc
      checkout from the beginning of this week, see
      
        https://circleci.com/gh/ghc/ghc/4739
      
      This is hopefully the final (or second to final) patch to
      address #14890.
      
      Test Plan: ./validate --slow
      
      Reviewers: bgamari, hvr, simonmar
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #14890
      
      Differential Revision: https://phabricator.haskell.org/D4712
      c4219d9f
    • Ben Gamari's avatar
      base: Fix typo · 9171c7f8
      Ben Gamari authored
      9171c7f8
  6. May 19, 2018
  7. May 18, 2018
    • Simon Peyton Jones's avatar
      Do not unify representational equalities · ae292c6d
      Simon Peyton Jones authored
      This patch is an easy fix to Trac #15144, which was caused
      by accidentally unifying a representational equality in the
      unflattener.  (The main code in TcInteract was always careful
      not to do so, but I'd missed the test in the unflattener.)
      
      See Note [Do not unify representational equalities]
      in TcInteract
      ae292c6d
    • Simon Peyton Jones's avatar
      Debug tracing only · 5a7c657e
      Simon Peyton Jones authored
      5a7c657e
    • 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
    • Simon Peyton Jones's avatar
      Tiny refactor · efe40544
      Simon Peyton Jones authored
      efe40544
    • Simon Peyton Jones's avatar
      Comments only · 797a4623
      Simon Peyton Jones authored
      797a4623
    • Ryan Scott's avatar
      Add regression tests for #11515 and #12563 · 819b9cfd
      Ryan Scott authored
      Happily, both of these issues appear to have been fixed in GHC 8.2.
      Let's add regression tests for them to ensure that they stay fixed.
      819b9cfd
  8. May 17, 2018
  9. May 16, 2018
Loading