windows installer is fully working

This commit is contained in:
Joey Hess 2013-05-14 19:59:14 -05:00
parent 6cbca01261
commit adbbb71ccb
3 changed files with 132 additions and 65 deletions

46
Build/BundledPrograms.hs Executable file
View file

@ -0,0 +1,46 @@
{- Bundled programs
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Build.BundledPrograms where
import Data.Maybe
import Build.SysConfig as SysConfig
{- Programs that git-annex uses, to include in the bundle.
-
- These may be just the command name, or the full path to it. -}
bundledPrograms :: [FilePath]
bundledPrograms = catMaybes
[ Nothing
#ifndef mingw32_HOST_OS
-- git is not included in the windows bundle
, Just "git"
#endif
, Just "cp"
, Just "xargs"
, Just "rsync"
, Just "ssh"
#ifndef mingw32_HOST_OS
, Just "sh"
#endif
, ifset SysConfig.gpg "gpg"
, ifset SysConfig.curl "curl"
, ifset SysConfig.wget "wget"
, ifset SysConfig.bup "bup"
, SysConfig.lsof
, SysConfig.sha1
, SysConfig.sha256
, SysConfig.sha512
, SysConfig.sha224
, SysConfig.sha384
]
where
ifset True s = Just s
ifset False _ = Nothing

View file

@ -1,7 +1,7 @@
{- Generates a NullSoft installer program for git-annex on Windows.
-
- git-annex should already be built by cabal, and ssh and rsync,
- as well as cygwin libraries, already installed.
- To build the installer, git-annex should already be built by cabal,
- and ssh and rsync, as well as cygwin libraries, already installed.
-
- This uses the Haskell nsis package (cabal install nsis)
- to generate a .nsi file, which is then used to produce
@ -19,49 +19,96 @@
{-# LANGUAGE OverloadedStrings #-}
import Development.NSIS
import System.FilePath
import Control.Monad
import System.Directory
import Data.String
main = writeFile "git-annex.nsi" $ nsis $ do
import Utility.Tmp
import Utility.CopyFile
import Utility.SafeCommand
import Build.BundledPrograms
main = do
withTmpDir "nsis-build" $ \tmpdir -> do
let gitannex = tmpdir </> "git-annex.exe"
mustSucceed "ln" [File "dist/build/git-annex/git-annex.exe", File gitannex]
writeFile nsifile $ makeInstaller gitannex
mustSucceed "C:\\Program Files\\NSIS\\makensis" [File nsifile]
removeFile nsifile -- left behind if makensis fails
where
nsifile = "git-annex.nsi"
mustSucceed cmd params = do
r <- boolSystem cmd params
case r of
True -> return ()
False -> error $ cmd ++ "failed"
installer :: FilePath
installer = "git-annex-installer.exe"
gitInstallDir :: Exp FilePath
gitInstallDir = fromString "$PROGRAMFILES\\Git\\cmd"
needGit :: Exp String
needGit = strConcat
[ fromString "You need git installed to use git-annex. Looking at "
, gitInstallDir
, fromString " , it seems to not be installed, "
, fromString "or may be installed in another location. "
, fromString "You can install git from http:////git-scm.com//"
]
makeInstaller :: FilePath -> String
makeInstaller gitannex = nsis $ do
name "git-annex"
outFile "git-annex-installer.exe"
installDir "$DESKTOP/git-annex"
outFile $ str installer
{- Installing into the same directory as git avoids needing to modify
- path myself, since the git installer already does it. -}
installDir gitInstallDir
requestExecutionLevel User
iff_ (fileExists "$WINDIR/git.exe")
(return ()) $ do
messageBox [MB_ABORTRETRYIGNORE]
"git does not seem to be installed. git-annex can't be used without git!"
iff (fileExists gitInstallDir)
(return ())
(alert needGit)
-- Pages to display
page Directory -- Pick where to install
page InstFiles -- Give a progress bar while installing
-- Groups of files to install
section "programs" [] $ do
setOutPath "$INSTDIR"
file [] "dist/build/git-annex/git-annex.exe"
fromcygwin "rsync.exe"
fromcygwin "ssh.exe"
fromcygwin "sha256.exe"
fromcygwin "sha1.exe"
fromcygwin "sha512.exe"
fromcygwin "sha384.exe"
section "DLLS" [] $ mapM_ fromcygwin
addfile gitannex
mapM_ addcygfile cygwinPrograms
section "DLLS" [] $ do
setOutPath "$INSTDIR"
[ "cygwin1.dll"
, "cygasn1-8.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"
]
mapM_ addcygfile cygwinDlls
where
fromcygwin f = file [] (str $ "/bin/" ++ f)
addfile f = file [] (str f)
addcygfile f = addfile $ "C:\\cygwin\\bin" </> f
cygwinPrograms :: [FilePath]
cygwinPrograms = map (\p -> p ++ ".exe") bundledPrograms
-- These are the dlls needed by Cygwin's rsync, ssh, etc.
cygwinDlls :: [FilePath]
cygwinDlls =
[ "cygwin1.dll"
, "cygasn1-8.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"
]

30
Build/Standalone.hs Normal file → Executable file
View file

@ -18,7 +18,7 @@ import System.Directory
import System.IO
import Control.Monad
import Data.List
import Build.SysConfig as SysConfig
import Build.BundledPrograms
import Utility.PartialPrelude
import Utility.Directory
@ -27,32 +27,6 @@ import Utility.Monad
import Utility.SafeCommand
import Utility.Path
{- Programs that git-annex uses, to include in the bundle.
-
- These may be just the command name, or the full path to it. -}
thirdpartyProgs :: [FilePath]
thirdpartyProgs = catMaybes
[ Just "git"
, Just "cp"
, Just "xargs"
, Just "gpg"
, Just "rsync"
, Just "ssh"
, Just "sh"
, ifset SysConfig.curl "curl"
, ifset SysConfig.wget "wget"
, ifset SysConfig.bup "bup"
, SysConfig.lsof
, SysConfig.sha1
, SysConfig.sha256
, SysConfig.sha512
, SysConfig.sha224
, SysConfig.sha384
]
where
ifset True s = Just s
ifset False _ = Nothing
progDir :: FilePath -> FilePath
#ifdef darwin_HOST_OS
progDir topdir = topdir
@ -76,5 +50,5 @@ main = getArgs >>= go
go (topdir:_) = do
let dir = progDir topdir
createDirectoryIfMissing True dir
installed <- forM thirdpartyProgs $ installProg dir
installed <- forM bundledPrograms $ installProg dir
writeFile "tmp/standalone-installed" (show installed)