module Debian.Package.Build.Command
( chdir, pwd
, createDirectoryIfMissing, renameDirectory, renameFile
, confirmPath
, unpackInDir, unpack, packInDir', packInDir
, cabalDebian', cabalDebian, dpkgParseChangeLog
, debuild, debi
, BuildMode (..)
, buildPackage, rebuild
, removeGhcLibrary
, withCurrentDir'
, readProcess', rawSystem', system'
) where
import Data.Maybe (fromMaybe)
import Control.Arrow ((&&&))
import Control.Monad.Trans.Class (lift)
import System.FilePath ((<.>), takeDirectory)
import qualified System.Directory as D
import qualified System.Process as Process
import System.Exit (ExitCode (..))
import Debian.Package.Data (Hackage, ghcLibraryBinPackages, ghcLibraryPackages, Source, parseChangeLog)
import Debian.Package.Build.Monad (Trace, traceCommand, traceOut, bracketTrace_)
splitCommand :: [a] -> (a, [a])
splitCommand = head &&& tail
handleExit :: String -> ExitCode -> IO ()
handleExit cmd = d where
d (ExitFailure rv) = fail $ unwords ["Failed with", show rv ++ ":", cmd]
d ExitSuccess = return ()
readProcess' :: [String] -> Trace String
readProcess' cmd0 = do
traceCommand $ unwords cmd0
lift $ do
let (cmd, args) = splitCommand cmd0
Process.readProcess cmd args ""
rawSystem' :: [String] -> Trace ()
rawSystem' cmd0 = do
traceCommand $ unwords cmd0
lift $ do
let (cmd, args) = splitCommand cmd0
Process.rawSystem cmd args >>= handleExit cmd
system' :: String -> Trace ()
system' cmd = do
traceCommand cmd
lift $ Process.system cmd >>= handleExit cmd
chdir :: String -> Trace ()
chdir dir = do
traceCommand $ "<setCurrentDirectory> " ++ dir
lift $ D.setCurrentDirectory dir
pwd :: IO String
pwd = D.getCurrentDirectory
createDirectoryIfMissing :: String -> Trace ()
createDirectoryIfMissing dir = do
traceCommand $ "<createDirectoryIfMissing True> " ++ dir
lift $ D.createDirectoryIfMissing True dir
renameMsg :: String -> String -> String -> String
renameMsg tag src dst = unwords ["<" ++ tag ++ "> ", src, "-->", dst]
renameDirectory :: String -> String -> Trace ()
renameDirectory src dst = do
traceCommand $ renameMsg "renameDirectory" src dst
lift $ D.renameDirectory src dst
renameFile :: String -> String -> Trace ()
renameFile src dst = do
traceCommand $ renameMsg "renameFile" src dst
lift $ D.renameFile src dst
confirmPath :: String -> Trace ()
confirmPath path =
readProcess' ["ls", "-ld", path] >>= traceOut
unpackInDir :: FilePath -> FilePath -> Trace ()
apath `unpackInDir` dir = do
lift . putStrLn $ unwords ["Unpacking", apath, "in", dir, "."]
rawSystem' ["tar", "-C", dir, "-zxf", apath]
unpack :: FilePath -> Trace ()
unpack apath = apath `unpackInDir` takeDirectory apath
packInDir' :: FilePath -> FilePath -> FilePath -> Trace ()
packInDir' pdir apath wdir = do
lift . putStrLn $ unwords ["Packing", pdir, "in", wdir, "into", apath, "."]
rawSystem' ["tar", "-C", wdir, "-zcf", apath, pdir]
packInDir :: FilePath -> FilePath -> Trace ()
pdir `packInDir` wdir =
packInDir' pdir (pdir <.> "tar" <.> "gz") wdir
withCurrentDir' :: FilePath -> Trace a -> Trace a
withCurrentDir' dir act = do
saveDir <- lift pwd
bracketTrace_
(chdir dir)
(chdir saveDir)
act
cabalDebian' :: Maybe String -> Trace ()
cabalDebian' mayRev =
rawSystem'
[ "cabal-debian"
, "--debianize"
, "--quilt"
, "--revision=" ++ fromMaybe "1~autogen1" mayRev
]
cabalDebian :: FilePath -> Maybe String -> Trace ()
cabalDebian dir = withCurrentDir' dir . cabalDebian'
dpkgParseChangeLog :: FilePath -> Trace Source
dpkgParseChangeLog cpath = do
str <- readProcess' ["dpkg-parsechangelog", "-l" ++ cpath]
maybe (fail $ "parseChangeLog: failed: " ++ str) return
$ parseChangeLog str
run :: String -> [String] -> Trace ()
run cmd = rawSystem' . (cmd :)
debuild' :: [String] -> Trace ()
debuild' = run "debuild"
debuild :: FilePath -> [String] -> Trace ()
debuild dir = withCurrentDir' dir . debuild'
debi :: FilePath -> [String] -> Trace ()
debi dir = withCurrentDir' dir . rawSystem' . (["sudo", "debi"] ++)
data BuildMode = All | Bin
buildPackage :: FilePath -> BuildMode -> [String] -> Trace ()
buildPackage dir mode opts = do
let modeOpt All = []
modeOpt Bin = ["-B"]
debuild dir $ ["-uc", "-us"] ++ modeOpt mode ++ opts
rebuild :: FilePath -> BuildMode -> [String] -> Trace ()
rebuild dir mode opts = do
debuild dir ["clean"]
buildPackage dir mode opts
removeGhcLibrary :: BuildMode -> Hackage -> Trace ()
removeGhcLibrary mode hkg = do
let pkgs All = ghcLibraryBinPackages
pkgs Bin = ghcLibraryPackages
system' $ unwords ["yes '' |", "sudo apt-get remove", unwords $ pkgs mode hkg, "|| true"]