Repository : ssh://darcs.haskell.org//srv/darcs/ghc On branch : ghc-7.4
http://hackage.haskell.org/trac/ghc/changeset/13968dc3646e8d516a6eff19297cc0bb5864c0fa >--------------------------------------------------------------- commit 13968dc3646e8d516a6eff19297cc0bb5864c0fa Author: Ubuntu <[email protected]> Date: Wed Jan 18 01:22:35 2012 +0000 Incorrect type conversion in LLVM backend (#5785). >--------------------------------------------------------------- compiler/llvmGen/Llvm/Types.hs | 5 ++++- 1 files changed, 4 insertions(+), 1 deletions(-) diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index 1013426..aa3ba4f 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -7,6 +7,7 @@ module Llvm.Types where #include "HsVersions.h" import Data.Char +import Data.Int import Data.List (intercalate) import Numeric @@ -186,7 +187,9 @@ getPlainName (LMLitVar x ) = getLit x -- | Print a literal value. No type. getLit :: LlvmLit -> String -getLit (LMIntLit i _ ) = show ((fromInteger i)::Int) +getLit (LMIntLit i (LMInt 32)) = show (fromInteger i :: Int32) +getLit (LMIntLit i (LMInt 64)) = show (fromInteger i :: Int64) +getLit (LMIntLit i _ ) = show (fromInteger i :: Int) getLit (LMFloatLit r LMFloat ) = fToStr $ realToFrac r getLit (LMFloatLit r LMDouble) = dToStr r getLit f@(LMFloatLit _ _) = error $ "Can't print this float literal!" ++ show f _______________________________________________ Cvs-ghc mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-ghc
