add check for unclean tree
This commit is contained in:
parent
c77ac11acc
commit
0e7984a793
4 changed files with 20 additions and 6 deletions
|
@ -1 +0,0 @@
|
||||||
1ac368a4-19e2-11e0-8c0f-8fcd42cf5a8d test repo
|
|
|
@ -147,7 +147,7 @@ withStrings a params = return $ map a params
|
||||||
withFilesToBeCommitted :: CommandSeekStrings
|
withFilesToBeCommitted :: CommandSeekStrings
|
||||||
withFilesToBeCommitted a params = do
|
withFilesToBeCommitted a params = do
|
||||||
repo <- Annex.gitRepo
|
repo <- Annex.gitRepo
|
||||||
tocommit <- liftIO $ runPreserveOrder (Git.stagedFiles repo) params
|
tocommit <- liftIO $ runPreserveOrder (Git.stagedFilesNotDeleted repo) params
|
||||||
tocommit' <- filterFiles tocommit
|
tocommit' <- filterFiles tocommit
|
||||||
return $ map a tocommit'
|
return $ map a tocommit'
|
||||||
withFilesUnlocked :: CommandSeekBackendFiles
|
withFilesUnlocked :: CommandSeekBackendFiles
|
||||||
|
|
|
@ -8,6 +8,7 @@
|
||||||
module Command.Unannex where
|
module Command.Unannex where
|
||||||
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
|
import Control.Monad (unless)
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
@ -32,6 +33,11 @@ start file = isAnnexed file $ \(key, backend) -> do
|
||||||
ishere <- inAnnex key
|
ishere <- inAnnex key
|
||||||
if ishere
|
if ishere
|
||||||
then do
|
then do
|
||||||
|
g <- Annex.gitRepo
|
||||||
|
staged <- liftIO $ Git.stagedFiles g [Git.workTree g]
|
||||||
|
unless (null staged) $
|
||||||
|
error "This command cannot be run when there are already files staged for commit."
|
||||||
|
|
||||||
showStart "unannex" file
|
showStart "unannex" file
|
||||||
return $ Just $ perform file key backend
|
return $ Just $ perform file key backend
|
||||||
else return Nothing
|
else return Nothing
|
||||||
|
|
17
GitRepo.hs
17
GitRepo.hs
|
@ -38,6 +38,7 @@ module GitRepo (
|
||||||
inRepo,
|
inRepo,
|
||||||
notInRepo,
|
notInRepo,
|
||||||
stagedFiles,
|
stagedFiles,
|
||||||
|
stagedFilesNotDeleted,
|
||||||
changedUnstagedFiles,
|
changedUnstagedFiles,
|
||||||
checkAttr,
|
checkAttr,
|
||||||
decodeGitFile,
|
decodeGitFile,
|
||||||
|
@ -243,12 +244,20 @@ notInRepo :: Repo -> [FilePath] -> IO [FilePath]
|
||||||
notInRepo repo l = pipeNullSplit repo $
|
notInRepo repo l = pipeNullSplit repo $
|
||||||
["ls-files", "--others", "--exclude-standard", "-z", "--"] ++ l
|
["ls-files", "--others", "--exclude-standard", "-z", "--"] ++ l
|
||||||
|
|
||||||
|
{- Returns a list of all files that are staged for commit. -}
|
||||||
|
stagedFiles :: Repo -> [FilePath] -> IO [FilePath]
|
||||||
|
stagedFiles repo l = stagedFiles' repo l []
|
||||||
|
|
||||||
{- Returns a list of the files, staged for commit, that are being added,
|
{- Returns a list of the files, staged for commit, that are being added,
|
||||||
- moved, or changed (but not deleted), from the specified locations. -}
|
- moved, or changed (but not deleted), from the specified locations. -}
|
||||||
stagedFiles :: Repo -> [FilePath] -> IO [FilePath]
|
stagedFilesNotDeleted :: Repo -> [FilePath] -> IO [FilePath]
|
||||||
stagedFiles repo l = pipeNullSplit repo $
|
stagedFilesNotDeleted repo l = stagedFiles' repo l ["--diff-filter=ACMRT"]
|
||||||
["diff", "--cached", "--name-only", "--diff-filter=ACMRT", "-z",
|
|
||||||
"--"] ++ l
|
stagedFiles' :: Repo -> [FilePath] -> [String] -> IO [FilePath]
|
||||||
|
stagedFiles' repo l middle = pipeNullSplit repo $ start ++ middle ++ end
|
||||||
|
where
|
||||||
|
start = ["diff", "--cached", "--name-only", "-z"]
|
||||||
|
end = ["--"] ++ l
|
||||||
|
|
||||||
{- Returns a list of files that have unstaged changes. -}
|
{- Returns a list of files that have unstaged changes. -}
|
||||||
changedUnstagedFiles :: Repo -> [FilePath] -> IO [FilePath]
|
changedUnstagedFiles :: Repo -> [FilePath] -> IO [FilePath]
|
||||||
|
|
Loading…
Reference in a new issue