git-annex/Command/Lock.hs

121 lines
3.4 KiB
Haskell
Raw Normal View History

2010-11-09 19:59:49 +00:00
{- git-annex command
-
2015-12-11 14:42:18 +00:00
- Copyright 2010,2015 Joey Hess <id@joeyh.name>
2010-11-09 19:59:49 +00:00
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Lock where
import Command
2011-10-04 04:40:47 +00:00
import qualified Annex.Queue
2013-12-05 20:05:07 +00:00
import qualified Annex
2015-12-11 14:42:18 +00:00
import Annex.Version
import Annex.Content
import Annex.Link
import Annex.InodeSentinal
import Annex.Perms
import Annex.ReplaceFile
2015-12-11 14:42:18 +00:00
import Utility.InodeCache
import qualified Database.Keys
2015-12-22 17:23:33 +00:00
import Annex.Ingest
import Logs.Location
import Git.FilePath
cmd :: Command
cmd = notDirect $ withGlobalOptions annexedMatchingOptions $
command "lock" SectionCommon
"undo unlock command"
paramPaths (withParams seek)
2010-11-09 19:59:49 +00:00
seek :: CmdParams -> CommandSeek
2015-12-11 14:42:18 +00:00
seek ps = ifM versionSupportsUnlockedPointers
( withFilesInGit (whenAnnexed startNew) ps
, do
withFilesOldUnlocked startOld ps
withFilesOldUnlockedToBeCommitted startOld ps
2015-12-11 14:42:18 +00:00
)
2010-11-11 22:54:52 +00:00
2015-12-11 14:42:18 +00:00
startNew :: FilePath -> Key -> CommandStart
startNew file key = ifM (isJust <$> isAnnexLink file)
( stop
, do
showStart "lock" file
2016-01-01 17:22:38 +00:00
go =<< liftIO (isPointerFile file)
)
2015-12-11 14:42:18 +00:00
where
go (Just key')
| key' == key = cont True
2015-12-11 14:42:18 +00:00
| otherwise = errorModified
go Nothing =
ifM (isUnmodified key file)
( cont False
, ifM (Annex.getState Annex.force)
( cont True
, errorModified
)
)
cont = next . performNew file key
2010-11-09 19:59:49 +00:00
2015-12-11 14:42:18 +00:00
performNew :: FilePath -> Key -> Bool -> CommandPerform
performNew file key filemodified = do
lockdown =<< calcRepo (gitAnnexLocation key)
2015-12-22 17:23:33 +00:00
addLink file key
2015-12-11 14:42:18 +00:00
=<< withTSDelta (liftIO . genInodeCache file)
next $ cleanupNew file key
where
lockdown obj = do
ifM (catchBoolIO $ sameInodeCache obj =<< Database.Keys.getInodeCaches key)
( breakhardlink obj
, repopulate obj
)
whenM (liftIO $ doesFileExist obj) $
freezeContent obj
-- It's ok if the file is hard linked to obj, but if some other
-- associated file is, we need to break that link to lock down obj.
breakhardlink obj = whenM (catchBoolIO $ (> 1) . linkCount <$> liftIO (getFileStatus obj)) $ do
mfc <- withTSDelta (liftIO . genInodeCache file)
unlessM (sameInodeCache obj (maybeToList mfc)) $ do
modifyContent obj $ replaceFile obj $ \tmp -> do
unlessM (checkedCopyFile key obj tmp Nothing) $
error "unable to lock file"
Database.Keys.storeInodeCaches key [obj]
-- Try to repopulate obj from an unmodified associated file.
repopulate obj
| filemodified = modifyContent obj $ do
g <- Annex.gitRepo
fs <- map (`fromTopFilePath` g)
<$> Database.Keys.getAssociatedFiles key
mfile <- firstM (isUnmodified key) fs
liftIO $ nukeFile obj
case mfile of
Just unmodified ->
unlessM (checkedCopyFile key unmodified obj Nothing)
lostcontent
Nothing -> lostcontent
| otherwise = modifyContent obj $
liftIO $ renameFile file obj
lostcontent = logStatus key InfoMissing
2015-12-11 14:42:18 +00:00
cleanupNew :: FilePath -> Key -> CommandCleanup
cleanupNew file key = do
Database.Keys.removeAssociatedFile key =<< inRepo (toTopFilePath file)
2015-12-11 14:42:18 +00:00
return True
startOld :: FilePath -> CommandStart
startOld file = do
showStart "lock" file
unlessM (Annex.getState Annex.force)
errorModified
next $ performOld file
performOld :: FilePath -> CommandPerform
performOld file = do
Annex.Queue.addCommand "checkout" [Param "--"] [file]
2015-12-11 14:42:18 +00:00
next $ return True
errorModified :: a
errorModified = error "Locking this file would discard any changes you have made to it. Use 'git annex add' to stage your changes. (Or, use --force to override)"