summaryrefslogtreecommitdiff
path: root/ghc/compiler/deSugar
diff options
context:
space:
mode:
authorsimonpj <unknown>2003-12-30 16:29:27 +0000
committersimonpj <unknown>2003-12-30 16:29:27 +0000
commitf714e6b642fd614a9971717045ae47c3d871275e (patch)
treefeaea7c0a1c45921aaf3346d642da616dee33942 /ghc/compiler/deSugar
parent9e90a28e134b8e5af3f6ec9b7300bc41324fea9c (diff)
downloadhaskell-f714e6b642fd614a9971717045ae47c3d871275e.tar.gz
[project @ 2003-12-30 16:29:17 by simonpj]
---------------------------- Re-do kind inference (again) ---------------------------- [WARNING: interface file binary representation has (as usual) changed slightly; recompile your libraries!] Inspired by the lambda-cube, for some time GHC has used type Kind = Type That is, kinds were represented by the same data type as types. But GHC also supports unboxed types and unboxed tuples, and these complicate the kind system by requiring a sub-kind relationship. Notably, an unboxed tuple is acceptable as the *result* of a function but not as an *argument*. So we have the following setup: ? / \ / \ ?? (#) / \ * # where * [LiftedTypeKind] means a lifted type # [UnliftedTypeKind] means an unlifted type (#) [UbxTupleKind] means unboxed tuple ?? [ArgTypeKind] is the lub of *,# ? [OpenTypeKind] means any type at all In particular: error :: forall a:?. String -> a (->) :: ?? -> ? -> * (\(x::t) -> ...) Here t::?? (i.e. not unboxed tuple) All this has beome rather difficult to accommodate with Kind=Type, so this commit splits the two. * Kind is a distinct type, defined in types/Kind.lhs * IfaceType.IfaceKind disappears: we just re-use Kind.Kind * TcUnify.unifyKind is a distinct unifier for kinds * TyCon no longer needs KindCon and SuperKindCon variants * TcUnify.zapExpectedType takes an expected Kind now, so that in TcPat.tcMonoPatBndr we can express that the bound variable must have an argTypeKind (??). The big change is really that kind inference is much more systematic and well behaved. In particular, a kind variable can unify only with a "simple kind", which is built from * and (->). This deals neatly with awkward questions about how we can combine sub-kinding with type inference. Lots of small consequential changes, especially to the kind-checking plumbing in TcTyClsDecls. (We played a bit fast and loose before, and now we have to be more honest, in particular about how kind inference works for type synonyms. They can have kinds like (* -> #), so This cures two long-standing SourceForge bugs * 753777 (tcfail115.hs), which used erroneously to pass, but crashed in the code generator type T a = Int -> (# Int, Int #) f :: T a -> T a f t = \x -> case t x of r -> r * 753780 (tc167.hs), which used erroneously to fail f :: (->) Int# Int# Still, the result is not entirely satisfactory. In particular * The error message from tcfail115 is pretty obscure * SourceForge bug 807249 (Instance match failure on openTypeKind) is not fixed. Alas.
Diffstat (limited to 'ghc/compiler/deSugar')
-rw-r--r--ghc/compiler/deSugar/Check.lhs2
-rw-r--r--ghc/compiler/deSugar/Desugar.lhs1
-rw-r--r--ghc/compiler/deSugar/DsGRHSs.lhs2
-rw-r--r--ghc/compiler/deSugar/DsListComp.lhs4
4 files changed, 4 insertions, 5 deletions
diff --git a/ghc/compiler/deSugar/Check.lhs b/ghc/compiler/deSugar/Check.lhs
index d1ae572578..4885b13b79 100644
--- a/ghc/compiler/deSugar/Check.lhs
+++ b/ghc/compiler/deSugar/Check.lhs
@@ -23,7 +23,7 @@ import TysWiredIn
import PrelNames ( unboundKey )
import TyCon ( tyConDataCons, tupleTyConBoxity, isTupleTyCon )
import BasicTypes ( Boxity(..) )
-import SrcLoc ( noSrcLoc, Located(..), getLoc, unLoc, noLoc )
+import SrcLoc ( noSrcLoc, Located(..), unLoc, noLoc )
import UniqSet
import Util ( takeList, splitAtList, notNull )
import Outputable
diff --git a/ghc/compiler/deSugar/Desugar.lhs b/ghc/compiler/deSugar/Desugar.lhs
index 879058e0e6..ac50a0133b 100644
--- a/ghc/compiler/deSugar/Desugar.lhs
+++ b/ghc/compiler/deSugar/Desugar.lhs
@@ -39,7 +39,6 @@ import CoreFVs ( ruleRhsFreeVars )
import ErrUtils ( doIfSet, dumpIfSet_dyn, pprBagOfWarnings,
mkWarnMsg, errorsFound, WarnMsg )
import Outputable
-import qualified Pretty
import UniqSupply ( mkSplitUniqSupply )
import SrcLoc ( Located(..), SrcSpan, unLoc )
import DATA_IOREF ( readIORef )
diff --git a/ghc/compiler/deSugar/DsGRHSs.lhs b/ghc/compiler/deSugar/DsGRHSs.lhs
index 60c67bc440..b36632699d 100644
--- a/ghc/compiler/deSugar/DsGRHSs.lhs
+++ b/ghc/compiler/deSugar/DsGRHSs.lhs
@@ -12,7 +12,7 @@ import {-# SOURCE #-} DsExpr ( dsLExpr, dsLet )
import {-# SOURCE #-} Match ( matchSinglePat )
import HsSyn ( Stmt(..), HsExpr(..), GRHSs(..), GRHS(..),
- HsMatchContext(..), Pat(..), LStmt )
+ HsMatchContext(..), Pat(..) )
import CoreSyn ( CoreExpr )
import Type ( Type )
import Var ( Id )
diff --git a/ghc/compiler/deSugar/DsListComp.lhs b/ghc/compiler/deSugar/DsListComp.lhs
index 41bb4d70ff..d6b00657d7 100644
--- a/ghc/compiler/deSugar/DsListComp.lhs
+++ b/ghc/compiler/deSugar/DsListComp.lhs
@@ -8,7 +8,7 @@ module DsListComp ( dsListComp, dsPArrComp ) where
#include "HsVersions.h"
-import {-# SOURCE #-} DsExpr ( dsExpr, dsLExpr, dsLet )
+import {-# SOURCE #-} DsExpr ( dsLExpr, dsLet )
import BasicTypes ( Boxity(..) )
import HsSyn
@@ -31,7 +31,7 @@ import Match ( matchSimply )
import PrelNames ( foldrName, buildName, replicatePName, mapPName,
filterPName, zipPName, crossPName )
import PrelInfo ( pAT_ERROR_ID )
-import SrcLoc ( noLoc, Located(..), unLoc )
+import SrcLoc ( noLoc, unLoc )
import Panic ( panic )
\end{code}