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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/0a56bcf2584ac23345cff880961efe3fd14391d8

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

commit 0a56bcf2584ac23345cff880961efe3fd14391d8
Author: [email protected] <unknown>
Date:   Mon Feb 14 02:05:31 2011 +0000

    Fixed two syntax errors

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

 compiler/vectorise/Vectorise/Exp.hs |    4 ++--
 1 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/compiler/vectorise/Vectorise/Exp.hs 
b/compiler/vectorise/Vectorise/Exp.hs
index 091a760..079e826 100644
--- a/compiler/vectorise/Vectorise/Exp.hs
+++ b/compiler/vectorise/Vectorise/Exp.hs
@@ -186,7 +186,7 @@ vectScalarLam args recFns body
         pprTrace "vectScalarLam is prim res" (ppr $ is_prim_ty res_ty) $
         pprTrace "vectScalarLam is scalar body" (ppr $ is_scalar 
(extendVarSetList scalars args) body) $
         pprTrace "vectScalarLam arg tys" (ppr $ arg_tys) $ -}
-        onlyIfV (all is_prim_ty arg_tys
+      onlyIfV (all is_prim_ty arg_tys
                && is_prim_ty res_ty
                && is_scalar (extendVarSetList scalars args) body
                && uses scalars body)
@@ -198,7 +198,7 @@ vectScalarLam args recFns body
             clo_var <- hoistExpr (fsLit "clo") clo DontInline
             lclo    <- liftPD (Var clo_var)
             {- pprTrace "  lam is scalar" (ppr "") $ -}
-              return (Var clo_var, lclo)
+            return (Var clo_var, lclo)
   where
     arg_tys = map idType args
     res_ty  = exprType body



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

Reply via email to