Skip to content
Snippets Groups Projects
  1. Jun 27, 2018
    • Simon Peyton Jones's avatar
      Fix error recovery for pattern synonyms · 149d7912
      Simon Peyton Jones authored
      As Trac #15289 showed, we were carrying on after a type error
      in a pattern synonym, and then crashing.  This patch improves
      error handling for pattern synonyms.
      
      I also moved a bit of code from TcBinds into TcPatSyn, which
      helpfully narrows the API.
      
      (cherry picked from commit 2896082e)
    • Alan Zimmerman's avatar
      API Annotations when parsing typapp · 4cfeca02
      Alan Zimmerman authored and Ben Gamari's avatar Ben Gamari committed
      Make sure the original annotations are still accessible for a promoted
      type.
      
      Closes #15303
      
      (cherry picked from commit e53c113d)
      4cfeca02
    • Simon Peyton Jones's avatar
      Fix TcLevel manipulation in TcDerivInfer.simplifyDeriv · 145f7c66
      Simon Peyton Jones authored
      The level numbers we were getting simply didn't obey the
      invariant (ImplicInv) in TcType
         Note [TcLevel and untouchable type variables]
      
      That leads to chaos. Easy to fix.  I improved the documentation.
      
      I also added an assertion in TcSimplify that checks that
      level numbers go up by 1 as we dive inside implications, so
      that we catch the problem at source rather than than through
      its obscure consequences.
      
      That in turn showed up that TcRules was also generating
      constraints that didn't obey (ImplicInv), so I fixed that too.
      I have no idea what consequences were lurking behing that
      bug, but anyway now it's fixed.  Hooray.
      
      (cherry picked from commit 261dd83c)
      145f7c66
    • Simon Peyton Jones's avatar
      Refactor the kind-checking of tyvar binders · 7e19610c
      Simon Peyton Jones authored
      The refactoring here is driven by the ghastly mess described in
      comment:24 of Trac #1520.  The overall goal is to simplify the
      kind-checking of typev-variable binders, and in particular to narrow
      the use of the "in-scope tyvar binder" stuff,
      which is needed only for associated types: see the new
      Note [Kind-checking tyvar binders for associated types] in TcHsType.
      
      Now
      
      * The "in-scope tyvar binder" stuff is done only in
           - kcLHsQTyVars, which is used for the LHsQTyVars of a
             data/newtype, or type family declaration.
      
           - tcFamTyPats, which is used for associated family instances;
             it now calls tcImplicitQTKBndrs, which in turn usese
             newFlexiKindedQTyVar
      
      * tcExpicitTKBndrs (which is used only for function signatures,
        data con signatures, pattern synonym signatures, and expression
        type signatures) now does not go via the "in-scope tyvar binder"
        stuff at all.
      
      While I'm still not happy with all this code, the code is generally
      simpler, and I think this is a useful step forward. It does cure
      the problem too.
      
      (It's hard to trigger the problem in vanilla Haskell code, because
      the renamer would normally use different names for nested binders,
      so I can't offer a test.)
      
      (cherry picked from commit 9fc40c73)
      7e19610c
    • Simon Peyton Jones's avatar
      Instances in no-evidence implications · 61adfbe6
      Simon Peyton Jones authored
      Trac #15290 showed that it's possible that we might attempt to use a
      quantified constraint to solve an equality in a situation where we
      don't have anywhere to put the evidence bindings.  This made GHC crash.
      
      This patch stops the crash, but still rejects the pogram.  See
      Note [Instances in no-evidence implications] in TcInteract.
      
      Finding this bug revealed another lurking bug:
      
      * An infelicity in the treatment of superclasses -- we were expanding
        them locally at the leaves, rather than at their binding site; see
        (3a) in Note [The superclass story].
      
        As a consequence, TcRnTypes.superclassesMightHelp must look inside
        implications.
      
      In more detail:
      
      * Stop the crash, by making TcInteract.chooseInstance test for
        the no-evidence-bindings case.  In that case we simply don't
        use the instance.  This entailed a slight change to the type
        of chooseInstance.
      
      * Make TcSMonad.getPendingScDicts (now renamed getPendingGivenScs)
        return only Givens from the /current level/; and make
        TcRnTypes.superClassesMightHelp look inside implications.
      
      * Refactor the simpl_loop and superclass-expansion stuff in
        TcSimplify.  The logic is much easier to understand now, and
        has less duplication.
      
      (cherry picked from commit 32eb4199)
      61adfbe6
  2. Jun 25, 2018
  3. Jun 24, 2018
    • Vladislav Zavialov's avatar
      Do not imply NoStarIsType by TypeOperators/TypeInType · abd66223
      Vladislav Zavialov authored and Ben Gamari's avatar Ben Gamari committed
      Implementation of the "Embrace TypeInType" proposal was done according
      to the spec, which specified that TypeOperators must imply NoStarIsType.
      This implication was meant to prevent breakage and to be removed in 2
      releases.  However, compiling head.hackage has shown that this
      implication only magnified the breakage, so there is no reason to have
      it in the first place.
      
      To remain in compliance with the three-release policy, we add a
      workaround to define the (*) type operator even when -XStarIsType is on.
      
      Test Plan: ./validate
      
      Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4865
      abd66223
    • Alan Zimmerman's avatar
      TTG for IPBind had wrong extension name · 0c701b69
      Alan Zimmerman authored and Ben Gamari's avatar Ben Gamari committed
      The standard[1] for extension naming is to use the XC prefix for the
      internal extension points, rather than for a new constructor.
      
      This is violated for IPBind, having
      
          data IPBind id
            = IPBind
                  (XIPBind id)
                  (Either (Located HsIPName) (IdP id))
                  (LHsExpr id)
            | XCIPBind (XXIPBind id)
      
      Swap the usage of XIPBind and XCIPBind
      
      [1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow#Namingconventions
      
      Closes #15302
      
      (cherry picked from commit 5f06cf6b)
      0c701b69
  4. Jun 20, 2018
  5. Jun 19, 2018
  6. Jun 18, 2018
    • Richard Eisenberg's avatar
      Fix typo in comment only · de692fd5
      Richard Eisenberg authored
      [skip ci]
      de692fd5
    • Gabor Greif's avatar
      Typofixes in docs and comments [ci skip] · 6ac8a72f
      Gabor Greif authored
      6ac8a72f
    • Simon Peyton Jones's avatar
      Fix typechecking of kind signatures · 30b029be
      Simon Peyton Jones authored
      When typechecking a type like
         Maybe (a :: <kind-sig>)
      with a kind signature, we were using tc_lhs_kind to
      typecheck the signature.  But that's utterly wrong; we
      need the signature to be fully solid (non unresolved
      equalities) before using it.  In the case of Trac #14904
      we went on to instantiate the kind signature, when it
      still had embedded unsolved constraints.  This tripped
      the level-checking assertion when unifying a variable.
      
      The fix looks pretty easy to me: just call tcLHsKind
      instead.  I had to add KindSigCtxt to
      30b029be
    • Simon Peyton Jones's avatar
      Two small refactorings · 850ae8c5
      Simon Peyton Jones authored
      * Define Type.substTyVarBndrs, and use it
      
      * Rename substTyVarBndrCallback to substTyVarBndrUsing,
        and other analogous higher order functions.  I kept
        stumbling over the name.
      850ae8c5
    • Simon Peyton Jones's avatar
      Fix an infinite loop in niFixTCvSubst · d6216443
      Simon Peyton Jones authored
      Trac #14164 made GHC loop, a pretty serious error. It turned
      out that Unify.niFixTCvSubst was looping forever, because we
      had a substitution like
          a :-> ....(b :: (c :: d))....
          d :-> ...
      We correctly recognised that d was free in the range of the
      substitution, but then failed to apply it "deeeply enough"
      to the range of the substiuttion, so d was /still/ free in
      the range, and we kept on going.
      
      Trac #9106 was caused by a similar problem, but alas my
      fix to Trac #9106 was inadequate when the offending type
      variable is more deeply buried.  Urk.
      
      This time I think I've fixed it!  It's much more subtle
      than I though, and it took most of a long train journey
      to figure it out.  I wrote a long note to explain:
      Note [Finding the substitution fixpoint]
      d6216443
  7. Jun 17, 2018
    • Ryan Scott's avatar
      Remove accidentally checked-in T14845.stderr · 50d7b2ac
      Ryan Scott authored
      This was a stderr file for a WIP test in D4728. I ended up removing
      the test, but forgot to remove the stderr file.
      50d7b2ac
    • Vladislav Zavialov's avatar
      Add -Werror=compat · 04e9fe5c
      Vladislav Zavialov authored and Ben Gamari's avatar Ben Gamari committed
      Add a flag `-Werror=compat` to GHC which has the effect of `-Werror=x
      -Werror=y ...`, where `x, y, ...` are warnings from the `-Wcompat`
      option group.
      
      Test Plan: ./validate
      
      Reviewers: bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15278
      
      Differential Revision: https://phabricator.haskell.org/D4860
      04e9fe5c
    • Ömer Sinan Ağacan's avatar
      Use __FILE__ for Cmm assertion locations, fix #8619 · 008ea12d
      Ömer Sinan Ağacan authored
      It seems like we currently support string literals in Cmm, so we can use
      __LINE__ CPP macro in assertion macros. This improves error messages
      that previously looked like
      
          ASSERTION FAILED: file (null), line 1302
      
      (null) part now shows the actual file name.
      
      Also inline some single-use string literals in PrimOps.cmm.
      
      Reviewers: bgamari, simonmar, erikd
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4862
      008ea12d
    • Sergei Trofimovich's avatar
      UNREG: fix CmmRegOff large offset handling on W64 platforms · b8e34992
      Sergei Trofimovich authored and Ben Gamari's avatar Ben Gamari committed
      Gabor noticed C warning when building unregisterised
      64-bit compiler on GHC.Integer.Types (from integer-simple).
      
      Minimised example with a warning:
      
      ```haskell
      {-# LANGUAGE MagicHash #-}
      {-# LANGUAGE NoImplicitPrelude #-}
      {-# OPTIONS_GHC -Wall #-}
      
      module M (bug) where
      
      import GHC.Prim (Word#, minusWord#, ltWord#)
      import GHC.Types (isTrue#)
      
      -- assume Word = Word64
      bug :: Word# -> Word#
      bug x = if isTrue# (x `ltWord#` 0x8000000000000000##) then 0##
              else x `minusWord#` 0x8000000000000000##
      ```
      
      ```
      $ LANG=C x86_64-UNREG-linux-gnu-ghc -O1 -c M.hs -fforce-recomp
      /tmp/ghc30219_0/ghc_1.hc: In function 'M_bug_entry':
      
      /tmp/ghc30219_0/ghc_1.hc:20:14: error:
           warning: integer constant is so large that it is unsigned
      ```
      
      It's caused by limited handling of integer literals in CmmRegOff.
      This change switches to use standard integer literal pretty-printer.
      
      C code before the change:
      
      ```c
      FN_(M_bug_entry) {
      W_ _sAg;
      _cAr:
      _sAg = *Sp;
      switch ((W_)(_sAg < 0x8000000000000000UL)) {
      case 0x1UL: goto _cAq;
      default: goto _cAp;
      }
      _cAp:
      R1.w = _sAg+-9223372036854775808;
      // ...
      ```
      
      C code after the change:
      
      ```c
      FN_(M_bug_entry) {
      W_ _sAg;
      _cAr:
      _sAg = *Sp;
      switch ((W_)(_sAg < 0x8000000000000000UL)) {
      case 0x1UL: goto _cAq;
      default: goto _cAp;
      }
      _cAp:
      R1.w = _sAg+(-0x8000000000000000UL);
      ```
      
      URL: https://mail.haskell.org/pipermail/ghc-devs/2018-June/015875.html
      
      
      Reported-by: Gabor Greif
      Signed-off-by: default avatarSergei Trofimovich <slyfox@gentoo.org>
      
      Test Plan: test generated code on unregisterised mips64 and amd64
      
      Reviewers: simonmar, ggreif, bgamari
      
      Reviewed By: ggreif, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      Differential Revision: https://phabricator.haskell.org/D4856
      b8e34992
    • Ryan Scott's avatar
      Provide a better error message for unpromotable data constructor contexts · c6375411
      Ryan Scott authored
      Trac #14845 brought to light a corner case where a data
      constructor could not be promoted (even with `-XTypeInType`) due to
      an unpromotable constraint in its context. However, the error message
      was less than helpful, so this patch adds an additional check to
      `tcTyVar` catch unpromotable data constructors like these //before//
      they're promoted, and to give a sensible error message in such cases.
      
      Test Plan: make test TEST="T13895 T14845"
      
      Reviewers: simonpj, goldfire, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #13895, #14845
      
      Differential Revision: https://phabricator.haskell.org/D4728
      c6375411
    • Azel's avatar
      Improve documentation of Eq, Ord instances for Float and Double · 793902e6
      Azel authored
      Reviewers: sjakobi, dfeuer, bgamari, hvr
      
      Reviewed By: sjakobi, bgamari
      
      Subscribers: rwbarton, thomie, carter
      
      GHC Trac Issues: #15078
      
      Differential Revision: https://phabricator.haskell.org/D4736
      793902e6
    • sgillespie's avatar
      Improve error message when importing an unusable package · df0f148f
      sgillespie authored
      If a module cannot be found because it is ignored or from an unusable
      package, report this to the user and the reason it is unusable.
      
      Currently, GHC displays the standard "Cannot find module error". For
      example:
      
      ```
      <no location info>: error:
          Could not find module ‘Control.Monad.Random’
          Perhaps you meant
            Control.Monad.Reader (from mtl-2.2.2)
            Control.Monad.Cont (from mtl-2.2.2)
            Control.Monad.Error (from mtl-2.2.2)
      ```
      
      GHC does, however, indicate unusable/ignored packages with the -v flag:
      
      ```
      package MonadRandom-0.5.1-1421RgpXdhC8e8UI7D3emA is unusable due to
      missing dependencies:
        fail-4.9.0.0-BAHmj60kS5K7NVhhKpm9J5
      ```
      
      With this change, I took that message and added it to the output of the
      "Cannot find module" message.
      
      Reviewers: bgamari, dfeuer
      
      Reviewed By: bgamari
      
      Subscribers: Phyx, dfeuer, rwbarton, thomie, carter
      
      GHC Trac Issues: #4806
      
      Differential Revision: https://phabricator.haskell.org/D4783
      df0f148f
Loading