add whenM and unlessM
Just more golfing.. I am pretty sure something in a library somewhere can do this, but I have been unable to find it.
This commit is contained in:
parent
75a3f5027f
commit
c91929f693
16 changed files with 60 additions and 63 deletions
|
@ -7,8 +7,6 @@
|
||||||
|
|
||||||
module Command.Drop where
|
module Command.Drop where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
import qualified Backend
|
import qualified Backend
|
||||||
import LocationLog
|
import LocationLog
|
||||||
|
@ -46,7 +44,6 @@ perform key backend numcopies = do
|
||||||
|
|
||||||
cleanup :: Key -> CommandCleanup
|
cleanup :: Key -> CommandCleanup
|
||||||
cleanup key = do
|
cleanup key = do
|
||||||
inannex <- inAnnex key
|
whenM (inAnnex key) $ removeAnnex key
|
||||||
when inannex $ removeAnnex key
|
|
||||||
logStatus key ValueMissing
|
logStatus key ValueMissing
|
||||||
return True
|
return True
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.DropUnused where
|
module Command.DropUnused where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
@ -24,6 +23,7 @@ import qualified Remote
|
||||||
import qualified GitRepo as Git
|
import qualified GitRepo as Git
|
||||||
import Backend
|
import Backend
|
||||||
import Key
|
import Key
|
||||||
|
import Utility
|
||||||
|
|
||||||
type UnusedMap = M.Map String Key
|
type UnusedMap = M.Map String Key
|
||||||
|
|
||||||
|
@ -72,8 +72,7 @@ performOther :: (Git.Repo -> Key -> FilePath) -> Key -> CommandPerform
|
||||||
performOther filespec key = do
|
performOther filespec key = do
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
let f = filespec g key
|
let f = filespec g key
|
||||||
e <- liftIO $ doesFileExist f
|
liftIO $ whenM (doesFileExist f) $ removeFile f
|
||||||
when e $ liftIO $ removeFile f
|
|
||||||
next $ return True
|
next $ return True
|
||||||
|
|
||||||
readUnusedLog :: FilePath -> Annex UnusedMap
|
readUnusedLog :: FilePath -> Annex UnusedMap
|
||||||
|
|
|
@ -7,11 +7,11 @@
|
||||||
|
|
||||||
module Command.Find where
|
module Command.Find where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
import Content
|
import Content
|
||||||
|
import Utility
|
||||||
|
|
||||||
command :: [Command]
|
command :: [Command]
|
||||||
command = [repoCommand "find" (paramOptional $ paramRepeating paramPath) seek
|
command = [repoCommand "find" (paramOptional $ paramRepeating paramPath) seek
|
||||||
|
@ -23,6 +23,5 @@ seek = [withFilesInGit start]
|
||||||
{- Output a list of files. -}
|
{- Output a list of files. -}
|
||||||
start :: CommandStartString
|
start :: CommandStartString
|
||||||
start file = isAnnexed file $ \(key, _) -> do
|
start file = isAnnexed file $ \(key, _) -> do
|
||||||
exists <- inAnnex key
|
whenM (inAnnex key) $ liftIO $ putStrLn file
|
||||||
when exists $ liftIO $ putStrLn file
|
|
||||||
stop
|
stop
|
||||||
|
|
|
@ -8,7 +8,6 @@
|
||||||
module Command.Migrate where
|
module Command.Migrate where
|
||||||
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import Control.Monad (unless, when)
|
|
||||||
import System.Posix.Files
|
import System.Posix.Files
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
@ -20,6 +19,7 @@ import Locations
|
||||||
import Types
|
import Types
|
||||||
import Content
|
import Content
|
||||||
import Messages
|
import Messages
|
||||||
|
import Utility
|
||||||
import qualified Command.Add
|
import qualified Command.Add
|
||||||
|
|
||||||
command :: [Command]
|
command :: [Command]
|
||||||
|
@ -63,9 +63,7 @@ perform file oldkey newbackend = do
|
||||||
ok <- getViaTmpUnchecked newkey $ \t -> do
|
ok <- getViaTmpUnchecked newkey $ \t -> do
|
||||||
-- Make a hard link to the old backend's
|
-- Make a hard link to the old backend's
|
||||||
-- cached key, to avoid wasting disk space.
|
-- cached key, to avoid wasting disk space.
|
||||||
liftIO $ do
|
liftIO $ unlessM (doesFileExist t) $ createLink src t
|
||||||
exists <- doesFileExist t
|
|
||||||
unless exists $ createLink src t
|
|
||||||
return True
|
return True
|
||||||
if ok
|
if ok
|
||||||
then do
|
then do
|
||||||
|
@ -74,6 +72,4 @@ perform file oldkey newbackend = do
|
||||||
next $ Command.Add.cleanup file newkey
|
next $ Command.Add.cleanup file newkey
|
||||||
else stop
|
else stop
|
||||||
where
|
where
|
||||||
cleantmp t = do
|
cleantmp t = whenM (doesFileExist t) $ removeFile t
|
||||||
exists <- doesFileExist t
|
|
||||||
when exists $ removeFile t
|
|
||||||
|
|
|
@ -7,13 +7,13 @@
|
||||||
|
|
||||||
module Command.RecvKey where
|
module Command.RecvKey where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
import CmdLine
|
import CmdLine
|
||||||
import Content
|
import Content
|
||||||
|
import Utility
|
||||||
import RsyncFile
|
import RsyncFile
|
||||||
|
|
||||||
command :: [Command]
|
command :: [Command]
|
||||||
|
@ -25,9 +25,7 @@ seek = [withKeys start]
|
||||||
|
|
||||||
start :: CommandStartKey
|
start :: CommandStartKey
|
||||||
start key = do
|
start key = do
|
||||||
present <- inAnnex key
|
whenM (inAnnex key) $ error "key is already present in annex"
|
||||||
when present $
|
|
||||||
error "key is already present in annex"
|
|
||||||
|
|
||||||
ok <- getViaTmp key (liftIO . rsyncServerReceive)
|
ok <- getViaTmp key (liftIO . rsyncServerReceive)
|
||||||
if ok
|
if ok
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.SendKey where
|
module Command.SendKey where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
|
||||||
|
@ -15,6 +14,7 @@ import Locations
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import Command
|
import Command
|
||||||
import Content
|
import Content
|
||||||
|
import Utility
|
||||||
import RsyncFile
|
import RsyncFile
|
||||||
|
|
||||||
command :: [Command]
|
command :: [Command]
|
||||||
|
@ -26,9 +26,8 @@ seek = [withKeys start]
|
||||||
|
|
||||||
start :: CommandStartKey
|
start :: CommandStartKey
|
||||||
start key = do
|
start key = do
|
||||||
present <- inAnnex key
|
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
let file = gitAnnexLocation g key
|
let file = gitAnnexLocation g key
|
||||||
when present $
|
whenM (inAnnex key) $
|
||||||
liftIO $ rsyncServerSend file
|
liftIO $ rsyncServerSend file -- does not return
|
||||||
liftIO exitFailure
|
liftIO exitFailure
|
||||||
|
|
|
@ -8,7 +8,6 @@
|
||||||
module Command.Uninit where
|
module Command.Uninit where
|
||||||
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import Control.Monad (when)
|
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
@ -44,8 +43,7 @@ perform = do
|
||||||
gitPreCommitHookUnWrite :: Git.Repo -> Annex ()
|
gitPreCommitHookUnWrite :: Git.Repo -> Annex ()
|
||||||
gitPreCommitHookUnWrite repo = do
|
gitPreCommitHookUnWrite repo = do
|
||||||
let hook = Command.Init.preCommitHook repo
|
let hook = Command.Init.preCommitHook repo
|
||||||
hookexists <- liftIO $ doesFileExist hook
|
whenM (liftIO $ doesFileExist hook) $ do
|
||||||
when hookexists $ do
|
|
||||||
c <- liftIO $ readFile hook
|
c <- liftIO $ readFile hook
|
||||||
if c == Command.Init.preCommitScript
|
if c == Command.Init.preCommitScript
|
||||||
then liftIO $ removeFile hook
|
then liftIO $ removeFile hook
|
||||||
|
@ -56,8 +54,7 @@ gitPreCommitHookUnWrite repo = do
|
||||||
gitAttributesUnWrite :: Git.Repo -> IO ()
|
gitAttributesUnWrite :: Git.Repo -> IO ()
|
||||||
gitAttributesUnWrite repo = do
|
gitAttributesUnWrite repo = do
|
||||||
let attributes = Git.attributes repo
|
let attributes = Git.attributes repo
|
||||||
attrexists <- doesFileExist attributes
|
whenM (doesFileExist attributes) $ do
|
||||||
when attrexists $ do
|
|
||||||
c <- readFileStrict attributes
|
c <- readFileStrict attributes
|
||||||
safeWriteFile attributes $ unlines $
|
safeWriteFile attributes $ unlines $
|
||||||
filter (\l -> not $ l `elem` Command.Init.attrLines) $ lines c
|
filter (\l -> not $ l `elem` Command.Init.attrLines) $ lines c
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module Command.Unlock where
|
module Command.Unlock where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import System.Directory hiding (copyFile)
|
import System.Directory hiding (copyFile)
|
||||||
|
|
||||||
|
@ -19,6 +18,7 @@ import Messages
|
||||||
import Locations
|
import Locations
|
||||||
import Content
|
import Content
|
||||||
import CopyFile
|
import CopyFile
|
||||||
|
import Utility
|
||||||
|
|
||||||
command :: [Command]
|
command :: [Command]
|
||||||
command =
|
command =
|
||||||
|
@ -38,9 +38,7 @@ start file = isAnnexed file $ \(key, _) -> do
|
||||||
|
|
||||||
perform :: FilePath -> Key -> CommandPerform
|
perform :: FilePath -> Key -> CommandPerform
|
||||||
perform dest key = do
|
perform dest key = do
|
||||||
inbackend <- Backend.hasKey key
|
unlessM (Backend.hasKey key) $ error "content not present"
|
||||||
when (not inbackend) $
|
|
||||||
error "content not present"
|
|
||||||
|
|
||||||
checkDiskSpace key
|
checkDiskSpace key
|
||||||
|
|
||||||
|
|
|
@ -134,8 +134,7 @@ withTmp key action = do
|
||||||
let tmp = gitAnnexTmpLocation g key
|
let tmp = gitAnnexTmpLocation g key
|
||||||
liftIO $ createDirectoryIfMissing True (parentDir tmp)
|
liftIO $ createDirectoryIfMissing True (parentDir tmp)
|
||||||
res <- action tmp
|
res <- action tmp
|
||||||
tmp_exists <- liftIO $ doesFileExist tmp
|
liftIO $ whenM (doesFileExist tmp) $ liftIO $ removeFile tmp
|
||||||
when tmp_exists $ liftIO $ removeFile tmp
|
|
||||||
return res
|
return res
|
||||||
|
|
||||||
{- Checks that there is disk space available to store a given key,
|
{- Checks that there is disk space available to store a given key,
|
||||||
|
@ -160,8 +159,7 @@ checkDiskSpace' adjustment key = do
|
||||||
megabyte :: Integer
|
megabyte :: Integer
|
||||||
megabyte = 1000000
|
megabyte = 1000000
|
||||||
needmorespace n = do
|
needmorespace n = do
|
||||||
force <- Annex.getState Annex.force
|
unlessM (Annex.getState Annex.force) $
|
||||||
unless force $
|
|
||||||
error $ "not enough free space, need " ++
|
error $ "not enough free space, need " ++
|
||||||
roughSize storageUnits True n ++
|
roughSize storageUnits True n ++
|
||||||
" more (use --force to override this check or adjust annex.diskreserve)"
|
" more (use --force to override this check or adjust annex.diskreserve)"
|
||||||
|
|
|
@ -7,7 +7,6 @@
|
||||||
|
|
||||||
module CopyFile (copyFile) where
|
module CopyFile (copyFile) where
|
||||||
|
|
||||||
import Control.Monad (when)
|
|
||||||
import System.Directory (doesFileExist, removeFile)
|
import System.Directory (doesFileExist, removeFile)
|
||||||
|
|
||||||
import Utility
|
import Utility
|
||||||
|
@ -17,8 +16,7 @@ import qualified SysConfig
|
||||||
- and because this allows easy access to features like cp --reflink. -}
|
- and because this allows easy access to features like cp --reflink. -}
|
||||||
copyFile :: FilePath -> FilePath -> IO Bool
|
copyFile :: FilePath -> FilePath -> IO Bool
|
||||||
copyFile src dest = do
|
copyFile src dest = do
|
||||||
e <- doesFileExist dest
|
whenM (doesFileExist dest) $
|
||||||
when e $
|
|
||||||
removeFile dest
|
removeFile dest
|
||||||
boolSystem "cp" [params, File src, File dest]
|
boolSystem "cp" [params, File src, File dest]
|
||||||
where
|
where
|
||||||
|
|
|
@ -329,9 +329,9 @@ gitCommandLine repo _ = assertLocal repo $ error "internal"
|
||||||
|
|
||||||
{- Runs git in the specified repo, throwing an error if it fails. -}
|
{- Runs git in the specified repo, throwing an error if it fails. -}
|
||||||
run :: Repo -> String -> [CommandParam] -> IO ()
|
run :: Repo -> String -> [CommandParam] -> IO ()
|
||||||
run repo subcommand params = assertLocal repo $ do
|
run repo subcommand params = assertLocal repo $
|
||||||
ok <- boolSystem "git" (gitCommandLine repo ((Param subcommand):params))
|
boolSystem "git" (gitCommandLine repo ((Param subcommand):params))
|
||||||
unless ok $ error $ "git " ++ show params ++ " failed"
|
<|> error $ "git " ++ show params ++ " failed"
|
||||||
|
|
||||||
{- Runs a git subcommand and returns it output, lazily.
|
{- Runs a git subcommand and returns it output, lazily.
|
||||||
-
|
-
|
||||||
|
|
|
@ -11,7 +11,7 @@ import qualified Data.ByteString.Lazy.Char8 as L
|
||||||
import IO
|
import IO
|
||||||
import Control.Exception.Extensible (IOException)
|
import Control.Exception.Extensible (IOException)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Control.Monad (unless, when)
|
import Control.Monad (when)
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import System.Process
|
import System.Process
|
||||||
import System.Exit
|
import System.Exit
|
||||||
|
@ -75,8 +75,7 @@ bupSetup u c = do
|
||||||
-- bup init will create the repository.
|
-- bup init will create the repository.
|
||||||
-- (If the repository already exists, bup init again appears safe.)
|
-- (If the repository already exists, bup init again appears safe.)
|
||||||
showNote "bup init"
|
showNote "bup init"
|
||||||
ok <- bup "init" buprepo []
|
bup "init" buprepo [] <|> error "bup init failed"
|
||||||
unless ok $ error "bup init failed"
|
|
||||||
|
|
||||||
storeBupUUID u buprepo
|
storeBupUUID u buprepo
|
||||||
|
|
||||||
|
@ -172,9 +171,9 @@ storeBupUUID u buprepo = do
|
||||||
if Git.repoIsUrl r
|
if Git.repoIsUrl r
|
||||||
then do
|
then do
|
||||||
showNote "storing uuid"
|
showNote "storing uuid"
|
||||||
ok <- onBupRemote r boolSystem "git"
|
onBupRemote r boolSystem "git"
|
||||||
[Params $ "config annex.uuid " ++ u]
|
[Params $ "config annex.uuid " ++ u]
|
||||||
unless ok $ do error "ssh failed"
|
<|> error "ssh failed"
|
||||||
else liftIO $ do
|
else liftIO $ do
|
||||||
r' <- Git.configRead r
|
r' <- Git.configRead r
|
||||||
let olduuid = Git.configGet r' "annex.uuid" ""
|
let olduuid = Git.configGet r' "annex.uuid" ""
|
||||||
|
|
|
@ -62,8 +62,8 @@ directorySetup u c = do
|
||||||
-- verify configuration is sane
|
-- verify configuration is sane
|
||||||
let dir = maybe (error "Specify directory=") id $
|
let dir = maybe (error "Specify directory=") id $
|
||||||
M.lookup "directory" c
|
M.lookup "directory" c
|
||||||
e <- liftIO $ doesDirectoryExist dir
|
liftIO $ doesDirectoryExist dir
|
||||||
when (not e) $ error $ "Directory does not exist: " ++ dir
|
<|> error $ "Directory does not exist: " ++ dir
|
||||||
c' <- encryptionSetup c
|
c' <- encryptionSetup c
|
||||||
|
|
||||||
-- The directory is stored in git config, not in this remote's
|
-- The directory is stored in git config, not in this remote's
|
||||||
|
|
|
@ -10,7 +10,7 @@ module Remote.Rsync (remote) where
|
||||||
import qualified Data.ByteString.Lazy.Char8 as L
|
import qualified Data.ByteString.Lazy.Char8 as L
|
||||||
import Control.Exception.Extensible (IOException)
|
import Control.Exception.Extensible (IOException)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Control.Monad.State (liftIO, when)
|
import Control.Monad.State (liftIO)
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Posix.Files
|
import System.Posix.Files
|
||||||
|
@ -168,9 +168,8 @@ withRsyncScratchDir a = do
|
||||||
nuke tmp
|
nuke tmp
|
||||||
return res
|
return res
|
||||||
where
|
where
|
||||||
nuke d = liftIO $ do
|
nuke d = liftIO $
|
||||||
e <- doesDirectoryExist d
|
doesDirectoryExist d <&> removeDirectoryRecursive d
|
||||||
when e $ liftIO $ removeDirectoryRecursive d
|
|
||||||
|
|
||||||
rsyncRemote :: RsyncOpts -> [CommandParam] -> Annex Bool
|
rsyncRemote :: RsyncOpts -> [CommandParam] -> Annex Bool
|
||||||
rsyncRemote o params = do
|
rsyncRemote o params = do
|
||||||
|
|
32
Utility.hs
32
Utility.hs
|
@ -1,4 +1,4 @@
|
||||||
{- git-annex utility functions
|
{- general purpose utility functions
|
||||||
-
|
-
|
||||||
- Copyright 2010-2011 Joey Hess <joey@kitenet.net>
|
- Copyright 2010-2011 Joey Hess <joey@kitenet.net>
|
||||||
-
|
-
|
||||||
|
@ -26,6 +26,10 @@ module Utility (
|
||||||
dirContents,
|
dirContents,
|
||||||
myHomeDir,
|
myHomeDir,
|
||||||
catchBool,
|
catchBool,
|
||||||
|
whenM,
|
||||||
|
(<&>),
|
||||||
|
unlessM,
|
||||||
|
(<|>),
|
||||||
|
|
||||||
prop_idempotent_shellEscape,
|
prop_idempotent_shellEscape,
|
||||||
prop_idempotent_shellEscape_multiword,
|
prop_idempotent_shellEscape_multiword,
|
||||||
|
@ -46,7 +50,8 @@ import System.FilePath
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Foreign (complement)
|
import Foreign (complement)
|
||||||
import Data.List
|
import Data.List
|
||||||
import Control.Monad (liftM2)
|
import Data.Maybe
|
||||||
|
import Control.Monad (liftM2, when, unless)
|
||||||
|
|
||||||
{- A type for parameters passed to a shell command. A command can
|
{- A type for parameters passed to a shell command. A command can
|
||||||
- be passed either some Params (multiple parameters can be included,
|
- be passed either some Params (multiple parameters can be included,
|
||||||
|
@ -110,7 +115,7 @@ shellEscape f = "'" ++ escaped ++ "'"
|
||||||
{- Unescapes a set of shellEscaped words or filenames. -}
|
{- Unescapes a set of shellEscaped words or filenames. -}
|
||||||
shellUnEscape :: String -> [String]
|
shellUnEscape :: String -> [String]
|
||||||
shellUnEscape [] = []
|
shellUnEscape [] = []
|
||||||
shellUnEscape s = word:(shellUnEscape rest)
|
shellUnEscape s = word : shellUnEscape rest
|
||||||
where
|
where
|
||||||
(word, rest) = findword "" s
|
(word, rest) = findword "" s
|
||||||
findword w [] = (w, "")
|
findword w [] = (w, "")
|
||||||
|
@ -165,7 +170,7 @@ prop_parentDir_basics dir
|
||||||
dirContains :: FilePath -> FilePath -> Bool
|
dirContains :: FilePath -> FilePath -> Bool
|
||||||
dirContains a b = a == b || a' == b' || (a'++"/") `isPrefixOf` b'
|
dirContains a b = a == b || a' == b' || (a'++"/") `isPrefixOf` b'
|
||||||
where
|
where
|
||||||
norm p = maybe "" id $ absNormPath p "."
|
norm p = fromMaybe "" $ absNormPath p "."
|
||||||
a' = norm a
|
a' = norm a
|
||||||
b' = norm b
|
b' = norm b
|
||||||
|
|
||||||
|
@ -178,7 +183,7 @@ absPath file = do
|
||||||
{- Converts a filename into a normalized, absolute path
|
{- Converts a filename into a normalized, absolute path
|
||||||
- from the specified cwd. -}
|
- from the specified cwd. -}
|
||||||
absPathFrom :: FilePath -> FilePath -> FilePath
|
absPathFrom :: FilePath -> FilePath -> FilePath
|
||||||
absPathFrom cwd file = maybe bad id $ absNormPath cwd file
|
absPathFrom cwd file = fromMaybe bad $ absNormPath cwd file
|
||||||
where
|
where
|
||||||
bad = error $ "unable to normalize " ++ file
|
bad = error $ "unable to normalize " ++ file
|
||||||
|
|
||||||
|
@ -258,3 +263,20 @@ myHomeDir = do
|
||||||
{- Catches IO errors and returns a Bool -}
|
{- Catches IO errors and returns a Bool -}
|
||||||
catchBool :: IO Bool -> IO Bool
|
catchBool :: IO Bool -> IO Bool
|
||||||
catchBool = flip catch (const $ return False)
|
catchBool = flip catch (const $ return False)
|
||||||
|
|
||||||
|
{- when with a monadic conditional -}
|
||||||
|
whenM :: Monad m => m Bool -> m () -> m ()
|
||||||
|
whenM c a = c >>= flip when a
|
||||||
|
|
||||||
|
unlessM :: Monad m => m Bool -> m () -> m ()
|
||||||
|
unlessM c a = c >>= flip unless a
|
||||||
|
|
||||||
|
(<&>) :: Monad m => m Bool -> m () -> m ()
|
||||||
|
(<&>) = whenM
|
||||||
|
|
||||||
|
(<|>) :: Monad m => m Bool -> m () -> m ()
|
||||||
|
(<|>) = unlessM
|
||||||
|
|
||||||
|
-- low fixity allows eg, foo bar <|> error $ "failed " ++ meep
|
||||||
|
infixr 0 <&>
|
||||||
|
infixr 0 <|>
|
||||||
|
|
|
@ -6,7 +6,6 @@
|
||||||
-}
|
-}
|
||||||
|
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import Control.Monad (when)
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
import qualified GitRepo as Git
|
import qualified GitRepo as Git
|
||||||
|
@ -66,8 +65,7 @@ builtin cmd dir params = do
|
||||||
|
|
||||||
external :: [String] -> IO ()
|
external :: [String] -> IO ()
|
||||||
external params = do
|
external params = do
|
||||||
ret <- boolSystem "git-shell" $ map Param $ ("-c":filterparams params)
|
unlessM (boolSystem "git-shell" $ map Param $ "-c":filterparams params) $
|
||||||
when (not ret) $
|
|
||||||
error "git-shell failed"
|
error "git-shell failed"
|
||||||
|
|
||||||
-- Drop all args after "--".
|
-- Drop all args after "--".
|
||||||
|
|
Loading…
Reference in a new issue