move standalone building code out of Makefile and into Build.Standalone
This includes making Build.Standalone run LinuxMkLibs or OSXMkLibs rather than doing that separately. Which is groundwork for a later optimisation. Also it simplified the code some.
This commit is contained in:
parent
465842f3f6
commit
e62817c00d
6 changed files with 144 additions and 109 deletions
|
@ -5,9 +5,8 @@
|
|||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Main where
|
||||
module Build.LinuxMkLibs (mklibs) where
|
||||
|
||||
import System.Environment
|
||||
import Data.Maybe
|
||||
import System.FilePath
|
||||
import Control.Monad
|
||||
|
@ -25,14 +24,8 @@ import Utility.Path
|
|||
import Utility.FileMode
|
||||
import Utility.CopyFile
|
||||
|
||||
main :: IO ()
|
||||
main = getArgs >>= go
|
||||
where
|
||||
go [] = error "specify LINUXSTANDALONE_DIST"
|
||||
go (top:_) = mklibs top
|
||||
|
||||
mklibs :: FilePath -> IO ()
|
||||
mklibs top = do
|
||||
mklibs :: FilePath -> a -> IO ()
|
||||
mklibs top _installedbins = do
|
||||
fs <- dirContentsRecursive top
|
||||
exes <- filterM checkExe fs
|
||||
libs <- parseLdd <$> readProcess "ldd" exes
|
||||
|
@ -71,8 +64,7 @@ consolidateUsrLib top libdirs = map reverse <$> go [] (map reverse libdirs)
|
|||
let x' = reverse x
|
||||
let y' = reverse y
|
||||
fs <- getDirectoryContents (inTop top x')
|
||||
forM_ fs $ \f -> do
|
||||
print f
|
||||
forM_ fs $ \f ->
|
||||
unless (dirCruft f) $
|
||||
renameFile
|
||||
(inTop top (x' </> f))
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Main where
|
||||
module Build.OSXMkLibs (mkLibs) where
|
||||
|
||||
import System.Environment (getArgs)
|
||||
import Data.Maybe
|
||||
|
@ -31,17 +31,20 @@ import qualified Data.Set as S
|
|||
|
||||
type LibMap = M.Map FilePath String
|
||||
|
||||
mklibs :: FilePath -> M.Map FilePath FilePath -> IO ()
|
||||
mklibs appbase installedbins = mklibs' appbase installedbins [] [] M.empty
|
||||
|
||||
{- Recursively find and install libs, until nothing new to install is found. -}
|
||||
mklibs :: FilePath -> [FilePath] -> [(FilePath, FilePath)] -> LibMap -> IO ()
|
||||
mklibs appbase libdirs replacement_libs libmap = do
|
||||
(new, replacement_libs', libmap') <- installLibs appbase replacement_libs libmap
|
||||
mklibs' :: FilePath -> M.Map FilePath FilePath -> [FilePath] -> [(FilePath, FilePath)] -> LibMap -> IO ()
|
||||
mklibs' appbase installedbins libdirs replacement_libs libmap = do
|
||||
(new, replacement_libs', libmap') <- installLibs appbase installedbins replacement_libs libmap
|
||||
unless (null new) $
|
||||
mklibs appbase (libdirs++new) replacement_libs' libmap'
|
||||
mklibs' appbase installedbins (libdirs++new) replacement_libs' libmap'
|
||||
|
||||
{- Returns directories into which new libs were installed. -}
|
||||
installLibs :: FilePath -> [(FilePath, FilePath)] -> LibMap -> IO ([FilePath], [(FilePath, FilePath)], LibMap)
|
||||
installLibs :: FilePath -> M.Map FilePath FilePath -> [(FilePath, FilePath)] -> LibMap -> IO ([FilePath], [(FilePath, FilePath)], LibMap)
|
||||
installLibs appbase replacement_libs libmap = do
|
||||
(needlibs, replacement_libs', libmap') <- otool appbase replacement_libs libmap
|
||||
(needlibs, replacement_libs', libmap') <- otool appbase installedbins replacement_libs libmap
|
||||
libs <- forM needlibs $ \lib -> do
|
||||
pathlib <- findLibPath lib
|
||||
let shortlib = fromMaybe (error "internal") (M.lookup lib libmap')
|
||||
|
@ -78,8 +81,8 @@ installLibs appbase replacement_libs libmap = do
|
|||
- library files returned may need to be run through findLibPath
|
||||
- to find the actual libraries to install.
|
||||
-}
|
||||
otool :: FilePath -> [(FilePath, FilePath)] -> LibMap -> IO ([FilePath], [(FilePath, FilePath)], LibMap)
|
||||
otool appbase replacement_libs libmap = do
|
||||
otool :: FilePath -> M.Map FilePath FilePath -> [(FilePath, FilePath)] -> LibMap -> IO ([FilePath], [(FilePath, FilePath)], LibMap)
|
||||
otool appbase installedbins replacement_libs libmap = do
|
||||
files <- filterM doesFileExist =<< dirContentsRecursive appbase
|
||||
process [] files replacement_libs libmap
|
||||
where
|
||||
|
@ -99,7 +102,7 @@ otool appbase replacement_libs libmap = do
|
|||
_ <- boolSystem "chmod" [Param "755", File file]
|
||||
libs <- filter want . parseOtool
|
||||
<$> readProcess "otool" ["-L", file]
|
||||
expanded_libs <- expand_rpath libs replacement_libs file
|
||||
expanded_libs <- expand_rpath installedbins libs replacement_libs file
|
||||
let rls' = nub $ rls ++ (zip libs expanded_libs)
|
||||
m' <- install_name_tool file libs expanded_libs m
|
||||
process (expanded_libs:c) rest rls' m'
|
||||
|
@ -118,12 +121,10 @@ findLibPath l = go =<< getEnv "DYLD_LIBRARY_PATH"
|
|||
- option (so it doesn't do anything.. hopefully!) and asking the dynamic
|
||||
- linker to print expanded rpaths.
|
||||
-}
|
||||
expand_rpath :: [String] -> [(FilePath, FilePath)] -> FilePath -> IO [String]
|
||||
expand_rpath libs replacement_libs cmd
|
||||
expand_rpath :: M.Map FilePath FilePath -> [String] -> [(FilePath, FilePath)] -> FilePath -> IO [String]
|
||||
expand_rpath installedbins libs replacement_libs cmd
|
||||
| any ("@rpath" `isInfixOf`) libs = do
|
||||
installed <- M.fromList . Prelude.read
|
||||
<$> readFile "tmp/standalone-installed"
|
||||
let origcmd = case M.lookup cmd installed of
|
||||
let origcmd = case M.lookup cmd installedbins of
|
||||
Nothing -> cmd
|
||||
Just cmd' -> cmd'
|
||||
s <- catchDefaultIO "" $ readProcess "sh" ["-c", probe origcmd]
|
||||
|
@ -185,9 +186,3 @@ getLibName lib libmap = case M.lookup lib libmap of
|
|||
used = S.fromList $ M.elems libmap
|
||||
nextfreename = fromMaybe (error "ran out of short library names!") $
|
||||
headMaybe $ dropWhile (`S.member` used) names
|
||||
|
||||
main :: IO ()
|
||||
main = getArgs >>= go
|
||||
where
|
||||
go [] = error "specify OSXAPP_BASE"
|
||||
go (appbase:_) = mklibs appbase [] [] M.empty
|
||||
|
|
|
@ -1,26 +1,37 @@
|
|||
{- Makes standalone bundle.
|
||||
-
|
||||
- Copyright 2012-2019 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2012-2020 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
|
||||
module Main where
|
||||
|
||||
import System.Environment (getArgs)
|
||||
import Control.Monad.IfElse
|
||||
import System.Environment
|
||||
import System.FilePath
|
||||
import System.Posix.Files
|
||||
import Control.Monad
|
||||
import Build.BundledPrograms
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import qualified Data.Map as M
|
||||
|
||||
import Utility.SafeCommand
|
||||
import Utility.Process
|
||||
import Utility.Path
|
||||
import Utility.Directory
|
||||
import Utility.Env
|
||||
import Build.BundledPrograms
|
||||
#ifdef darwin_HOST_OS
|
||||
import Build.OSXMkLibs (mklibs)
|
||||
import Build.Version
|
||||
import Utility.Split
|
||||
#else
|
||||
import Build.LinuxMkLibs (mklibs)
|
||||
import Utility.FileMode
|
||||
#endif
|
||||
|
||||
progDir :: FilePath -> FilePath
|
||||
#ifdef darwin_HOST_OS
|
||||
|
@ -42,6 +53,16 @@ installProg dir prog = searchPath prog >>= go
|
|||
error $ "install failed for " ++ prog
|
||||
return (dest, f)
|
||||
|
||||
installBundledPrograms :: FilePath -> IO (M.Map FilePath FilePath)
|
||||
installBundledPrograms topdir = M.fromList . concat <$> mapM go
|
||||
[ (progDir topdir, preferredBundledPrograms)
|
||||
, (extraProgDir topdir, extraBundledPrograms)
|
||||
]
|
||||
where
|
||||
go (dir, progs) = do
|
||||
createDirectoryIfMissing True dir
|
||||
forM progs $ installProg dir
|
||||
|
||||
installGitLibs :: FilePath -> IO ()
|
||||
installGitLibs topdir = do
|
||||
-- install git-core programs; these are run by the git command
|
||||
|
@ -100,21 +121,93 @@ installGitLibs topdir = do
|
|||
case ls of
|
||||
[] -> error $ "git " ++ opt ++ "did not output a location"
|
||||
(p:_) -> return p
|
||||
|
||||
cp src dest = do
|
||||
nukeFile dest
|
||||
unlessM (boolSystem "cp" [Param "-a", File src, File dest]) $
|
||||
|
||||
cp :: FilePath -> FilePath -> IO ()
|
||||
cp src dest = do
|
||||
nukeFile dest
|
||||
unlessM (boolSystem "cp" [Param "-a", File src, File dest]) $
|
||||
error "cp failed"
|
||||
|
||||
installMagic :: FilePath -> IO ()
|
||||
#ifdef darwin_HOST_OS
|
||||
installMagic topdir = getEnv "OSX_MAGIC_FILE" >>= \case
|
||||
Nothing -> hputStrLn stderr "OSX_MAGIC_FILE not set; not including it"
|
||||
Just f -> do
|
||||
let mdir = topdir </> "magic"
|
||||
createDirectoryIfMissing True mdir
|
||||
unlessM (boolSystem "cp" [File f, File mdir </> "magic.mgc") $
|
||||
error "cp failed"
|
||||
#else
|
||||
installMagic topdir = do
|
||||
let mdir = topdir </> "magic"
|
||||
createDirectoryIfMissing True mdir
|
||||
unlessM (boolSystem "cp" [File "/usr/share/file/magic.mgc", File (mdir </> "magic.mgc")]) $
|
||||
error "cp failed"
|
||||
#endif
|
||||
|
||||
installLocales :: FilePath -> IO ()
|
||||
#ifdef darwin_HOST_OS
|
||||
installLocales _ = return ()
|
||||
#else
|
||||
installLocales topdir = cp "/usr/share/i18n" (topdir </> "i18n")
|
||||
#endif
|
||||
|
||||
installWrapper :: FilePath -> FilePath -> IO ()
|
||||
#ifdef darwin_HOST_OS
|
||||
installWrapper topdir basedir = do
|
||||
removeDirectoryRecursive basedir
|
||||
createDirectoryIfMissing True (takeDirectory basedir)
|
||||
unlessM (boolSystem "cp" [Param "-R", File "standalone/osx/git-annex.app", File basedir]) $
|
||||
error "cp failed"
|
||||
plist <- lines <$> readFile "standalone/osx/Info.plist.template"
|
||||
version <- getVersion
|
||||
writeFile (basedir </> "Contents" </> "Info.plist")
|
||||
(unlines (map (expandversion version) plist))
|
||||
where
|
||||
expandversion v l = replace "GIT_ANNEX_VERSION" v l
|
||||
#else
|
||||
installWrapper topdir _basedir = do
|
||||
removeDirectoryRecursive topdir
|
||||
createDirectoryIfMissing True (takeDirectory topdir)
|
||||
unlessM (boolSystem "cp" [Param "-R", File "standalone/linux/skel", File topdir]) $
|
||||
error "cp failed"
|
||||
runshell <- lines <$> readFile "standalone/linux/skel/runshell"
|
||||
-- GIT_ANNEX_PACKAGE_INSTALL can be set by a distributor and
|
||||
-- runshell will be modified
|
||||
gapi <- getEnv "GIT_ANNEX_PACKAGE_INSTALL"
|
||||
writeFile (topdir </> "runshell")
|
||||
(unlines (map (expandrunshell gapi) runshell))
|
||||
modifyFileMode (topdir </> "runshell") (addModes executeModes)
|
||||
where
|
||||
expandrunshell (Just gapi) l@"GIT_ANNEX_PACKAGE_INSTALL=" = l ++ gapi
|
||||
expandrunshell _ l = l
|
||||
#endif
|
||||
|
||||
installGitAnnex :: FilePath -> IO ()
|
||||
#ifdef darwin_HOST_OS
|
||||
installGitAnnex topdir = go topdir
|
||||
#else
|
||||
installGitAnnex topdir = go (topdir </> "bin")
|
||||
#endif
|
||||
where
|
||||
go bindir = do
|
||||
createDirectoryIfMissing True bindir
|
||||
unlessM (boolSystem "cp" [File "git-annex", File bindir]) $
|
||||
error "cp failed"
|
||||
unlessM (boolSystem "strip" [File (bindir </> "git-annex")]) $
|
||||
error "strip failed"
|
||||
createLink "git-annex" (bindir </> "git-annex-shell")
|
||||
createLink "git-annex" (bindir </> "git-remote-tor-annex")
|
||||
|
||||
main :: IO ()
|
||||
main = getArgs >>= go
|
||||
where
|
||||
go [] = error "specify topdir"
|
||||
go (topdir:_) = do
|
||||
installed <- forM
|
||||
[ (progDir topdir, preferredBundledPrograms)
|
||||
, (extraProgDir topdir, extraBundledPrograms) ] $ \(dir, progs) -> do
|
||||
createDirectoryIfMissing True dir
|
||||
forM progs $ installProg dir
|
||||
writeFile "tmp/standalone-installed" (show (concat installed))
|
||||
go (topdir:basedir:[]) = do
|
||||
installWrapper topdir basedir
|
||||
installGitAnnex topdir
|
||||
installedbins <- installBundledPrograms topdir
|
||||
installGitLibs topdir
|
||||
installMagic topdir
|
||||
installLocales topdir
|
||||
mklibs topdir installedbins
|
||||
go _ = error "specify topdir and basedir"
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue