[project @ 2000-12-12 14:35:08 by simonmar]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsExpr.lhs
index 829f9ab..4ba2e2a 100644 (file)
@@ -19,7 +19,7 @@ import HsTypes                ( HsType )
 -- others:
 import Name            ( Name, isLexSym ) 
 import Outputable      
-import PprType         ( pprType, pprParendType )
+import PprType         ( pprParendType )
 import Type            ( Type )
 import Var             ( TyVar )
 import DataCon         ( DataCon )
@@ -153,6 +153,7 @@ data HsExpr id pat
 
   | HsSCC      FAST_STRING     -- "set cost centre" (_scc_) annotation
                (HsExpr id pat) -- expr whose cost is to be measured
+
 \end{code}
 
 These constructors only appear temporarily in the parser.
@@ -165,6 +166,8 @@ The renamer translates them into the Right Thing.
                (HsExpr id pat)
 
   | ELazyPat   (HsExpr id pat) -- ~ pattern
+
+  | HsType      (HsType id)     -- Explicit type argument; e.g  f {| Int |} x y
 \end{code}
 
 Everything from here on appears only in typechecker output.
@@ -302,8 +305,7 @@ ppr_expr (HsDoOut do_or_list_comp stmts _ _ _ _ _) = pprDo do_or_list_comp stmts
 ppr_expr (ExplicitList exprs)
   = brackets (fsep (punctuate comma (map ppr_expr exprs)))
 ppr_expr (ExplicitListOut ty exprs)
-  = hcat [ brackets (fsep (punctuate comma (map ppr_expr exprs))),
-          ifNotPprForUser ((<>) space (parens (pprType ty))) ]
+  = brackets (fsep (punctuate comma (map ppr_expr exprs)))
 
 ppr_expr (ExplicitTuple exprs boxity)
   = tupleParens boxity (sep (punctuate comma (map ppr_expr exprs)))
@@ -362,6 +364,8 @@ ppr_expr (DictApp expr dnames)
   = hang (ppr_expr expr)
         4 (brackets (interpp'SP dnames))
 
+ppr_expr (HsType id) = ppr id
+    
 \end{code}
 
 Parenthesize unless very simple:
@@ -389,7 +393,7 @@ pprParendExpr expr
 
 \begin{code}
 isOperator :: Outputable a => a -> Bool
-isOperator v = isLexSym (_PK_ (showSDoc (ppr v)))
+isOperator v = isLexSym (_PK_ (showSDocUnqual (ppr v)))
        -- We use (showSDoc (ppr v)), rather than isSymOcc (getOccName v) simply so
        -- that we don't need NamedThing in the context of all these functions.
        -- Gruesome, but simple.
@@ -446,7 +450,9 @@ pprDo ListComp stmts
 
 \begin{code}
 data Stmt id pat
-  = BindStmt   pat
+  = ParStmt    [[Stmt id pat]]         -- List comp only: parallel set of quals
+  | ParStmtOut [([id], [Stmt id pat])] -- PLC after renaming
+  | BindStmt   pat
                (HsExpr id pat)
                SrcLoc
 
@@ -470,6 +476,10 @@ instance (Outputable id, Outputable pat) =>
                Outputable (Stmt id pat) where
     ppr stmt = pprStmt stmt
 
+pprStmt (ParStmt stmtss)
+ = hsep (map (\stmts -> ptext SLIT("| ") <> ppr stmts) stmtss)
+pprStmt (ParStmtOut stmtss)
+ = hsep (map (\stmts -> ptext SLIT("| ") <> ppr stmts) stmtss)
 pprStmt (BindStmt pat expr _)
  = hsep [ppr pat, ptext SLIT("<-"), ppr expr]
 pprStmt (LetStmt binds)