git-annex/Build/NullSoftInstaller.hs

204 lines
5.9 KiB
Haskell
Raw Normal View History

2013-05-14 22:01:45 +00:00
{- Generates a NullSoft installer program for git-annex on Windows.
-
2013-05-15 00:59:14 +00:00
- To build the installer, git-annex should already be built by cabal,
- and ssh and rsync, as well as cygwin libraries, already installed.
2013-05-14 21:15:02 +00:00
-
- This uses the Haskell nsis package (cabal install nsis)
- to generate a .nsi file, which is then used to produce
- git-annex-installer.exe
-
- The installer includes git-annex, and utilities it uses, with the
- exception of git. The user needs to install git separately,
- and the installer checks for that.
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
2013-05-14 22:01:45 +00:00
-}
{-# LANGUAGE OverloadedStrings #-}
import Development.NSIS
import System.Directory
2013-05-15 00:59:14 +00:00
import System.FilePath
import Control.Monad
import Data.String
import Data.Maybe
2013-05-14 22:01:45 +00:00
2013-05-15 00:59:14 +00:00
import Utility.Tmp
import Utility.Path
2013-05-15 00:59:14 +00:00
import Utility.CopyFile
import Utility.SafeCommand
import Build.BundledPrograms
main = do
withTmpDir "nsis-build" $ \tmpdir -> do
2013-05-17 00:41:20 +00:00
let gitannex = tmpdir </> gitannexprogram
2013-05-15 00:59:14 +00:00
mustSucceed "ln" [File "dist/build/git-annex/git-annex.exe", File gitannex]
2013-05-17 00:41:20 +00:00
let license = tmpdir </> licensefile
2013-05-17 00:04:05 +00:00
mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"]
extrabins <- forM (cygwinPrograms ++ cygwinDlls) $ \f -> do
p <- searchPath f
when (isNothing p) $
print ("unable to find in PATH", f)
return p
webappscript <- vbsLauncher tmpdir "git-annex-webapp" "git-annex webapp"
autostartscript <- vbsLauncher tmpdir "git-annex-autostart" "git annex assistant --autostart"
writeFile nsifile $ makeInstaller gitannex license
(catMaybes extrabins)
[ webappscript, autostartscript ]
2013-05-17 18:06:47 +00:00
mustSucceed "makensis" [File nsifile]
2013-05-15 00:59:14 +00:00
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 ()
2013-05-17 00:04:05 +00:00
False -> error $ cmd ++ " failed"
2013-05-15 00:59:14 +00:00
{- Generates a .vbs launcher which runs a command without any visible DOS
- box. -}
vbsLauncher :: FilePath -> String -> String -> IO String
vbsLauncher tmpdir basename cmd = do
let f = tmpdir </> basename ++ ".vbs"
writeFile f $ unlines
[ "Set objshell=CreateObject(\"Wscript.Shell\")"
, "objShell.Run(\"" ++ cmd ++ "\"), 0, False"
]
return f
2013-05-17 00:41:20 +00:00
gitannexprogram :: FilePath
gitannexprogram = "git-annex.exe"
licensefile :: FilePath
licensefile = "git-annex-licenses.txt"
2013-05-15 00:59:14 +00:00
installer :: FilePath
installer = "git-annex-installer.exe"
2013-05-17 00:41:20 +00:00
uninstaller :: FilePath
uninstaller = "git-annex-uninstall.exe"
2013-05-15 00:59:14 +00:00
gitInstallDir :: Exp FilePath
gitInstallDir = fromString "$PROGRAMFILES\\Git"
2013-05-15 00:59:14 +00:00
2013-12-10 04:37:06 +00:00
startMenuItem :: Exp FilePath
startMenuItem = "$SMPROGRAMS/git-annex.lnk"
autoStartItem :: Exp FilePath
autoStartItem = "$SMSTARTUP/git-annex-autostart.lnk"
2013-05-15 00:59:14 +00:00
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 -> FilePath -> [FilePath] -> [FilePath] -> String
makeInstaller gitannex license extrabins launchers = nsis $ do
2013-05-14 22:01:45 +00:00
name "git-annex"
2013-05-15 00:59:14 +00:00
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
2013-12-10 04:32:08 +00:00
requestExecutionLevel Admin
2013-05-15 00:59:14 +00:00
iff (fileExists gitInstallDir)
(return ())
(alert needGit)
2013-05-14 22:01:45 +00:00
-- Pages to display
page Directory -- Pick where to install
2013-05-17 00:32:59 +00:00
page (License license)
2013-05-14 22:01:45 +00:00
page InstFiles -- Give a progress bar while installing
2013-12-10 04:13:15 +00:00
-- Start menu shortcut
2013-12-10 04:17:20 +00:00
Development.NSIS.createDirectory "$SMPROGRAMS"
2013-12-10 04:37:06 +00:00
createShortcut startMenuItem
[ Target "wscript.exe"
2014-06-17 18:05:31 +00:00
, Parameters "\"$INSTDIR/git-annex-webapp.vbs\""
2014-06-17 18:28:44 +00:00
, StartOptions "SW_SHOWNORMAL"
, IconFile "$INSTDIR/cmd/git-annex.exe"
2013-12-10 04:13:15 +00:00
, IconIndex 2
, KeyboardShortcut "ALT|CONTROL|a"
2013-12-10 04:26:14 +00:00
, Description "git-annex webapp"
2013-12-10 04:13:15 +00:00
]
createShortcut autoStartItem
[ Target "wscript.exe"
2014-06-17 18:05:31 +00:00
, Parameters "\"$INSTDIR/git-annex-autostart.vbs\""
2014-06-17 18:28:44 +00:00
, StartOptions "SW_SHOWNORMAL"
, IconFile "$INSTDIR/cmd/git-annex.exe"
, IconIndex 2
, Description "git-annex autostart"
]
section "bins" [] $ do
setOutPath "$INSTDIR\\bin"
mapM_ addfile extrabins
section "cmd" [] $ do
setOutPath "$INSTDIR\\cmd"
addfile gitannex
section "meta" [] $ do
setOutPath "$INSTDIR"
2013-05-17 00:00:31 +00:00
addfile license
mapM_ addfile launchers
2013-05-17 00:41:20 +00:00
writeUninstaller $ str uninstaller
2013-12-10 04:37:06 +00:00
uninstall $ do
2013-12-10 04:37:58 +00:00
delete [RebootOK] $ startMenuItem
delete [RebootOK] $ autoStartItem
removefilesFrom "$INSTDIR/bin" extrabins
removefilesFrom "$INSTDIR/cmd" [gitannex]
removefilesFrom "$INSTDIR" $
launchers ++
[ license
2013-05-17 00:41:20 +00:00
, uninstaller
]
2013-05-14 22:01:45 +00:00
where
2013-05-15 00:59:14 +00:00
addfile f = file [] (str f)
removefilesFrom d = mapM_ (\f -> delete [RebootOK] $ fromString $ d ++ "/" ++ takeFileName f)
2013-05-15 00:59:14 +00:00
cygwinPrograms :: [FilePath]
cygwinPrograms = map (\p -> p ++ ".exe") bundledPrograms
-- These are the dlls needed by Cygwin's rsync, ssh, etc.
2013-12-11 15:49:35 +00:00
-- TODO: Use ldd (available in cygwin) to automatically find all
-- needed libs.
2013-05-15 00:59:14 +00:00
cygwinDlls :: [FilePath]
cygwinDlls =
[ "cygwin1.dll"
, "cygasn1-8.dll"
, "cygattr-1.dll"
2013-05-15 00:59:14 +00:00
, "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"
2013-12-11 15:10:30 +00:00
, "cygidn-11.dll"
, "libcurl-4.dll"
2013-12-11 15:23:39 +00:00
, "cyggnutls-26.dll"
, "libcrypto.dll"
2013-12-11 15:34:22 +00:00
, "libssl.dll"
, "cyggcrypt-11.dll"
2013-12-11 15:44:14 +00:00
, "cyggpg-error-0.dll"
2013-12-11 15:49:35 +00:00
, "cygp11-kit-0.dll"
, "cygtasn1-3.dll"
2013-12-11 15:53:56 +00:00
, "cygffi-6.dll"
, "cygbz2-1.dll"
, "cygreadline7.dll"
, "cygncursesw-10.dll"
, "cygusb0.dll"
2013-05-15 00:59:14 +00:00
]