summaryrefslogtreecommitdiff
path: root/ghc/compiler/deSugar/Check.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2000-05-25 12:41:22 +0000
committersimonpj <unknown>2000-05-25 12:41:22 +0000
commit495ef8bd9ef30bffe50ea399b91e3ba09646b59a (patch)
treeb9ee4302d494d28a81879051d9d3e2a7693ec5e8 /ghc/compiler/deSugar/Check.lhs
parentb5c71bff716366ae888bf120776d3e163c86c60a (diff)
downloadhaskell-495ef8bd9ef30bffe50ea399b91e3ba09646b59a.tar.gz
[project @ 2000-05-25 12:41:14 by simonpj]
~~~~~~~~~~~~ Apr/May 2000 ~~~~~~~~~~~~ This is a pretty big commit! It adds stuff I've been working on over the last month or so. DO NOT MERGE IT WITH 4.07! Interface file formats have changed a little; you'll need to make clean before remaking. Simon PJ Recompilation checking ~~~~~~~~~~~~~~~~~~~~~~ Substantial improvement in recompilation checking. The version management is now entirely internal to GHC. ghc-iface.lprl is dead! The trick is to generate the new interface file in two steps: - first convert Types etc to HsTypes etc, and thereby build a new ParsedIface - then compare against the parsed (but not renamed) version of the old interface file Doing this meant adding code to convert *to* HsSyn things, and to compare HsSyn things for equality. That is the main tedious bit. Another improvement is that we now track version info for fixities and rules, which was missing before. Interface file reading ~~~~~~~~~~~~~~~~~~~~~~ Make interface files reading more robust. * If the old interface file is unreadable, don't fail. [bug fix] * If the old interface file mentions interfaces that are unreadable, don't fail. [bug fix] * When we can't find the interface file, print the directories we are looking in. [feature] Type signatures ~~~~~~~~~~~~~~~ * New flag -ddump-types to print type signatures Type pruning ~~~~~~~~~~~~ When importing data T = T1 A | T2 B | T3 C it seems excessive to import the types A, B, C as well, unless the constructors T1, T2 etc are used. A,B,C might be more types, and importing them may mean reading more interfaces, and so on. So the idea is that the renamer will just import the decl data T unless one of the constructors is used. This turns out to be quite easy to implement. The downside is that we must make sure the constructors are always available if they are really needed, so I regard this as an experimental feature. Elimininate ThinAir names ~~~~~~~~~~~~~~~~~~~~~~~~~ Eliminate ThinAir.lhs and all its works. It was always a hack, and now the desugarer carries around an environment I think we can nuke ThinAir altogether. As part of this, I had to move all the Prelude RdrName defns from PrelInfo to PrelMods --- so I renamed PrelMods as PrelNames. I also had to move the builtinRules so that they are injected by the renamer (rather than appearing out of the blue in SimplCore). This is if anything simpler. Miscellaneous ~~~~~~~~~~~~~ * Tidy up the data types involved in Rules * Eliminate RnEnv.better_provenance; use Name.hasBetterProv instead * Add Unique.hasKey :: Uniquable a => a -> Unique -> Bool It's useful in a lot of places * Fix a bug in interface file parsing for __U[!]
Diffstat (limited to 'ghc/compiler/deSugar/Check.lhs')
-rw-r--r--ghc/compiler/deSugar/Check.lhs33
1 files changed, 13 insertions, 20 deletions
diff --git a/ghc/compiler/deSugar/Check.lhs b/ghc/compiler/deSugar/Check.lhs
index 821332a481..45a1ad8fcd 100644
--- a/ghc/compiler/deSugar/Check.lhs
+++ b/ghc/compiler/deSugar/Check.lhs
@@ -22,19 +22,18 @@ import DsUtils ( EquationInfo(..),
tidyLitPat
)
import Id ( idType )
-import DataCon ( DataCon, isTupleCon, isUnboxedTupleCon, dataConArgTys,
+import DataCon ( DataCon, dataConTyCon, dataConArgTys,
dataConSourceArity, dataConFieldLabels )
import Name ( Name, mkLocalName, getOccName, isDataSymOcc, getName, mkSrcVarOcc )
import Type ( Type, splitAlgTyConApp, mkTyVarTys,
- isUnboxedType, splitTyConApp_maybe
+ splitTyConApp_maybe
)
import TysWiredIn ( nilDataCon, consDataCon,
- mkListTy,
- mkTupleTy, tupleCon,
- mkUnboxedTupleTy, unboxedTupleCon
+ mkListTy, mkTupleTy, tupleCon
)
import Unique ( unboundKey )
-import TyCon ( tyConDataCons )
+import TyCon ( tyConDataCons, tupleTyConBoxity, isTupleTyCon )
+import BasicTypes ( Boxity(..) )
import SrcLoc ( noSrcLoc )
import UniqSet
import Outputable
@@ -538,13 +537,13 @@ make_con (ConPat id _ _ _ _) (p:q:ps, constraints)
fixity = panic "Check.make_con: Guessing fixity"
make_con (ConPat id _ _ _ pats) (ps,constraints)
- | isTupleCon id = (TuplePatIn pats_con True : rest_pats, constraints)
- | isUnboxedTupleCon id = (TuplePatIn pats_con False : rest_pats, constraints)
- | otherwise = (ConPatIn name pats_con : rest_pats, constraints)
+ | isTupleTyCon tc = (TuplePatIn pats_con (tupleTyConBoxity tc) : rest_pats, constraints)
+ | otherwise = (ConPatIn name pats_con : rest_pats, constraints)
where num_args = length pats
name = getName id
pats_con = take num_args ps
rest_pats = drop num_args ps
+ tc = dataConTyCon id
make_whole_con :: DataCon -> WarningPat
@@ -591,15 +590,9 @@ simplify_pat (ListPat ty ps) = foldr (\ x -> \y -> ConPat consDataCon list_ty []
where list_ty = mkListTy ty
-simplify_pat (TuplePat ps True) = ConPat (tupleCon arity)
- (mkTupleTy arity (map outPatType ps)) [] []
- (map simplify_pat ps)
- where
- arity = length ps
-
-simplify_pat (TuplePat ps False)
- = ConPat (unboxedTupleCon arity)
- (mkUnboxedTupleTy arity (map outPatType ps)) [] []
+simplify_pat (TuplePat ps boxity)
+ = ConPat (tupleCon boxity arity)
+ (mkTupleTy boxity arity (map outPatType ps)) [] []
(map simplify_pat ps)
where
arity = length ps
@@ -641,9 +634,9 @@ simplify_pat (NPlusKPat id hslit ty hsexpr1 hsexpr2) =
simplify_pat (DictPat dicts methods) =
case num_of_d_and_ms of
- 0 -> simplify_pat (TuplePat [] True)
+ 0 -> simplify_pat (TuplePat [] Boxed)
1 -> simplify_pat (head dict_and_method_pats)
- _ -> simplify_pat (TuplePat dict_and_method_pats True)
+ _ -> simplify_pat (TuplePat dict_and_method_pats Boxed)
where
num_of_d_and_ms = length dicts + length methods
dict_and_method_pats = map VarPat (dicts ++ methods)