git-annex/Command/Unlock.hs
Joey Hess 3a05d53761
add SeekInput (not yet used)
No behavior changes (hopefully), just adding SeekInput and plumbing it
through to the JSON display code for later use.

Over the course of 2 grueling days.

withFilesNotInGit reimplemented in terms of seekHelper
should be the only possible behavior change. It seems to test as
behaving the same.

Note that seekHelper dummies up the SeekInput in the case where
segmentPaths' gives up on sorting the expanded paths because there are
too many input paths. When SeekInput later gets exposed as a json field,
that will result in it being a little bit wrong in the case where
100 or more paths are passed to a git-annex command. I think this is a
subtle enough problem to not matter. If it does turn out to be a
problem, fixing it would require splitting up the input
parameters into groups of < 100, which would make git ls-files run
perhaps more than is necessary. May want to revisit this, because that
fix seems fairly low-impact.
2020-09-15 15:41:13 -04:00

66 lines
1.8 KiB
Haskell

{- git-annex command
-
- Copyright 2010-2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Command.Unlock where
import Command
import Annex.Content
import Annex.Perms
import Annex.Link
import Annex.ReplaceFile
import Git.FilePath
import qualified Database.Keys
import qualified Utility.RawFilePath as R
cmd :: Command
cmd = mkcmd "unlock" "unlock files for modification"
editcmd :: Command
editcmd = mkcmd "edit" "same as unlock"
mkcmd :: String -> String -> Command
mkcmd n d = withGlobalOptions [jsonOptions, annexedMatchingOptions] $
command n SectionCommon d paramPaths (withParams seek)
seek :: CmdParams -> CommandSeek
seek ps = withFilesInGitAnnex ww seeker =<< workTreeItems ww ps
where
ww = WarnUnmatchLsFiles
seeker = AnnexedFileSeeker
{ startAction = start
, checkContentPresent = Nothing
, usesLocationLog = False
}
start :: SeekInput -> RawFilePath -> Key -> CommandStart
start si file key = ifM (isJust <$> isAnnexLink file)
( starting "unlock" ai si $ perform file key
, stop
)
where
ai = mkActionItem (key, AssociatedFile (Just file))
perform :: RawFilePath -> Key -> CommandPerform
perform dest key = do
destmode <- liftIO $ catchMaybeIO $ fileMode <$> R.getFileStatus dest
replaceWorkTreeFile (fromRawFilePath dest) $ \tmp ->
ifM (inAnnex key)
( do
r <- linkFromAnnex key tmp destmode
case r of
LinkAnnexOk -> return ()
LinkAnnexNoop -> return ()
LinkAnnexFailed -> error "unlock failed"
, liftIO $ writePointerFile (toRawFilePath tmp) key destmode
)
next $ cleanup dest key destmode
cleanup :: RawFilePath -> Key -> Maybe FileMode -> CommandCleanup
cleanup dest key destmode = do
stagePointerFile dest destmode =<< hashPointerFile key
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath dest)
return True