merge clean into smudge command

The git filter config can be used to map the single git-annex command to
the 2 actions, and this avoids "git annex clean" being used for this thing,
it might have a better use for that name later.
This commit is contained in:
Joey Hess 2015-12-04 15:30:06 -04:00
parent 983c1894eb
commit 723e4e31a1
Failed to extract signature
6 changed files with 86 additions and 125 deletions

View file

@ -97,7 +97,6 @@ import qualified Command.Forget
import qualified Command.Proxy
import qualified Command.DiffDriver
import qualified Command.Smudge
import qualified Command.Clean
import qualified Command.Undo
import qualified Command.Version
#ifdef WITH_ASSISTANT
@ -204,7 +203,6 @@ cmds testoptparser testrunner =
, Command.Proxy.cmd
, Command.DiffDriver.cmd
, Command.Smudge.cmd
, Command.Clean.cmd
, Command.Undo.cmd
, Command.Version.cmd
#ifdef WITH_ASSISTANT

View file

@ -1,68 +0,0 @@
{- git-annex command
-
- Copyright 2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Clean where
import Common.Annex
import Command
import Annex.Content
import Annex.MetaData
import Annex.FileMatcher
import Types.KeySource
import Types.Key
import Backend
import Logs.Location
import qualified Data.ByteString.Lazy as B
cmd :: Command
cmd = noMessages $ dontCheck repoExists $
command "clean" SectionPlumbing
"git clean filter"
paramFile (withParams seek)
seek :: CmdParams -> CommandSeek
seek = withWords start
start :: [String] -> CommandStart
start [file] = do
ifM (shouldAnnex file)
( do
k <- ingest file
liftIO $ putStrLn (key2file k)
, liftIO $ B.hGetContents stdin >>= B.hPut stdout -- cat file
)
stop
start [] = error "clean filter run without filename; upgrade git"
start _ = error "clean filter passed multiple filenames"
shouldAnnex :: FilePath -> Annex Bool
shouldAnnex file = do
matcher <- largeFilesMatcher
checkFileMatcher matcher file
ingest :: FilePath -> Annex Key
ingest file = do
backend <- chooseBackend file
let source = KeySource
{ keyFilename = file
, contentLocation = file
, inodeCache = Nothing
}
k <- fst . fromMaybe (error "failed to generate a key")
<$> genKey source backend
-- Hard link (or copy) file content to annex
-- to prevent it from being lost when git checks out
-- a branch not containing this file.
r <- linkAnnex k file
case r of
LinkAnnexFailed -> error "Problem adding file to the annex"
LinkAnnexOk -> logStatus k InfoPresent
LinkAnnexNoop -> noop
genMetaData k file
=<< liftIO (getFileStatus file)
return k

View file

@ -10,20 +10,37 @@ module Command.Smudge where
import Common.Annex
import Command
import Types.Key
import Annex.Content
import Annex.MetaData
import Annex.FileMatcher
import Types.KeySource
import Backend
import Logs.Location
import qualified Data.ByteString.Lazy as B
cmd :: Command
cmd = noCommit $ noMessages $ dontCheck repoExists $
cmd = noCommit $ noMessages $
command "smudge" SectionPlumbing
"git smudge filter"
paramFile (withParams seek)
paramFile (seek <$$> optParser)
seek :: CmdParams -> CommandSeek
seek = withWords start
data SmudgeOptions = SmudgeOptions
{ smudgeFile :: FilePath
, cleanOption :: Bool
}
start :: [String] -> CommandStart
start [_file] = do
optParser :: CmdParamsDesc -> Parser SmudgeOptions
optParser desc = SmudgeOptions
<$> argument str ( metavar desc )
<*> switch ( long "clean" <> help "clean filter" )
seek :: SmudgeOptions -> CommandSeek
seek o = commandAction $
(if cleanOption o then clean else smudge) (smudgeFile o)
smudge :: FilePath -> CommandStart
smudge _file = do
liftIO $ fileEncoding stdin
s <- liftIO $ hGetContents stdin
case parsePointer s of
@ -35,8 +52,46 @@ start [_file] = do
(B.hPut stdout)
=<< catchMaybeIO (B.readFile content)
stop
start [] = error "smudge filter run without filename; upgrade git"
start _ = error "smudge filter passed multiple filenames"
clean :: FilePath -> CommandStart
clean file = do
ifM (shouldAnnex file)
( do
k <- ingest file
liftIO $ emitPointer k
, liftIO $ B.hGetContents stdin >>= B.hPut stdout -- cat file
)
stop
shouldAnnex :: FilePath -> Annex Bool
shouldAnnex file = do
matcher <- largeFilesMatcher
checkFileMatcher matcher file
ingest :: FilePath -> Annex Key
ingest file = do
backend <- chooseBackend file
let source = KeySource
{ keyFilename = file
, contentLocation = file
, inodeCache = Nothing
}
k <- fst . fromMaybe (error "failed to generate a key")
<$> genKey source backend
-- Hard link (or copy) file content to annex
-- to prevent it from being lost when git checks out
-- a branch not containing this file.
r <- linkAnnex k file
case r of
LinkAnnexFailed -> error "Problem adding file to the annex"
LinkAnnexOk -> logStatus k InfoPresent
LinkAnnexNoop -> noop
genMetaData k file
=<< liftIO (getFileStatus file)
return k
emitPointer :: Key -> IO ()
emitPointer = putStrLn . key2file
parsePointer :: String -> Maybe Key
parsePointer s

View file

@ -1,36 +0,0 @@
# NAME
git-annex clean - git filter driver for git-annex
# SYNOPSIS
git annex clean
# DESCRIPTION
When git-annex is used as a git filter driver, this command is run
by git commands such as `git add`. It generates a file that
is added to the git repository and points to the git-annex object
containing the content of a large file.
To configure git to use git-annex as a git filter driver, place the
following in the .gitattributes file:
* filter=annex
.* !filter
The annex.largefiles config is consulted to decide if a given file should
be added to git as-is, or if its content are large enough to need to use
git-annex.
# SEE ALSO
[[git-annex]](1)
[[git-annex-smudge]](1)
# AUTHOR
Joey Hess <id@joeyh.name>
Warning: Automatically converted into a man page by mdwn2man. Edit with care.

View file

@ -4,26 +4,36 @@ git-annex smudge - git filter driver for git-annex
# SYNOPSIS
git annex smudge
git annex smudge [--clean] file
# DESCRIPTION
When git-annex is used as a git filter driver, this command is run
by git commands such as `git checkout` and outputs the content of annexed
objects that pointer files point to.
This command lets git-annex be used as a git filter driver which lets
annexed files in the git repository to be unlocked at all times, instead
of being symlinks.
To configure git to use git-annex as a git filter driver, place the
following in the .gitattributes file:
The git configuration to use this command as a filter driver is as follows,
but this is normally set up for you by git-annex init, so you should
not need to configure it manually:
[filter "annex"]
clean = git-annex smudge --clean %f
smudge = git-annex smudge %f
To make git use this filter on all files except for dotfiles, put something
like the following in the .gitattributes file:
* filter=annex
.* !filter
When adding a file with `git add`, the annex.largefiles config is
consulted to decide if a given file should be added to git as-is,
or if its content are large enough to need to use git-annex.
# SEE ALSO
[[git-annex]](1)
[[git-annex-clean]](1)
# AUTHOR
Joey Hess <id@joeyh.name>

View file

@ -626,11 +626,13 @@ subdirectories).
See [[git-annex-diffdriver]](1) for details.
* `smudge`, `clean`
* `smudge`
These let git-annex be used as a git filter driver.
This command lets git-annex be used as a git filter driver, allowing
annexed files in the git repository to be unlocked at all times, instead
of being symlinks.
See [[git-annex-smudge]](1) and [[git-annex-clean]](1) for details.
See [[git-annex-smudge]](1) for details.
* `remotedaemon`