summaryrefslogtreecommitdiff
path: root/Build
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2015-05-12 13:23:22 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2015-05-12 13:23:22 -0400
commit4d49342612dd441cdc503b5294035fc05a9a5a77 (patch)
tree435a82d44b5a6aa3df411b36fb9fad2553cc670a /Build
parent44a48a19ffeb8085e7ae1f6bf58d5661adaf8a8d (diff)
parent5cd9e10cde3c06ecc6a97f5f60a9def22f959bd2 (diff)
Merge branch 'master' into concurrentprogress
Conflicts: Command/Fsck.hs Messages.hs Remote/Directory.hs Remote/Git.hs Remote/Helper/Special.hs Types/Remote.hs debian/changelog git-annex.cabal
Diffstat (limited to 'Build')
-rw-r--r--Build/BundledPrograms.hs5
-rw-r--r--Build/Configure.hs2
-rw-r--r--Build/DesktopFile.hs1
-rw-r--r--Build/DistributionUpdate.hs2
-rw-r--r--Build/NullSoftInstaller.hs72
-rw-r--r--Build/TestConfig.hs2
-rw-r--r--Build/Version.hs4
-rwxr-xr-xBuild/mdwn2man1
8 files changed, 40 insertions, 49 deletions
diff --git a/Build/BundledPrograms.hs b/Build/BundledPrograms.hs
index 1e826cb10..4ceee3b52 100644
--- a/Build/BundledPrograms.hs
+++ b/Build/BundledPrograms.hs
@@ -35,13 +35,14 @@ bundledPrograms = catMaybes
#endif
, Just "rsync"
#ifndef darwin_HOST_OS
+#ifndef mingw32_HOST_OS
-- OS X has ssh installed by default.
-- Linux probably has ssh, but not guaranteed.
- -- On Windows, msysgit provides ssh, but not in PATH,
- -- so we ship our own.
+ -- On Windows, msysgit provides ssh.
, Just "ssh"
, Just "ssh-keygen"
#endif
+#endif
#ifndef mingw32_HOST_OS
, Just "sh"
#endif
diff --git a/Build/Configure.hs b/Build/Configure.hs
index c90231b29..55f2493a1 100644
--- a/Build/Configure.hs
+++ b/Build/Configure.hs
@@ -1,5 +1,7 @@
{- Checks system configuration and generates SysConfig.hs. -}
+{-# OPTIONS_GHC -fno-warn-tabs #-}
+
module Build.Configure where
import System.Directory
diff --git a/Build/DesktopFile.hs b/Build/DesktopFile.hs
index 6e70b0d5f..9d68ff1d9 100644
--- a/Build/DesktopFile.hs
+++ b/Build/DesktopFile.hs
@@ -7,6 +7,7 @@
-}
{-# LANGUAGE CPP #-}
+{-# OPTIONS_GHC -fno-warn-tabs #-}
module Build.DesktopFile where
diff --git a/Build/DistributionUpdate.hs b/Build/DistributionUpdate.hs
index 37b8e04aa..da1202fe2 100644
--- a/Build/DistributionUpdate.hs
+++ b/Build/DistributionUpdate.hs
@@ -10,7 +10,7 @@
import Common.Annex
import Types.Distribution
-import Build.Version
+import Build.Version (getChangelogVersion, Version)
import Utility.UserInfo
import Utility.Url
import qualified Git.Construct
diff --git a/Build/NullSoftInstaller.hs b/Build/NullSoftInstaller.hs
index 42260bd3f..7bb16f3f7 100644
--- a/Build/NullSoftInstaller.hs
+++ b/Build/NullSoftInstaller.hs
@@ -1,7 +1,8 @@
{- Generates a NullSoft installer program for git-annex on Windows.
-
- To build the installer, git-annex should already be built by cabal,
- - and ssh and rsync, as well as cygwin libraries, already installed.
+ - and ssh and rsync etc, as well as cygwin libraries, already installed
+ - from cygwin.
-
- This uses the Haskell nsis package (cabal install nsis)
- to generate a .nsi file, which is then used to produce
@@ -11,7 +12,7 @@
- exception of git. The user needs to install git separately,
- and the installer checks for that.
-
- - Copyright 2013 Joey Hess <id@joeyh.name>
+ - Copyright 2013-2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -22,13 +23,17 @@ import Development.NSIS
import System.Directory
import System.FilePath
import Control.Monad
+import Control.Applicative
import Data.String
import Data.Maybe
+import Data.Char
+import Data.List (nub, isPrefixOf)
import Utility.Tmp
import Utility.Path
import Utility.CopyFile
import Utility.SafeCommand
+import Utility.Process
import Build.BundledPrograms
main = do
@@ -37,17 +42,19 @@ main = do
mustSucceed "ln" [File "dist/build/git-annex/git-annex.exe", File gitannex]
let license = tmpdir </> licensefile
mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"]
- extrabins <- forM (cygwinPrograms ++ cygwinDlls) $ \f -> do
+ extrabins <- forM (cygwinPrograms) $ \f -> do
p <- searchPath f
when (isNothing p) $
print ("unable to find in PATH", f)
return p
+ dlls <- forM (catMaybes extrabins) findCygLibs
+ dllpaths <- mapM searchPath (nub (concat dlls))
webappscript <- vbsLauncher tmpdir "git-annex-webapp" "git-annex webapp"
autostartscript <- vbsLauncher tmpdir "git-annex-autostart" "git annex assistant --autostart"
let htmlhelp = tmpdir </> "git-annex.html"
writeFile htmlhelp htmlHelpText
writeFile nsifile $ makeInstaller gitannex license htmlhelp
- (catMaybes extrabins)
+ (wrappers ++ catMaybes (extrabins ++ dllpaths))
[ webappscript, autostartscript ]
mustSucceed "makensis" [File nsifile]
removeFile nsifile -- left behind if makensis fails
@@ -85,7 +92,7 @@ uninstaller = "git-annex-uninstall.exe"
gitInstallDir :: Exp FilePath
gitInstallDir = fromString "$PROGRAMFILES\\Git"
--- This intentionall has a different name than git-annex or
+-- This intentionally has a different name than git-annex or
-- git-annex-webapp, since it is itself treated as an executable file.
-- Also, on XP, the filename is displayed, not the description.
startMenuItem :: Exp FilePath
@@ -169,46 +176,6 @@ makeInstaller gitannex license htmlhelp extrabins launchers = nsis $ do
cygwinPrograms :: [FilePath]
cygwinPrograms = map (\p -> p ++ ".exe") bundledPrograms
--- These are the dlls needed by Cygwin's rsync, ssh, etc.
--- TODO: Use ldd (available in cygwin) to automatically find all
--- needed libs.
-cygwinDlls :: [FilePath]
-cygwinDlls =
- [ "cygwin1.dll"
- , "cygasn1-8.dll"
- , "cygattr-1.dll"
- , "cygheimbase-1.dll"
- , "cygroken-18.dll"
- , "cygcom_err-2.dll"
- , "cygheimntlm-0.dll"
- , "cygsqlite3-0.dll"
- , "cygcrypt-0.dll"
- , "cyghx509-5.dll"
- , "cygssp-0.dll"
- , "cygcrypto-1.0.0.dll"
- , "cygiconv-2.dll"
- , "cyggcc_s-1.dll"
- , "cygintl-8.dll"
- , "cygwind-0.dll"
- , "cyggssapi-3.dll"
- , "cygkrb5-26.dll"
- , "cygz.dll"
- , "cygidn-11.dll"
- , "libcurl-4.dll"
- , "cyggnutls-26.dll"
- , "libcrypto.dll"
- , "libssl.dll"
- , "cyggcrypt-11.dll"
- , "cyggpg-error-0.dll"
- , "cygp11-kit-0.dll"
- , "cygtasn1-3.dll"
- , "cygffi-6.dll"
- , "cygbz2-1.dll"
- , "cygreadline7.dll"
- , "cygncursesw-10.dll"
- , "cygusb0.dll"
- ]
-
-- msysgit opens Program Files/Git/doc/git/html/git-annex.html
-- when git annex --help is run.
htmlHelpText :: String
@@ -221,3 +188,18 @@ htmlHelpText = unlines
, "</body>"
, "</html"
]
+
+-- Find cygwin libraries used by the specified executable.
+findCygLibs :: FilePath -> IO [FilePath]
+findCygLibs p = filter iscyg . mapMaybe parse . lines <$> readProcess "ldd" [p]
+ where
+ parse l = case words (dropWhile isSpace l) of
+ (dll:"=>":_dllpath:_offset:[]) -> Just dll
+ _ -> Nothing
+ iscyg f = "cyg" `isPrefixOf` f || "lib" `isPrefixOf` f
+
+wrappers :: [FilePath]
+wrappers =
+ [ "standalone\\windows\\ssh.cmd"
+ , "standalone\\windows\\ssh-keygen.cmd"
+ ]
diff --git a/Build/TestConfig.hs b/Build/TestConfig.hs
index e55641fb0..35daf1945 100644
--- a/Build/TestConfig.hs
+++ b/Build/TestConfig.hs
@@ -1,5 +1,7 @@
{- Tests the system and generates Build.SysConfig.hs. -}
+{-# OPTIONS_GHC -fno-warn-tabs #-}
+
module Build.TestConfig where
import Utility.Path
diff --git a/Build/Version.hs b/Build/Version.hs
index da9d1bbcb..44b2b975b 100644
--- a/Build/Version.hs
+++ b/Build/Version.hs
@@ -1,5 +1,7 @@
{- Package version determination, for configure script. -}
+{-# OPTIONS_GHC -fno-warn-tabs #-}
+
module Build.Version where
import Data.Maybe
@@ -18,7 +20,7 @@ type Version = String
{- Set when making an official release. (Distribution vendors should set
- this too.) -}
isReleaseBuild :: IO Bool
-isReleaseBuild = isJust <$> catchMaybeIO (getEnv "RELEASE_BUILD")
+isReleaseBuild = (== Just "1") <$> catchMaybeIO (getEnv "RELEASE_BUILD")
{- Version is usually based on the major version from the changelog,
- plus the date of the last commit, plus the git rev of that commit.
diff --git a/Build/mdwn2man b/Build/mdwn2man
index a29ce649e..7ad0d889b 100755
--- a/Build/mdwn2man
+++ b/Build/mdwn2man
@@ -20,6 +20,7 @@ while (<>) {
s/^[ \n]+//;
s/^\t/ /;
s/-/\\-/g;
+ s/git\\-annex/git-annex/g;
s/^Warning:.*//g;
s/^$/.PP\n/;
s/^\*\s+(.*)/.IP "$1"/;