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

On branch  : simd

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

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

commit e83973baad54a9392f3a7573d058f20e91865212
Merge: 599f75f... df43fcd...
Author: Geoffrey Mainland <[email protected]>
Date:   Sun Nov 27 21:08:14 2011 +0000

    Merge branch 'master', remote-tracking branch 'origin' into simd
    
    Conflicts:
        compiler/llvmGen/LlvmCodeGen/CodeGen.hs

 aclocal.m4                                         |   93 +-
 compiler/basicTypes/DataCon.lhs                    |    9 +-
 compiler/basicTypes/MkId.lhs                       |   10 +-
 compiler/basicTypes/Module.lhs                     |  111 +-
 compiler/basicTypes/OccName.lhs                    |   28 +-
 compiler/cmm/PprC.hs                               |  410 +++---
 compiler/codeGen/CgCase.lhs                        |   18 +-
 compiler/codeGen/CgForeignCall.hs                  |  191 ++--
 compiler/codeGen/StgCmmForeign.hs                  |  167 +-
 compiler/coreSyn/CoreFVs.lhs                       |    2 +-
 compiler/coreSyn/CoreLint.lhs                      |   84 +-
 compiler/coreSyn/CoreSubst.lhs                     |   17 +-
 compiler/coreSyn/CoreSyn.lhs                       |    8 +-
 compiler/coreSyn/CoreUtils.lhs                     |   45 +-
 compiler/coreSyn/PprCore.lhs                       |    3 +-
 compiler/deSugar/Desugar.lhs                       |   20 +-
 compiler/deSugar/DsBinds.lhs                       |   89 +-
 compiler/deSugar/DsCCall.lhs                       |    4 +-
 compiler/deSugar/DsForeign.lhs                     |   17 +-
 compiler/deSugar/DsMeta.hs                         |    8 +-
 compiler/deSugar/DsMonad.lhs                       |   28 +-
 compiler/deSugar/DsUtils.lhs                       |    2 +-
 compiler/ghc.cabal.in                              |    8 +-
 compiler/ghc.mk                                    |   31 +-
 compiler/ghci/ByteCodeItbls.lhs                    |  131 +-
 compiler/ghci/ObjLink.lhs                          |   15 +-
 compiler/hsSyn/Convert.lhs                         |    2 +-
 compiler/hsSyn/HsBinds.lhs                         |   17 +-
 compiler/hsSyn/HsDecls.lhs                         |   26 +-
 compiler/hsSyn/HsExpr.lhs                          |   19 +-
 compiler/hsSyn/HsTypes.lhs                         |   28 +-
 compiler/hsSyn/HsUtils.lhs                         |   17 +-
 compiler/iface/BuildTyCl.lhs                       |    6 +-
 compiler/iface/FlagChecker.hs                      |    4 +-
 compiler/iface/LoadIface.lhs                       |    3 +-
 compiler/iface/MkIface.lhs                         |   20 +-
 compiler/iface/TcIface.lhs                         |  101 +-
 compiler/llvmGen/LlvmCodeGen.hs                    |    1 +
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs            |   74 +-
 compiler/llvmGen/LlvmMangler.hs                    |  115 +--
 compiler/main/DriverPhases.hs                      |  104 +-
 compiler/main/DriverPipeline.hs                    |  121 +-
 compiler/main/DynFlags.hs                          |   97 +-
 compiler/main/ErrUtils.lhs                         |  168 +-
 compiler/main/ErrUtils.lhs-boot                    |    1 +
 compiler/main/GHC.hs                               |   11 +-
 compiler/main/HscMain.hs                           |  128 ++-
 compiler/main/HscTypes.lhs                         |   28 +
 compiler/main/StaticFlags.hs                       |    4 +-
 compiler/main/SysTools.lhs                         |   41 +-
 compiler/nativeGen/AsmCodeGen.lhs                  |    6 -
 compiler/nativeGen/PIC.hs                          |    5 -
 compiler/nativeGen/PPC/CodeGen.hs                  |    8 +-
 compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs |   12 -
 compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs     |    3 -
 compiler/nativeGen/RegAlloc/Linear/Main.hs         |    3 -
 compiler/nativeGen/SPARC/CodeGen/CCall.hs          |  313 ++--
 compiler/nativeGen/TargetReg.hs                    |   15 -
 compiler/nativeGen/X86/CodeGen.hs                  |   55 +-
 compiler/parser/Lexer.x                            |   20 +-
 compiler/parser/Parser.y.pp                        |   44 +-
 compiler/parser/RdrHsSyn.lhs                       |    3 +-
 compiler/prelude/ForeignCall.lhs                   |    6 +-
 compiler/prelude/PrelNames.lhs                     |   12 +-
 compiler/prelude/TysPrim.lhs                       |   20 +-
 compiler/prelude/primops.txt.pp                    |   25 +-
 compiler/rename/RnExpr.lhs                         |   11 +-
 compiler/rename/RnSource.lhs                       |  106 +-
 compiler/simplCore/CoreMonad.lhs                   |    9 +-
 compiler/simplCore/OccurAnal.lhs                   |    4 +-
 compiler/simplCore/SetLevels.lhs                   |    4 +-
 compiler/simplCore/SimplUtils.lhs                  |    2 +-
 compiler/simplCore/Simplify.lhs                    |   25 +-
 compiler/specialise/Specialise.lhs                 |    2 +-
 compiler/typecheck/Inst.lhs                        |   71 +-
 compiler/typecheck/TcBinds.lhs                     |   12 +-
 compiler/typecheck/TcCanonical.lhs                 | 1362 +++++++++++------
 compiler/typecheck/TcErrors.lhs                    |   48 +-
 compiler/typecheck/TcForeign.lhs                   |   22 +-
 compiler/typecheck/TcGenGenerics.lhs               |    5 +-
 compiler/typecheck/TcHsSyn.lhs                     |   22 +-
 compiler/typecheck/TcHsType.lhs                    |  447 +++---
 compiler/typecheck/TcInstDcls.lhs                  |    1 -
 compiler/typecheck/TcInteract.lhs                  | 1666 +++++++-------------
 compiler/typecheck/TcMType.lhs                     |   87 +-
 compiler/typecheck/TcMatches.lhs                   |    2 -
 compiler/typecheck/TcRnDriver.lhs                  |   51 +-
 compiler/typecheck/TcRnMonad.lhs                   |   15 +
 compiler/typecheck/TcRnTypes.lhs                   |  196 ++-
 compiler/typecheck/TcSMonad.lhs                    | 1211 ++++++++++----
 compiler/typecheck/TcSimplify.lhs                  |  528 ++++---
 compiler/typecheck/TcSplice.lhs                    |    2 +-
 compiler/typecheck/TcTyClsDecls.lhs                |    4 +-
 compiler/typecheck/TcType.lhs                      |   41 +-
 compiler/typecheck/TcUnify.lhs                     |   14 +-
 compiler/types/Coercion.lhs                        |  120 +-
 compiler/types/FunDeps.lhs                         |   10 +-
 compiler/types/Kind.lhs                            |   37 +-
 compiler/types/Type.lhs                            |   75 +-
 compiler/types/TypeRep.lhs                         |   25 +-
 compiler/utils/Bag.lhs                             |    1 +
 compiler/utils/Outputable.lhs                      |  296 ++--
 compiler/utils/Platform.hs                         |    8 +-
 compiler/vectorise/Vectorise.hs                    |   33 +-
 compiler/vectorise/Vectorise/Builtins.hs           |    6 +-
 compiler/vectorise/Vectorise/Builtins/Base.hs      |   37 +-
 .../vectorise/Vectorise/Builtins/Initialise.hs     |  106 +-
 compiler/vectorise/Vectorise/Env.hs                |   30 +-
 compiler/vectorise/Vectorise/Exp.hs                |  325 +++--
 .../vectorise/Vectorise/Generic/Description.hs     |  291 ++++
 .../Vectorise/{Type => Generic}/PADict.hs          |   55 +-
 compiler/vectorise/Vectorise/Generic/PAMethods.hs  |  595 +++++++
 compiler/vectorise/Vectorise/Generic/PData.hs      |  151 ++
 compiler/vectorise/Vectorise/Monad.hs              |   55 +-
 compiler/vectorise/Vectorise/Monad/Base.hs         |    4 +
 compiler/vectorise/Vectorise/Monad/Global.hs       |   47 +-
 compiler/vectorise/Vectorise/Type/Env.hs           |  231 ++-
 compiler/vectorise/Vectorise/Type/PData.hs         |   87 -
 compiler/vectorise/Vectorise/Type/PRepr.hs         |  369 -----
 compiler/vectorise/Vectorise/Type/Repr.hs          |  107 --
 compiler/vectorise/Vectorise/Type/TyConDecl.hs     |    6 -
 compiler/vectorise/Vectorise/Type/Type.hs          |   80 +-
 compiler/vectorise/Vectorise/Utils.hs              |   19 +-
 compiler/vectorise/Vectorise/Utils/Base.hs         |  253 ++-
 compiler/vectorise/Vectorise/Utils/Closure.hs      |  100 +-
 compiler/vectorise/Vectorise/Utils/Hoisting.hs     |   75 +-
 compiler/vectorise/Vectorise/Utils/PADict.hs       |    7 +-
 compiler/vectorise/Vectorise/Utils/Poly.hs         |   22 +-
 compiler/vectorise/Vectorise/Var.hs                |  114 +-
 compiler/vectorise/Vectorise/Vect.hs               |  149 +-
 configure.ac                                       |    7 +
 distrib/configure.ac.in                            |    3 +
 docs/man/ghc.mk                                    |    2 +-
 docs/users_guide/codegens.xml                      |  123 ++
 docs/users_guide/debugging.xml                     |   36 +-
 docs/users_guide/ffi-chap.xml                      |  117 +-
 docs/users_guide/flags.xml                         |   53 +-
 docs/users_guide/glasgow_exts.xml                  |  370 ++++-
 docs/users_guide/packages.xml                      |    3 +-
 docs/users_guide/phases.xml                        |   47 +-
 docs/users_guide/runtime_control.xml               |   42 +-
 docs/users_guide/safe_haskell.xml                  |  418 ++++--
 docs/users_guide/separate_compilation.xml          |   28 +-
 docs/users_guide/sooner.xml                        |   14 +-
 docs/users_guide/ug-ent.xml.in                     |    1 +
 docs/users_guide/using.xml                         |   43 +-
 driver/ghci/ghc.mk                                 |    6 +-
 driver/split/ghc-split.lprl                        |  469 ++----
 ghc.mk                                             |   99 +-
 ghc/ghc.mk                                         |   11 +-
 ghc/hschooks.c                                     |    4 +
 includes/Rts.h                                     |   30 +
 includes/Stg.h                                     |   79 +-
 includes/ghc.mk                                    |    6 +-
 includes/rts/Flags.h                               |   21 +-
 includes/rts/storage/InfoTables.h                  |    5 -
 includes/rts/storage/TSO.h                         |    6 +
 includes/stg/MachRegs.h                            |  294 ----
 includes/stg/TailCalls.h                           |  124 --
 libffi/ghc.mk                                      |   16 +-
 mk/config.mk.in                                    |    1 +
 mk/project.mk.in                                   |    3 +
 mk/tree.mk                                         |   21 +
 rts/Exception.cmm                                  |   39 +-
 rts/GetTime.h                                      |   14 +-
 rts/Linker.c                                       |   27 +-
 rts/PrimOps.cmm                                    |   13 +-
 rts/ProfHeap.c                                     |    3 +-
 rts/ProfHeap.h                                     |    4 +-
 rts/Profiling.c                                    |    8 +-
 rts/Proftimer.c                                    |    6 +-
 rts/RtsFlags.c                                     |   76 +-
 rts/RtsStartup.c                                   |    3 +-
 rts/RtsUtils.c                                     |    2 +-
 rts/Schedule.c                                     |    2 +-
 rts/Stats.c                                        |  162 +-
 rts/Stats.h                                        |    6 +-
 rts/StgCRun.c                                      | 1016 ++++--------
 rts/StgMiscClosures.cmm                            |   24 +-
 rts/Task.c                                         |   19 +-
 rts/Task.h                                         |   25 +-
 rts/Threads.c                                      |   12 +-
 rts/Ticker.h                                       |    2 +-
 rts/eventlog/EventLog.c                            |   23 +-
 rts/posix/GetTime.c                                |   38 +-
 rts/posix/Itimer.c                                 |  122 +-
 rts/posix/Itimer.h                                 |    2 -
 rts/posix/Select.c                                 |   39 +-
 rts/posix/Select.h                                 |    8 +-
 rts/sm/Compact.c                                   |    3 +-
 rts/sm/GC.c                                        |    2 +-
 rts/sm/GCTDecl.h                                   |   15 +-
 rts/sm/GCThread.h                                  |    6 +-
 rts/win32/GetTime.c                                |   31 +-
 rts/win32/Ticker.c                                 |  178 +--
 rules/build-dependencies.mk                        |    6 +-
 rules/build-package-way.mk                         |    6 +-
 rules/build-package.mk                             |    4 +-
 rules/build-perl.mk                                |    2 +-
 rules/build-prog.mk                                |    4 +
 rules/clean-target.mk                              |    2 +-
 rules/docbook.mk                                   |    2 +-
 rules/manual-package-config.mk                     |    2 +-
 rules/shell-wrapper.mk                             |    4 +-
 sync-all                                           |   10 +
 utils/ghc-pkg/ghc.mk                               |   10 +-
 utils/mkdirhier/ghc.mk                             |    2 +-
 utils/runghc/ghc.mk                                |    2 +-
 validate                                           |    6 +-
 209 files changed, 9632 insertions(+), 7993 deletions(-)

diff --cc compiler/llvmGen/LlvmCodeGen/CodeGen.hs
index 7e27298,b2ad4c5..9c500bb
--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs
@@@ -754,21 -757,46 +757,60 @@@ genMachOp env _ op [x] = case op o
      MO_FF_Conv from to
          -> sameConv from (widthToLlvmFloat to) LM_Fptrunc LM_Fpext
  
 +    MO_VF_Neg len w ->
 +        let ty    = widthToLlvmFloat w
 +            vecty = LMVector len ty
 +            all0  = LMFloatLit (-0) ty
 +            all0s = LMLitVar $ LMVectorLit (replicate len all0) vecty
 +        in negate vecty all0s LM_MO_FSub    
 +
 +    MO_VN_Neg len w ->
 +        let ty    = widthToLlvmInt w
 +            vecty = LMVector len ty
 +            all0  = LMIntLit (-0) ty
 +            all0s = LMLitVar $ LMVectorLit (replicate len all0) vecty
 +        in negate vecty all0s LM_MO_Sub    
 +
-     a -> panic $ "genMachOp: unmatched unary CmmMachOp! (" ++ show a ++ ")"
+     -- Handle unsupported cases explicitly so we get a warning
+     -- of missing case when new MachOps added
+     MO_Add _          -> panicOp
+     MO_Mul _          -> panicOp
+     MO_Sub _          -> panicOp
+     MO_S_MulMayOflo _ -> panicOp
+     MO_S_Quot _       -> panicOp
+     MO_S_Rem _        -> panicOp
+     MO_U_MulMayOflo _ -> panicOp
+     MO_U_Quot _       -> panicOp
+     MO_U_Rem _        -> panicOp
+ 
+     MO_Eq  _          -> panicOp
+     MO_Ne  _          -> panicOp
+     MO_S_Ge _         -> panicOp
+     MO_S_Gt _         -> panicOp
+     MO_S_Le _         -> panicOp
+     MO_S_Lt _         -> panicOp
+     MO_U_Ge _         -> panicOp
+     MO_U_Gt _         -> panicOp
+     MO_U_Le _         -> panicOp
+     MO_U_Lt _         -> panicOp
+ 
+     MO_F_Add        _ -> panicOp
+     MO_F_Sub        _ -> panicOp
+     MO_F_Mul        _ -> panicOp
+     MO_F_Quot       _ -> panicOp
+     MO_F_Eq         _ -> panicOp
+     MO_F_Ne         _ -> panicOp
+     MO_F_Ge         _ -> panicOp
+     MO_F_Gt         _ -> panicOp
+     MO_F_Le         _ -> panicOp
+     MO_F_Lt         _ -> panicOp
+ 
+     MO_And          _ -> panicOp
+     MO_Or           _ -> panicOp
+     MO_Xor          _ -> panicOp
+     MO_Shl          _ -> panicOp
+     MO_U_Shr        _ -> panicOp
+     MO_S_Shr        _ -> panicOp
  
      where
          negate ty v2 negOp = do
@@@ -895,20 -908,15 +940,28 @@@ genMachOp_slow env opt op [x, y] = cas
      MO_U_Shr _ -> genBinMach LM_MO_LShr
      MO_S_Shr _ -> genBinMach LM_MO_AShr
  
 +    MO_VF_Add _ _  -> genBinMach LM_MO_FAdd
 +    MO_VF_Sub _ _  -> genBinMach LM_MO_FSub
 +    MO_VF_Mul _ _  -> genBinMach LM_MO_FMul
 +    MO_VF_Quot _ _ -> genBinMach LM_MO_FDiv
 +    
 +    MO_VN_Add _ _   -> genBinMach LM_MO_Add
 +    MO_VN_Sub _ _   -> genBinMach LM_MO_Sub
 +    MO_VN_Mul _ _   -> genBinMach LM_MO_Mul
 +    MO_VN_SQuot _ _ -> genBinMach LM_MO_SDiv
 +    MO_VN_SRem _ _  -> genBinMach LM_MO_SRem
 +    MO_VN_UQuot _ _ -> genBinMach LM_MO_UDiv
 +    MO_VN_URem _ _  -> genBinMach LM_MO_URem
-     
-     a -> panic $ "genMachOp: unmatched binary CmmMachOp! (" ++ show a ++ ")"
++
+     MO_Not _       -> panicOp
+     MO_S_Neg _     -> panicOp
+     MO_F_Neg _     -> panicOp
+ 
+     MO_SF_Conv _ _ -> panicOp
+     MO_FS_Conv _ _ -> panicOp
+     MO_SS_Conv _ _ -> panicOp
+     MO_UU_Conv _ _ -> panicOp
+     MO_FF_Conv _ _ -> panicOp
  
      where
          binLlvmOp ty binOp = do



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

Reply via email to