[commit: ghc] wip/type-app: Allow @_ to be used without fuss (2d2d3a9)
git at git.haskell.org
git at git.haskell.org
Fri Aug 7 12:08:07 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/type-app
Link : http://ghc.haskell.org/trac/ghc/changeset/2d2d3a906d4c67018579f583d2e174aca8eab21a/ghc
>---------------------------------------------------------------
commit 2d2d3a906d4c67018579f583d2e174aca8eab21a
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Thu Aug 6 11:39:57 2015 -0400
Allow @_ to be used without fuss
>---------------------------------------------------------------
2d2d3a906d4c67018579f583d2e174aca8eab21a
compiler/typecheck/TcHsType.hs | 7 +++----
testsuite/tests/typecheck/should_compile/Vta1.hs | 3 +--
2 files changed, 4 insertions(+), 6 deletions(-)
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 6dea9e3..1b181af 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -237,12 +237,11 @@ tcHsTypeApp (hs_ty, wcs) kind
= do { nwc_tvs <- mapM newWildcardVarMetaKind wcs
; tcExtendTyVarEnv nwc_tvs $
do { ty <- tcCheckLHsType hs_ty kind
-
- ; addErrCtxt (pprSigCtxt TypeAppCtxt empty (ppr hs_ty)) $
- emitWildcardHoleConstraints (zip wcs nwc_tvs)
-
; checkValidType TypeAppCtxt ty
; return ty } }
+ -- NB: we don't call emitWildcardHoleConstraints here, because
+ -- we want any holes in visible type applications to be used
+ -- without fuss. No errors, warnings, extensions, etc.
{-
These functions are used during knot-tying in
diff --git a/testsuite/tests/typecheck/should_compile/Vta1.hs b/testsuite/tests/typecheck/should_compile/Vta1.hs
index cb70916..c3ba43d 100644
--- a/testsuite/tests/typecheck/should_compile/Vta1.hs
+++ b/testsuite/tests/typecheck/should_compile/Vta1.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE TypeApplications, ScopedTypeVariables, PolyKinds,
- TypeFamilies, RankNTypes, PartialTypeSignatures,
+ TypeFamilies, RankNTypes,
FlexibleContexts #-}
-{-# OPTIONS_GHC -fno-warn-partial-type-signatures #-}
-- tests about visible type application
module Vta1 where
More information about the ghc-commits
mailing list