Minor refactoring
[ghc-hetmet.git] / compiler / hsSyn / HsPat.lhs
index e87a6a2..af921de 100644 (file)
@@ -25,7 +25,7 @@ module HsPat (
 
        isBangHsBind, hsPatNeedsParens,
        patsAreAllCons, isConPat, isSigPat, isWildPat,
-       patsAreAllLits, isLitPat, isIrrefutableHsPat, hasViewPat
+       patsAreAllLits, isLitPat, isIrrefutableHsPat
     ) where
 
 import {-# SOURCE #-} HsExpr           (SyntaxExpr, LHsExpr, pprLExpr)
@@ -177,13 +177,21 @@ data HsRecFields id arg   -- A bunch of record fields
                                --      { x = 3, y = True }
        -- Used for both expressions and patterns
   = HsRecFields { rec_flds   :: [HsRecField id arg],
-                 rec_dotdot :: Maybe Int }
-       -- Nothing => the normal case
-       -- Just n  => the group uses ".." notation, 
-       --              and the first n elts of rec_flds
-       --              were the user-written ones
-       -- (In the latter case, the remaining elts of
-       --  rec_flds are the non-user-written ones)
+                 rec_dotdot :: Maybe Int }  -- Note [DotDot fields]
+
+-- Note [DotDot fields]
+-- ~~~~~~~~~~~~~~~~~~~~
+-- The rec_dotdot field means this:
+--   Nothing => the normal case
+--   Just n  => the group uses ".." notation, 
+--
+-- In the latter case: 
+--
+--   *before* renamer: rec_flds are exactly the n user-written fields
+--
+--   *after* renamer:  rec_flds includes *all* fields, with 
+--                    the first 'n' being the user-written ones
+--                    and the remainder being 'filled in' implicitly
 
 data HsRecField id arg = HsRecField {
        hsRecFieldId  :: Located id,
@@ -196,9 +204,12 @@ data HsRecField id arg = HsRecField {
 -- If you write T { x, y = v+1 }, the HsRecFields will be
 --     HsRecField x x True ...
 --     HsRecField y (v+1) False ...
--- That is, for "punned" field x is immediately expanded to x=x
--- but with a punning flag so we can detect it later
+-- That is, for "punned" field x is expanded (in the renamer) 
+-- to x=x; but with a punning flag so we can detect it later
 -- (e.g. when pretty printing)
+--
+-- If the original field was qualified, we un-qualify it, thus
+--    T { A.x } means T { A.x = x }
 
 hsRecFields :: HsRecFields id arg -> [id]
 hsRecFields rbinds = map (unLoc . hsRecFieldId) (rec_flds rbinds)
@@ -299,7 +310,7 @@ instance (OutputableBndr id, Outputable arg)
       => Outputable (HsRecField id arg) where
   ppr (HsRecField { hsRecFieldId = f, hsRecFieldArg = arg, 
                    hsRecPun = pun })
-    = ppr f <+> (if pun then empty else equals <+> ppr arg)
+    = ppr f <+> (ppUnless pun $ equals <+> ppr arg)
 
 -- add parallel array brackets around a document
 --
@@ -369,34 +380,6 @@ patterns are treated specially, of course.
 
 The 1.3 report defines what ``irrefutable'' and ``failure-free'' patterns are.
 \begin{code}
-hasViewPat :: LPat id -> Bool
-hasViewPat (L _ p) = go p where
-  go (WildPat _)             = False
-  go (VarPat _)              = False
-  go (VarPatOut _ _)         = False
-  go (LazyPat p)             = hasViewPat p
-  go (AsPat _ p)             = hasViewPat p
-  go (ParPat p)              = hasViewPat p
-  go (BangPat p)             = hasViewPat p
-  go (ListPat p _)           = any hasViewPat p
-  go (TuplePat p _ _)        = any hasViewPat p
-  go (PArrPat p _)           = any hasViewPat p
-  go (ConPatIn _ p)          = go' p
-  go (ConPatOut _ _ _ _ p _) = go' p
-  go (ViewPat _ _ _)         = True
-  go (QuasiQuotePat _)       = False
-  go (LitPat _)              = False
-  go (NPat _ _ _)            = False
-  go (NPlusKPat _ _ _ _)     = False
-  go (TypePat _)             = False
-  go (SigPatIn p _)          = hasViewPat p
-  go (SigPatOut p _)         = hasViewPat p
-  go (CoPat _ _ _)           = False
-  go' p = case p of
-    PrefixCon ps              -> any hasViewPat ps
-    RecCon (HsRecFields fs _) -> any (hasViewPat . hsRecFieldArg) fs
-    InfixCon p1 p2            -> hasViewPat p1 || hasViewPat p2
-
 isWildPat :: Pat id -> Bool
 isWildPat (WildPat _) = True
 isWildPat _           = False