[Git][ghc/ghc][master] Fixes for LLVM 7
Marge Bot
gitlab at gitlab.haskell.org
Mon Jun 24 05:11:50 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
71aca77c by Erik de Castro Lopo at 2019-06-24T05:11:46Z
Fixes for LLVM 7
LLVM version numberinf changed recently. Previously, releases were numbered
4.0, 5.0 and 6.0 but with version 7, they dropped the redundant ".0".
Fix requires for Llvm detection and some code.
- - - - -
5 changed files:
- compiler/llvmGen/LlvmCodeGen.hs
- compiler/llvmGen/LlvmCodeGen/Base.hs
- compiler/main/DriverPipeline.hs
- compiler/main/SysTools/Tasks.hs
- configure.ac
Changes:
=====================================
compiler/llvmGen/LlvmCodeGen.hs
=====================================
@@ -3,7 +3,7 @@
-- -----------------------------------------------------------------------------
-- | This is the top-level module in the LLVM code generator.
--
-module LlvmCodeGen ( llvmCodeGen, llvmFixupAsm ) where
+module LlvmCodeGen ( LlvmVersion (..), llvmCodeGen, llvmFixupAsm ) where
#include "HsVersions.h"
=====================================
compiler/llvmGen/LlvmCodeGen/Base.hs
=====================================
@@ -13,7 +13,7 @@ module LlvmCodeGen.Base (
LiveGlobalRegs,
LlvmUnresData, LlvmData, UnresLabel, UnresStatic,
- LlvmVersion, supportedLlvmVersion, llvmVersionStr,
+ LlvmVersion (..), supportedLlvmVersion, llvmVersionStr,
LlvmM,
runLlvm, liftStream, withClearVars, varLookup, varInsert,
@@ -177,14 +177,25 @@ llvmPtrBits dflags = widthInBits $ typeWidth $ gcWord dflags
--
-- | LLVM Version Number
-type LlvmVersion = (Int, Int)
+data LlvmVersion
+ = LlvmVersion Int
+ | LlvmVersionOld Int Int
+ deriving Eq
+
+-- Custom show instance for backwards compatibility.
+instance Show LlvmVersion where
+ show (LlvmVersion maj) = show maj
+ show (LlvmVersionOld maj min) = show maj ++ "." ++ show min
-- | The LLVM Version that is currently supported.
supportedLlvmVersion :: LlvmVersion
-supportedLlvmVersion = sUPPORTED_LLVM_VERSION
+supportedLlvmVersion = LlvmVersion sUPPORTED_LLVM_VERSION
llvmVersionStr :: LlvmVersion -> String
-llvmVersionStr (major, minor) = show major ++ "." ++ show minor
+llvmVersionStr v =
+ case v of
+ LlvmVersion maj -> show maj
+ LlvmVersionOld maj min -> show maj ++ "." ++ show min
-- ----------------------------------------------------------------------------
-- * Environment Handling
=====================================
compiler/main/DriverPipeline.hs
=====================================
@@ -56,7 +56,7 @@ import StringBuffer ( hGetStringBuffer, hPutStringBuffer )
import BasicTypes ( SuccessFlag(..) )
import Maybes ( expectJust )
import SrcLoc
-import LlvmCodeGen ( llvmFixupAsm )
+import LlvmCodeGen ( LlvmVersion (..), llvmFixupAsm )
import MonadUtils
import GHC.Platform
import TcRnTypes
@@ -2038,7 +2038,8 @@ getBackendDefs :: DynFlags -> IO [String]
getBackendDefs dflags | hscTarget dflags == HscLlvm = do
llvmVer <- figureLlvmVersion dflags
return $ case llvmVer of
- Just n -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format n ]
+ Just (LlvmVersion n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (n,0) ]
+ Just (LlvmVersionOld m n) -> [ "-D__GLASGOW_HASKELL_LLVM__=" ++ format (m,n) ]
_ -> []
where
format (major, minor)
=====================================
compiler/main/SysTools/Tasks.hs
=====================================
@@ -23,7 +23,7 @@ import System.IO
import System.Process
import GhcPrelude
-import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion)
+import LlvmCodeGen.Base (LlvmVersion (..), llvmVersionStr, supportedLlvmVersion)
import SysTools.Process
import SysTools.Info
@@ -200,7 +200,7 @@ runClang dflags args = do
)
-- | Figure out which version of LLVM we are running this session
-figureLlvmVersion :: DynFlags -> IO (Maybe (Int, Int))
+figureLlvmVersion :: DynFlags -> IO (Maybe LlvmVersion)
figureLlvmVersion dflags = do
let (pgm,opts) = pgm_lc dflags
args = filter notNull (map showOpt opts)
@@ -222,8 +222,10 @@ figureLlvmVersion dflags = do
vline <- dropWhile (not . isDigit) `fmap` hGetLine pout
v <- case span (/= '.') vline of
("",_) -> fail "no digits!"
- (x,y) -> return (read x
- , read $ takeWhile isDigit $ drop 1 y)
+ (x,"") -> return $ LlvmVersion (read x)
+ (x,y) -> return $ LlvmVersionOld
+ (read x)
+ (read $ takeWhile isDigit $ drop 1 y)
hClose pin
hClose pout
=====================================
configure.ac
=====================================
@@ -628,7 +628,7 @@ AC_SUBST([LibtoolCmd])
# tools we are looking for. In the past, GHC supported a number of
# versions of LLVM simultaneously, but that stopped working around
# 3.5/3.6 release of LLVM.
-LlvmVersion=7.0
+LlvmVersion=7
AC_SUBST([LlvmVersion])
sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/')
AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/71aca77c780dad8496054a06a7fe65704a13a742
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/71aca77c780dad8496054a06a7fe65704a13a742
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190624/b3c734f7/attachment-0001.html>
More information about the ghc-commits
mailing list