Haskell Program Coverage
[ghc-hetmet.git] / compiler / hsSyn / HsExpr.lhs
index c42be90..9bcd06e 100644 (file)
@@ -1,7 +1,9 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-\section[HsExpr]{Abstract Haskell syntax: expressions}
+
+HsExpr: Abstract Haskell syntax: expressions
 
 \begin{code}
 module HsExpr where
@@ -9,20 +11,18 @@ module HsExpr where
 #include "HsVersions.h"
 
 -- friends:
-import HsDecls         ( HsGroup )
-import HsPat           ( LPat )
-import HsLit           ( HsLit(..), HsOverLit )
-import HsTypes         ( LHsType, PostTcType )
-import HsImpExp                ( isOperator, pprHsVar )
-import HsBinds         ( HsLocalBinds, DictBinds, isEmptyLocalBinds,
-                         ExprCoFn, pprCoFn )
+import HsDecls
+import HsPat
+import HsLit
+import HsTypes
+import HsImpExp
+import HsBinds
 
 -- others:
-import Type            ( Type, pprParendType )
-import Var             ( TyVar, Id )
-import Name            ( Name )
-import BasicTypes      ( IPName, Boxity, tupleParens, Arity, Fixity(..) )
-import SrcLoc          ( Located(..), unLoc )
+import Var
+import Name
+import BasicTypes
+import SrcLoc
 import Outputable      
 import FastString
 \end{code}
@@ -202,6 +202,18 @@ data HsExpr id
                                        -- always has an empty stack
 
   ---------------------------------------
+  -- Hpc Support
+
+  | HsTick 
+     Int                               -- module-local tick number
+     (LHsExpr id)                      -- sub-expression
+
+  | HsBinTick
+     Int                               -- module-local tick number for True
+     Int                               -- module-local tick number for False
+     (LHsExpr id)                      -- sub-expression
+
+  ---------------------------------------
   -- The following are commands, not expressions proper
 
   | HsArrApp   -- Arrow tail, or arrow application (f -< arg)
@@ -240,7 +252,7 @@ The renamer translates them into the Right Thing.
 Everything from here on appears only in typechecker output.
 
 \begin{code}
-  |  HsCoerce  ExprCoFn        -- TRANSLATION
+  |  HsWrap    HsWrapper       -- TRANSLATION
                (HsExpr id)
 
 type PendingSplice = (Name, LHsExpr Id)        -- Typechecked splices, waiting to be 
@@ -380,7 +392,7 @@ ppr_expr (EAsPat v e) = ppr v <> char '@' <> pprParendExpr e
 ppr_expr (HsSCC lbl expr)
   = sep [ ptext SLIT("_scc_") <+> doubleQuotes (ftext lbl), pprParendExpr expr ]
 
-ppr_expr (HsCoerce co_fn e) = pprCoFn (ppr_expr e) co_fn
+ppr_expr (HsWrap co_fn e) = pprHsWrapper (ppr_expr e) co_fn
 ppr_expr (HsType id)       = ppr id
 
 ppr_expr (HsSpliceE s)       = pprSplice s
@@ -391,6 +403,16 @@ ppr_expr (HsBracketOut e ps) = ppr e $$ ptext SLIT("pending") <+> ppr ps
 ppr_expr (HsProc pat (L _ (HsCmdTop cmd _ _ _)))
   = hsep [ptext SLIT("proc"), ppr pat, ptext SLIT("->"), ppr cmd]
 
+ppr_expr (HsTick tickId exp)
+  = hcat [ptext SLIT("tick<"), ppr tickId,ptext SLIT(">("), ppr exp,ptext SLIT(")")]
+ppr_expr (HsBinTick tickIdTrue tickIdFalse exp)
+  = hcat [ptext SLIT("bintick<"), 
+         ppr tickIdTrue,
+         ptext SLIT(","),
+         ppr tickIdFalse,
+         ptext SLIT(">("), 
+         ppr exp,ptext SLIT(")")]
+
 ppr_expr (HsArrApp arrow arg _ HsFirstOrderApp True)
   = hsep [ppr_lexpr arrow, ptext SLIT("-<"), ppr_lexpr arg]
 ppr_expr (HsArrApp arrow arg _ HsFirstOrderApp False)