summaryrefslogtreecommitdiff
path: root/ghc/compiler/deSugar/Check.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2000-09-22 15:56:16 +0000
committersimonpj <unknown>2000-09-22 15:56:16 +0000
commit1bba522f5ec82c43abd2ba4e84127b9c915dd020 (patch)
tree1a912e2e7f74da8abcca375d2559cb985af17544 /ghc/compiler/deSugar/Check.lhs
parenta8e1967fbb90eae923042827cef98a98d66d18e7 (diff)
downloadhaskell-1bba522f5ec82c43abd2ba4e84127b9c915dd020.tar.gz
[project @ 2000-09-22 15:56:12 by simonpj]
-------------------------------------------------- Tidying up HsLit, and making it possible to define your own numeric library Simon PJ 22 Sept 00 -------------------------------------------------- ** NOTE: I did these changes on the aeroplane. They should compile, and the Prelude still compiles OK, but it's entirely possible that I've broken something The original reason for this many-file but rather shallow commit is that it's impossible in Haskell to write your own numeric library. Why? Because when you say '1' you get (Prelude.fromInteger 1), regardless of what you hide from the Prelude, or import from other libraries you have written. So the idea is to extend the -fno-implicit-prelude flag so that in addition to no importing the Prelude, you can rebind fromInteger -- Applied to literal constants fromRational -- Ditto negate -- Invoked by the syntax (-x) the (-) used when desugaring n+k patterns After toying with other designs, I eventually settled on a simple, crude one: rather than adding a new flag, I just extended the semantics of -fno-implicit-prelude so that uses of fromInteger, fromRational and negate are all bound to "whatever is in scope" rather than "the fixed Prelude functions". So if you say {-# OPTIONS -fno-implicit-prelude #-} module M where import MyPrelude( fromInteger ) x = 3 the literal 3 will use whatever (unqualified) "fromInteger" is in scope, in this case the one gotten from MyPrelude. On the way, though, I studied how HsLit worked, and did a substantial tidy up, deleting quite a lot of code along the way. In particular. * HsBasic.lhs is renamed HsLit.lhs. It defines the HsLit type. * There are now two HsLit types, both defined in HsLit. HsLit for non-overloaded literals (like 'x') HsOverLit for overloaded literals (like 1 and 2.3) * HsOverLit completely replaces Inst.OverloadedLit, which disappears. An HsExpr can now be an HsOverLit as well as an HsLit. * HsOverLit carries the Name of the fromInteger/fromRational operation, so that the renamer can help with looking up the unqualified name when -fno-implicit-prelude is on. Ditto the HsExpr for negation. It's all very tidy now. * RdrHsSyn contains the stuff that handles -fno-implicit-prelude (see esp RdrHsSyn.prelQual). RdrHsSyn also contains all the "smart constructors" used by the parser when building HsSyn. See for example RdrHsSyn.mkNegApp (previously the renamer (!) did the business of turning (- 3#) into -3#). * I tidied up the handling of "special ids" in the parser. There's much less duplication now. * Move Sven's Horner stuff to the desugarer, where it belongs. There's now a nice function DsUtils.mkIntegerLit which brings together related code from no fewer than three separate places into one single place. Nice! * A nice tidy-up in MatchLit.partitionEqnsByLit became possible. * Desugaring of HsLits is now much tidier (DsExpr.dsLit) * Some stuff to do with RdrNames is moved from ParseUtil.lhs to RdrHsSyn.lhs, which is where it really belongs. * I also removed many unnecessary imports from modules quite a bit of dead code in divers places
Diffstat (limited to 'ghc/compiler/deSugar/Check.lhs')
-rw-r--r--ghc/compiler/deSugar/Check.lhs23
1 files changed, 5 insertions, 18 deletions
diff --git a/ghc/compiler/deSugar/Check.lhs b/ghc/compiler/deSugar/Check.lhs
index 45a1ad8fcd..c9c978158b 100644
--- a/ghc/compiler/deSugar/Check.lhs
+++ b/ghc/compiler/deSugar/Check.lhs
@@ -13,21 +13,14 @@ module Check ( check , ExhaustivePat ) where
import HsSyn
import TcHsSyn ( TypecheckedPat )
import DsHsSyn ( outPatType )
-import CoreSyn
-
-import DsUtils ( EquationInfo(..),
- MatchResult(..),
- EqnSet,
- CanItFail(..),
+import DsUtils ( EquationInfo(..), MatchResult(..), EqnSet, CanItFail(..),
tidyLitPat
)
import Id ( idType )
import DataCon ( DataCon, dataConTyCon, dataConArgTys,
dataConSourceArity, dataConFieldLabels )
import Name ( Name, mkLocalName, getOccName, isDataSymOcc, getName, mkSrcVarOcc )
-import Type ( Type, splitAlgTyConApp, mkTyVarTys,
- splitTyConApp_maybe
- )
+import Type ( splitAlgTyConApp, mkTyVarTys, splitTyConApp_maybe )
import TysWiredIn ( nilDataCon, consDataCon,
mkListTy, mkTupleTy, tupleCon
)
@@ -151,13 +144,7 @@ untidy b (ConOpPatIn pat1 name fixity pat2) =
untidy _ (ListPatIn pats) = ListPatIn (map untidy_no_pars pats)
untidy _ (TuplePatIn pats boxed) = TuplePatIn (map untidy_no_pars pats) boxed
-untidy _ (SigPatIn pat ty) = panic "Check.untidy: SigPatIn"
-untidy _ (LazyPatIn pat) = panic "Check.untidy: LazyPatIn"
-untidy _ (AsPatIn name pat) = panic "Check.untidy: AsPatIn"
-untidy _ (NPlusKPatIn name lit) = panic "Check.untidy: NPlusKPatIn"
-untidy _ (NegPatIn ipat) = panic "Check.untidy: NegPatIn"
-untidy _ (ParPatIn pat) = panic "Check.untidy: ParPatIn"
-untidy _ (RecPatIn name fields) = panic "Check.untidy: RecPatIn"
+untidy _ pat = pprPanic "Check.untidy: SigPatIn" (ppr pat)
pars :: NeedPars -> WarningPat -> WarningPat
pars True p = ParPatIn p
@@ -625,8 +612,8 @@ simplify_pat (RecPat dc ty ex_tvs dicts idps)
| nm == n = (nm,p):xs
| otherwise = x : insertNm nm p xs
-simplify_pat pat@(LitPat lit lit_ty) = tidyLitPat lit lit_ty pat
-simplify_pat pat@(NPat lit lit_ty hsexpr) = tidyLitPat lit lit_ty pat
+simplify_pat pat@(LitPat lit lit_ty) = tidyLitPat lit pat
+simplify_pat pat@(NPat lit lit_ty hsexpr) = tidyLitPat lit pat
simplify_pat (NPlusKPat id hslit ty hsexpr1 hsexpr2) =
WildPat ty