Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : unboxed-tuple-arguments2

http://hackage.haskell.org/trac/ghc/changeset/e9cc856d715a22894a77c755bfac0175f624d419

>---------------------------------------------------------------

commit e9cc856d715a22894a77c755bfac0175f624d419
Author: Max Bolingbroke <[email protected]>
Date:   Sat Mar 17 11:14:53 2012 +0000

    Remove the unused Type field from StgLam

>---------------------------------------------------------------

 compiler/stgSyn/CoreToStg.lhs |    6 +++---
 compiler/stgSyn/StgLint.lhs   |    2 +-
 compiler/stgSyn/StgSyn.lhs    |    4 +---
 3 files changed, 5 insertions(+), 7 deletions(-)

diff --git a/compiler/stgSyn/CoreToStg.lhs b/compiler/stgSyn/CoreToStg.lhs
index 71bdfe9..58feb66 100644
--- a/compiler/stgSyn/CoreToStg.lhs
+++ b/compiler/stgSyn/CoreToStg.lhs
@@ -277,7 +277,7 @@ mkTopStgRhs :: DynFlags -> FreeVarsInfo
             -> SRT -> StgBinderInfo -> StgExpr
             -> StgRhs
 
-mkTopStgRhs _ rhs_fvs srt binder_info (StgLam _ bndrs body)
+mkTopStgRhs _ rhs_fvs srt binder_info (StgLam bndrs body)
   = StgRhsClosure noCCS binder_info
                   (getFVs rhs_fvs)
                   ReEntrant
@@ -343,7 +343,7 @@ coreToStgExpr expr@(Lam _ _)
         fvs             = args' `minusFVBinders` body_fvs
         escs            = body_escs `delVarSetList` args'
         result_expr | null args' = body
-                    | otherwise  = StgLam (exprType expr) args' body
+                    | otherwise  = StgLam args' body
 
     return (result_expr, fvs, escs)
 
@@ -771,7 +771,7 @@ mkStgRhs :: FreeVarsInfo -> SRT -> StgBinderInfo -> StgExpr 
-> StgRhs
 
 mkStgRhs _ _ _ (StgConApp con args) = StgRhsCon noCCS con args
 
-mkStgRhs rhs_fvs srt binder_info (StgLam _ bndrs body)
+mkStgRhs rhs_fvs srt binder_info (StgLam bndrs body)
   = StgRhsClosure noCCS binder_info
                   (getFVs rhs_fvs)
                   ReEntrant
diff --git a/compiler/stgSyn/StgLint.lhs b/compiler/stgSyn/StgLint.lhs
index 9ccdfc3..8d339da 100644
--- a/compiler/stgSyn/StgLint.lhs
+++ b/compiler/stgSyn/StgLint.lhs
@@ -182,7 +182,7 @@ lintStgExpr (StgOpApp _ args res_ty) = runMaybeT $ do
     _maybe_arg_tys <- mapM (MaybeT . lintStgArg) args
     return res_ty
 
-lintStgExpr (StgLam _ bndrs _) = do
+lintStgExpr (StgLam bndrs _) = do
     addErrL (ptext (sLit "Unexpected StgLam") <+> ppr bndrs)
     return Nothing
 
diff --git a/compiler/stgSyn/StgSyn.lhs b/compiler/stgSyn/StgSyn.lhs
index defec75..5270aa9 100644
--- a/compiler/stgSyn/StgSyn.lhs
+++ b/compiler/stgSyn/StgSyn.lhs
@@ -212,8 +212,6 @@ finished it encodes (\x -> e) as (let f = \x -> e in f)
 
 \begin{code}
   | StgLam
-        Type       -- Type of whole lambda (useful when
-                   -- making a binder for it)
         [bndr]
         StgExpr    -- Body of lambda
 \end{code}
@@ -702,7 +700,7 @@ pprStgExpr (StgConApp con args)
 pprStgExpr (StgOpApp op args _)
   = hsep [ pprStgOp op, brackets (interppSP args)]
 
-pprStgExpr (StgLam _ bndrs body)
+pprStgExpr (StgLam bndrs body)
   =sep [ char '\\' <+> ppr bndrs <+> ptext (sLit "->"),
          pprStgExpr body ]
 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to