[GHC] #1311: newtypes of unboxed types disallowed - documentation bug and/or feature request
GHC
ghc-devs at haskell.org
Tue Dec 22 21:35:53 UTC 2015
#1311: newtypes of unboxed types disallowed - documentation bug and/or feature
request
-------------------------------------+-------------------------------------
Reporter: Isaac Dupree | Owner: osa1
Type: feature request | Status: new
Priority: low | Milestone: ⊥
Component: Compiler | Version: 7.7
Resolution: | Keywords:
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 osa1):
So I think this turned out to be more complicated than we first thought
(as usual). Richard, could you tell me if I'm going in the right
direction? Here's what I did so far:
{{{#!diff
--- a/compiler/typecheck/TcTyClsDecls.hs
+++ b/compiler/typecheck/TcTyClsDecls.hs
@@ -1490,7 +1490,7 @@ tcGadtSigType doc name ty@(HsIB { hsib_vars = vars
})
tcHsTyVarBndrs gtvs $ \ _ ->
do { ctxt <- tcHsContext cxt
; btys <- tcConArgs DataType hs_details
- ; ty' <- tcHsLiftedType res_ty
+ ; ty' <- tcHsOpenType res_ty
; field_lbls <- lookupConstructorFields name
; let (arg_tys, stricts) = unzip btys
bound_vars = allBoundVariabless ctxt `unionVarSet`
}}}
Second change:
{{{#!diff
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -1862,8 +1862,7 @@ tcDataKindSig :: Kind -> TcM [TyVar]
-- We use it also to make up argument type variables for for data
instances.
-- Never emits constraints.
tcDataKindSig kind
- = do { checkTc (isLiftedTypeKind res_kind) (badKindSig kind)
- ; span <- getSrcSpanM
+ = do { span <- getSrcSpanM
; us <- newUniqueSupply
; rdr_env <- getLocalRdrEnv
; let uniqs = uniqsFromSupply us
@@ -1880,11 +1879,6 @@ tcDataKindSig kind
mk_tv loc uniq occ kind
= mkTyVar (mkInternalName uniq occ loc) kind
-badKindSig :: Kind -> SDoc
-badKindSig kind
- = hang (ptext (sLit "Kind signature on data type declaration has non-*
return kind"))
- 2 (ppr kind)
-
{-
Note [Avoid name clashes for associated data types]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
}}}
Those are all for accepting this program:
{{{#!haskell
{-# LANGUAGE MagicHash, KindSignatures, GADTs #-}
module Main where
import GHC.Types
import GHC.Prim
import GHC.Exts
newtype Blah :: TYPE 'Unlifted where
Blah :: Int# -> Blah
main = return ()
}}}
For now I'm not trying to infer unlifted types, I'm trying to make cases
with explicit kind signatures working.
With these changes, GHC is failing with this panic:
{{{
ghc-stage1: panic! (the 'impossible' happened)
(GHC version 7.11.20151222 for x86_64-unknown-linux):
ASSERT failed! file compiler/typecheck/TcTyClsDecls.hs, line 1630
}}}
This is because we have some code that assume result types of ... I think
GADTs? ... are lifted. (I think newtypes defined this way are type checked
using GADT type checker?)
Am I doing this right? How should I proceed after this point? I feel like
I shouldn't lift these restrictions and instead I need some special cases
for newtypes. Am I right?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/1311#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list