New syntax for GADT-style record declarations, and associated refactoring
[ghc-hetmet.git] / compiler / rename / RnPat.lhs
index a5d965d..ac35fe5 100644 (file)
@@ -41,6 +41,7 @@ import {-# SOURCE #-} TcSplice ( runQuasiQuotePat )
 
 import HsSyn            
 import TcRnMonad
+import TcHsSyn         ( hsOverLitName )
 import RnEnv
 import RnTypes
 import DynFlags                ( DynFlag(..) )
@@ -53,15 +54,15 @@ import ListSetOps   ( removeDups, minusList )
 import Outputable
 import SrcLoc
 import FastString
-import Literal         ( inIntRange, inCharRange )
+import Literal         ( inCharRange )
 \end{code}
 
 
-*********************************************************
-*                                                      *
+%*********************************************************
+%*                                                     *
 \subsection{Patterns}
-*                                                      *
-*********************************************************
+%*                                                     *
+%*********************************************************
 
 \begin{code}
 -- externally abstract type of name makers,
@@ -211,7 +212,7 @@ rnLPatAndThen var@(NM varf) (L loc p) cont =
                -- (e.g. in the pattern (x, x -> y) x needs to be bound in the rhs of the tuple)
                                      
          SigPatIn pat ty -> do
-             patsigs <- doptM Opt_PatternSignatures
+             patsigs <- doptM Opt_ScopedTypeVariables
              if patsigs
               then rnLPatAndThen var pat
                       (\ pat' -> do { (ty', fvs1) <- rnHsTypeFVs tvdoc ty
@@ -266,7 +267,7 @@ rnLPatAndThen var@(NM varf) (L loc p) cont =
              ; return (res, fvs_res `plusFV` fv_expr) }
 
 #ifndef GHCI
-         pat@(QuasiQuotePat _) -> pprPanic "Can't do QuasiQuotePat without GHCi" (ppr p)
+         (QuasiQuotePat _) -> pprPanic "Can't do QuasiQuotePat without GHCi" (ppr p)
 #else
          QuasiQuotePat qq -> do
              (qq', _) <- rnQuasiQuote qq
@@ -295,9 +296,9 @@ rnLPatAndThen var@(NM varf) (L loc p) cont =
               ; rnLPatsAndThen var pats $ \ patslist ->
                 lcont (TuplePat patslist boxed placeHolderType) }
 
-         TypePat name -> 
-           do { (name', fvs1) <- rnHsTypeFVs (text "In a type pattern") name
-             ; (res, fvs2) <- lcont (TypePat name')
+         TypePat ty -> 
+           do { (ty', fvs1) <- rnHsTypeFVs (text "In a type pattern") ty
+             ; (res, fvs2) <- lcont (TypePat ty')
              ; return (res, fvs1 `plusFV` fvs2) }
 
          p -> pprPanic "rnLPatAndThen" (ppr p)
@@ -446,7 +447,7 @@ badDotDot str = ptext (sLit "You cannot use `..' in record") <+> text str
 
 badPun :: Located RdrName -> SDoc
 badPun fld = vcat [ptext (sLit "Illegal use of punning for field") <+> quotes (ppr fld),
-                  ptext (sLit "Use -XRecordPuns to permit this")]
+                  ptext (sLit "Use -XNamedFieldPuns to permit this")]
 
 
 -- wrappers
@@ -506,38 +507,39 @@ rnLit (HsChar c) = checkErr (inCharRange c) (bogusCharError c)
 rnLit _ = return ()
 
 rnOverLit :: HsOverLit t -> RnM (HsOverLit Name, FreeVars)
-rnOverLit (HsIntegral i _ _) = do
-    (from_integer_name, fvs) <- lookupSyntaxName fromIntegerName
-    if inIntRange i then
-        return (HsIntegral i from_integer_name placeHolderType, fvs)
-     else let
-       extra_fvs = mkFVs [plusIntegerName, timesIntegerName]
-       -- Big integer literals are built, using + and *, 
-       -- out of small integers (DsUtils.mkIntegerLit)
-       -- [NB: plusInteger, timesInteger aren't rebindable... 
-       --      they are used to construct the argument to fromInteger, 
-       --      which is the rebindable one.]
-        in
-        return (HsIntegral i from_integer_name placeHolderType, fvs `plusFV` extra_fvs)
-
-rnOverLit (HsFractional i _ _) = do
-    (from_rat_name, fvs) <- lookupSyntaxName fromRationalName
-    let
-       extra_fvs = mkFVs [ratioDataConName, plusIntegerName, timesIntegerName]
-       -- We have to make sure that the Ratio type is imported with
-       -- its constructor, because literals of type Ratio t are
-       -- built with that constructor.
-       -- The Rational type is needed too, but that will come in
-       -- as part of the type for fromRational.
-       -- The plus/times integer operations may be needed to construct the numerator
-       -- and denominator (see DsUtils.mkIntegerLit)
-    return (HsFractional i from_rat_name placeHolderType, fvs `plusFV` extra_fvs)
-
-rnOverLit (HsIsString s _ _) = do
-    (from_string_name, fvs) <- lookupSyntaxName fromStringName
-    return (HsIsString s from_string_name placeHolderType, fvs)
+rnOverLit lit@(OverLit {ol_val=val})
+  = do { let std_name = hsOverLitName val
+       ; (from_thing_name, fvs) <- lookupSyntaxName std_name
+       ; let rebindable = case from_thing_name of
+                               HsVar v -> v /= std_name
+                               _       -> panic "rnOverLit"
+       ; return (lit { ol_witness = from_thing_name
+                     , ol_rebindable = rebindable }, fvs) }
 \end{code}
 
+----------------------------------------------------------------
+-- Old code returned extra free vars need in desugarer
+-- but that is no longer necessary, I believe
+--     if inIntRange i then
+--        return (HsIntegral i from_integer_name placeHolderType, fvs)
+--     else let
+--     extra_fvs = mkFVs [plusIntegerName, timesIntegerName]
+-- Big integer literals are built, using + and *, 
+-- out of small integers (DsUtils.mkIntegerLit)
+-- [NB: plusInteger, timesInteger aren't rebindable... 
+--     they are used to construct the argument to fromInteger, 
+--     which is the rebindable one.]
+
+-- (HsFractional i _ _) = do
+--     extra_fvs = mkFVs [ratioDataConName, plusIntegerName, timesIntegerName]
+-- We have to make sure that the Ratio type is imported with
+-- its constructor, because literals of type Ratio t are
+-- built with that constructor.
+-- The Rational type is needed too, but that will come in
+-- as part of the type for fromRational.
+-- The plus/times integer operations may be needed to construct the numerator
+-- and denominator (see DsUtils.mkIntegerLit)
+
 %************************************************************************
 %*                                                                     *
 \subsubsection{Quasiquotation}
@@ -578,7 +580,7 @@ checkTupSize tup_size
 patSigErr :: Outputable a => a -> SDoc
 patSigErr ty
   =  (ptext (sLit "Illegal signature in pattern:") <+> ppr ty)
-       $$ nest 4 (ptext (sLit "Use -XPatternSignatures to permit it"))
+       $$ nest 4 (ptext (sLit "Use -XScopedTypeVariables to permit it"))
 
 dupFieldErr :: String -> RdrName -> SDoc
 dupFieldErr str dup