[GHC] #12670: Representation polymorphism validity check is too strict
GHC
ghc-devs at haskell.org
Fri Nov 18 04:35:54 UTC 2016
#12670: Representation polymorphism validity check is too strict
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: | Keywords: typeable
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
The patch that Simon was referring to in comment:4 was
eefe86d96d40697707c3ddfb9973a30a1897241f. Unfortunately this doesn't fix
the issue which described by this ticket; the typechecker still rejects
the program given in the ticket description.
Richard and I discussed this a few weeks ago and came to a solution which
looks something like this,
{{{#!patch
diff --git a/compiler/typecheck/TcPatSyn.hs
b/compiler/typecheck/TcPatSyn.hs
index 5c62121..62724c8 100644
--- a/compiler/typecheck/TcPatSyn.hs
+++ b/compiler/typecheck/TcPatSyn.hs
@@ -13,6 +13,7 @@ module TcPatSyn ( tcInferPatSynDecl, tcCheckPatSynDecl
) where
import HsSyn
+import TcHsSyn( checkForRepresentationPolymorphism )
import TcPat
import Type( mkTyVarBinders, mkEmptyTCvSubst
, tidyTyVarBinders, tidyTypes, tidyType )
@@ -312,6 +313,9 @@ tc_patsyn_finish lname dir is_infix lpat'
arg_tys = tidyTypes env2 arg_tys'
pat_ty = tidyType env2 pat_ty'
+ -- Check that the arguments aren't representationally polymorphic
+ ; mapM_ (checkForRepresentationPolymorphism empty) arg_tys
+
; traceTc "tc_patsyn_finish {" $
ppr (unLoc lname) $$ ppr (unLoc lpat') $$
ppr (univ_tvs, req_theta, req_ev_binds, req_dicts) $$
diff --git a/compiler/typecheck/TcTyClsDecls.hs
b/compiler/typecheck/TcTyClsDecls.hs
index c009bc9..9335676 100644
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -2296,6 +2296,9 @@ checkValidDataCon dflags existential_ok tc con
-- Check all argument types for validity
; checkValidType ctxt (dataConUserType con)
+ -- Check for representationally polymorphic fields
+ ; mapM_ (checkForRepresentationPolymorphism empty)
(dataConOrigArgTys con)
+
-- Extra checks for newtype data constructors
; when (isNewTyCon tc) (checkNewDataCon con)
diff --git a/compiler/typecheck/TcValidity.hs
b/compiler/typecheck/TcValidity.hs
index 6cc40a5..c9f3bda 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -487,8 +487,6 @@ check_type _ _ _ (TyVarTy _) = return ()
check_type env ctxt rank (FunTy arg_ty res_ty)
= do { check_type env ctxt arg_rank arg_ty
- ; when (representationPolymorphismForbidden ctxt) $
- checkForRepresentationPolymorphism empty arg_ty
; check_type env ctxt res_rank res_ty }
where
(arg_rank, res_rank) = funArgResRank rank
}}}
Unfortunately this still doesn't fix the Core Lint issues that inevitably
pop up when you try to use such a type.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12670#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list