git-annex/Build/EvilLinker.hs

141 lines
3.6 KiB
Haskell
Raw Normal View History

2013-12-06 16:27:21 +00:00
{- Allows linking haskell programs too big for all the files to fit in a
- command line.
-
- See https://ghc.haskell.org/trac/ghc/ticket/8596
-
2013-12-06 16:27:21 +00:00
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Main where
import Data.Maybe
import Data.Either
import Data.List
2013-12-06 17:14:01 +00:00
import Data.List.Utils
2013-12-06 16:27:21 +00:00
import Text.Parsec
import Text.Parsec.String
import Control.Applicative ((<$>))
import Control.Monad
import Utility.Monad
import Utility.Process
2013-12-06 16:43:30 +00:00
import System.Directory
2013-12-06 16:27:21 +00:00
2013-12-06 17:53:58 +00:00
data CmdParams = CmdParams
{ cmd :: String
, opts :: String
, env :: Maybe [(String, String)]
} deriving (Show)
2013-12-06 16:27:21 +00:00
2013-12-06 16:43:30 +00:00
{- Find where ghc calls gcc to link the executable. -}
2013-12-06 16:27:21 +00:00
parseGhcLink :: Parser CmdParams
parseGhcLink = do
2013-12-06 17:14:01 +00:00
many prelinkline
2013-12-06 16:27:21 +00:00
linkheaderline
char '"'
gcccmd <- many1 (noneOf "\"")
string "\" "
gccparams <- restOfLine
2013-12-06 17:53:58 +00:00
return $ CmdParams gcccmd (manglepaths gccparams) Nothing
2013-12-06 16:27:21 +00:00
where
linkheaderline = do
string "*** Linker"
restOfLine
2013-12-06 17:14:01 +00:00
prelinkline = do
2013-12-06 16:27:21 +00:00
notFollowedBy linkheaderline
restOfLine
2013-12-06 16:55:32 +00:00
manglepaths = replace "\\" "/"
2013-12-06 16:27:21 +00:00
2013-12-06 17:27:29 +00:00
{- Find where gcc calls collect2. -}
2013-12-06 16:48:39 +00:00
parseGccLink :: Parser CmdParams
2013-12-06 17:14:01 +00:00
parseGccLink = do
2013-12-06 18:20:44 +00:00
many preenv
env <- collectenv
2013-12-06 17:27:29 +00:00
try $ char ' '
path <- manyTill anyChar (try $ string collectcmd)
char ' '
collect2params <- restOfLine
2013-12-06 18:20:44 +00:00
return $ CmdParams (path ++ collectcmd) (escapeDosPaths collect2params) env
2013-12-06 17:14:01 +00:00
where
2013-12-06 17:27:29 +00:00
collectcmd = "collect2.exe"
2013-12-06 18:20:44 +00:00
pathenv = "COMPILER_PATH"
libpathenv = "LIBRARY_PATH"
optenv = "COLLECT_GCC_OPTIONS"
collectenv = do
string pathenv
2013-12-06 17:27:29 +00:00
char '='
2013-12-06 18:20:44 +00:00
p <- restOfLine
string libpathenv
char '='
lp <- restOfLine
string optenv
char '='
o <- restOfLine
return $ Just [(pathenv, p), (libpathenv, lp), (optenv, o)]
preenv = do
notFollowedBy collectenv
2013-12-06 17:27:29 +00:00
restOfLine
2013-12-06 18:20:44 +00:00
{- Find where collect2 calls ld. -}
parseCollect2 :: Parser CmdParams
parseCollect2 = do
string "GNU ld"
restOfLine
string "collect2 version"
restOfLine
path <- manyTill anyChar (try $ string ldcmd)
char ' '
params <- restOfLine
2013-12-06 18:46:32 +00:00
return $ CmdParams (path ++ ldcmd) (escapeDosPaths params) Nothing
2013-12-06 18:20:44 +00:00
where
ldcmd = "ld.exe"
2013-12-06 16:43:30 +00:00
2013-12-06 17:39:35 +00:00
{- Input contains something like
- c:/program files/haskell platform/foo -LC:/Program Files/Haskell Platform/ -L...
- and the *right* spaces must be escaped with \
-
- Argh.
-}
escapeDosPaths :: String -> String
escapeDosPaths = replace "Program Files" "Program\\ Files"
. replace "program files" "program\\ files"
. replace "Haskell Platform" "Haskell\\ Platform"
. replace "haskell platform" "haskell\\ platform"
2013-12-06 18:58:26 +00:00
. replace "Application Data" "Application\\ Data"
2013-12-06 17:39:35 +00:00
2013-12-06 16:27:21 +00:00
restOfLine :: Parser String
restOfLine = newline `after` many (noneOf "\n")
2013-12-06 18:29:58 +00:00
getOutput :: String -> [String] -> Maybe [(String, String)] -> IO (String, Bool)
2013-12-06 17:53:58 +00:00
getOutput cmd params env = do
2013-12-06 16:27:21 +00:00
putStrLn $ unwords [cmd, show params]
2013-12-06 18:29:58 +00:00
processTranscript' cmd params env Nothing
2013-12-06 16:27:21 +00:00
runParser' :: Parser a -> String -> a
2013-12-06 19:15:47 +00:00
runParser' p s = either failedparse id (parse p "" s)
where
2013-12-06 19:18:13 +00:00
failedparse e = error $ (show e) ++ "\n<<<\n" ++ s ++ "\n>>>"
2013-12-06 16:27:21 +00:00
2013-12-06 16:43:30 +00:00
atFile :: FilePath -> String
atFile f = '@':f
2013-12-06 18:29:58 +00:00
runAtFile :: Parser CmdParams -> String -> FilePath -> [String] -> IO (String, Bool)
2013-12-06 16:43:30 +00:00
runAtFile p s f extraparams = do
writeFile f (opts c)
2013-12-06 17:53:58 +00:00
out <- getOutput (cmd c) (atFile f:extraparams) (env c)
2013-12-06 16:43:30 +00:00
removeFile f
return out
where
c = runParser' p s
2013-12-06 16:27:21 +00:00
main = do
2013-12-06 18:29:58 +00:00
ghcout <- fst <$> getOutput "cabal"
2013-12-06 17:53:58 +00:00
["build", "--ghc-options=-v -keep-tmp-files"] Nothing
2013-12-06 18:29:58 +00:00
gccout <- fst <$> runAtFile parseGhcLink ghcout "gcc.opt" ["-v"]
collect2out <- fst <$> runAtFile parseGccLink gccout "collect2.opt" ["-v"]
(out, ok) <- runAtFile parseCollect2 collect2out "ld.opt" []
unless ok $
error $ "ld failed:\n" ++ out