don't hardcode path to cygwin stuff, look for it in PATH

This commit is contained in:
Joey Hess 2013-05-17 14:19:08 -04:00
parent b1b332592f
commit c2e279b6ce
2 changed files with 15 additions and 11 deletions

View file

@ -19,12 +19,14 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
import Development.NSIS import Development.NSIS
import System.Directory
import System.FilePath import System.FilePath
import Control.Monad import Control.Monad
import System.Directory
import Data.String import Data.String
import Data.Maybe
import Utility.Tmp import Utility.Tmp
import Utility.Path
import Utility.CopyFile import Utility.CopyFile
import Utility.SafeCommand import Utility.SafeCommand
import Build.BundledPrograms import Build.BundledPrograms
@ -35,7 +37,13 @@ main = do
mustSucceed "ln" [File "dist/build/git-annex/git-annex.exe", File gitannex] mustSucceed "ln" [File "dist/build/git-annex/git-annex.exe", File gitannex]
let license = tmpdir </> licensefile let license = tmpdir </> licensefile
mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"] mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"]
writeFile nsifile $ makeInstaller gitannex license extrafiles <- forM (cygwinPrograms ++ cygwinDlls) $ \f ->
p <- searchPath f
when (isNothing p) $
print ("unable to find in PATH", f)
return p
writeFile nsifile $ makeInstaller gitannex license $
catMaybes extrafiles
mustSucceed "makensis" [File nsifile] mustSucceed "makensis" [File nsifile]
removeFile nsifile -- left behind if makensis fails removeFile nsifile -- left behind if makensis fails
where where
@ -70,8 +78,8 @@ needGit = strConcat
, fromString "You can install git from http:////git-scm.com//" , fromString "You can install git from http:////git-scm.com//"
] ]
makeInstaller :: FilePath -> FilePath -> String makeInstaller :: FilePath -> FilePath -> [FilePath] -> String
makeInstaller gitannex license = nsis $ do makeInstaller gitannex license extrafiles = nsis $ do
name "git-annex" name "git-annex"
outFile $ str installer outFile $ str installer
{- Installing into the same directory as git avoids needing to modify {- Installing into the same directory as git avoids needing to modify
@ -88,15 +96,12 @@ makeInstaller gitannex license = nsis $ do
page (License license) page (License license)
page InstFiles -- Give a progress bar while installing page InstFiles -- Give a progress bar while installing
-- Groups of files to install -- Groups of files to install
section "programs" [] $ do section "main" [] $ do
setOutPath "$INSTDIR" setOutPath "$INSTDIR"
addfile gitannex addfile gitannex
addfile license addfile license
mapM_ addcygfile cygwinPrograms mapM_ addfile extrafiles
writeUninstaller $ str uninstaller writeUninstaller $ str uninstaller
section "libraries" [] $ do
setOutPath "$INSTDIR"
mapM_ addcygfile cygwinDlls
uninstall $ uninstall $
mapM_ (\f -> delete [RebootOK] $ fromString $ "$INSTDIR/" ++ f) $ mapM_ (\f -> delete [RebootOK] $ fromString $ "$INSTDIR/" ++ f) $
[ gitannexprogram [ gitannexprogram
@ -105,7 +110,6 @@ makeInstaller gitannex license = nsis $ do
] ++ cygwinPrograms ++ cygwinDlls ] ++ cygwinPrograms ++ cygwinDlls
where where
addfile f = file [] (str f) addfile f = file [] (str f)
addcygfile f = addfile $ "C:\\cygwin\\bin" </> f
cygwinPrograms :: [FilePath] cygwinPrograms :: [FilePath]
cygwinPrograms = map (\p -> p ++ ".exe") bundledPrograms cygwinPrograms = map (\p -> p ++ ".exe") bundledPrograms

View file

@ -39,4 +39,4 @@ incygwin cabal build
# Build the installer # Build the installer
cabal install nsis cabal install nsis
ghc --make Build/NullSoftInstaller.hs ghc --make Build/NullSoftInstaller.hs
Build/NullSoftInstaller.exe incygwin Build/NullSoftInstaller.exe