git-annex/Core.hs

201 lines
5.6 KiB
Haskell
Raw Normal View History

2010-10-27 20:53:54 +00:00
{- git-annex core functions
-
- Copyright 2010 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2010-10-14 07:40:26 +00:00
module Core where
2010-11-01 07:01:58 +00:00
import IO (try)
2010-10-14 07:40:26 +00:00
import System.Directory
import Control.Monad.State (liftIO)
2010-10-17 01:03:25 +00:00
import System.Path
2010-11-08 19:15:21 +00:00
import Control.Monad (when, unless, filterM)
import System.Posix.Files
import Data.Maybe
import System.FilePath
2010-10-16 20:20:49 +00:00
2010-10-14 07:40:26 +00:00
import Types
import Locations
2010-10-17 16:08:59 +00:00
import LocationLog
2010-10-14 07:40:26 +00:00
import UUID
import qualified GitRepo as Git
import qualified GitQueue
2010-10-14 07:40:26 +00:00
import qualified Annex
2010-11-08 19:15:21 +00:00
import qualified Backend
2010-10-17 01:03:25 +00:00
import Utility
2010-11-08 19:15:21 +00:00
import Messages
2010-11-01 07:01:58 +00:00
{- Runs a list of Annex actions. Catches IO errors and continues
- (but explicitly thrown errors terminate the whole command).
- Propigates an overall error status at the end.
-}
tryRun :: AnnexState -> [Annex Bool] -> IO ()
tryRun state actions = tryRun' state 0 actions
tryRun' :: AnnexState -> Integer -> [Annex Bool] -> IO ()
tryRun' state errnum (a:as) = do
result <- try $ Annex.run state a
case result of
2010-11-01 07:01:58 +00:00
Left err -> do
Annex.eval state $ showErr err
tryRun' state (errnum + 1) as
Right (True,state') -> tryRun' state' errnum as
Right (False,state') -> tryRun' state' (errnum + 1) as
tryRun' _ errnum [] =
2010-11-06 21:07:11 +00:00
when (errnum > 0) $ error $ show errnum ++ " failed"
2010-10-14 20:13:43 +00:00
2010-11-14 18:44:24 +00:00
{- Actions to perform each time ran. -}
2010-10-25 23:17:11 +00:00
startup :: Annex Bool
startup = do
2010-10-14 20:13:43 +00:00
prepUUID
2010-10-25 23:17:11 +00:00
return True
2010-10-14 21:57:04 +00:00
{- When git-annex is done, it runs this. -}
2010-10-25 23:17:11 +00:00
shutdown :: Annex Bool
2010-10-14 21:57:04 +00:00
shutdown = do
q <- Annex.queueGet
2010-10-28 16:40:05 +00:00
unless (q == GitQueue.empty) $ do
2010-11-08 20:47:36 +00:00
showSideAction "Recording state in git..."
Annex.queueRun
-- clean up any files left in the temp directory, but leave
-- the tmp directory itself
2010-11-08 20:47:36 +00:00
g <- Annex.gitRepo
2010-10-17 20:39:30 +00:00
let tmp = annexTmpLocation g
exists <- liftIO $ doesDirectoryExist tmp
when exists $ liftIO $ removeDirectoryRecursive tmp
liftIO $ createDirectoryIfMissing True tmp
2010-10-17 20:39:30 +00:00
2010-10-25 23:17:11 +00:00
return True
{- Checks if a given key is currently present in the annexLocation. -}
2010-10-14 23:36:11 +00:00
inAnnex :: Key -> Annex Bool
inAnnex key = do
2010-10-14 18:38:29 +00:00
g <- Annex.gitRepo
when (Git.repoIsUrl g) $ error "inAnnex cannot check remote repo"
liftIO $ doesFileExist $ annexLocation g key
2010-10-17 01:03:25 +00:00
{- Calculates the relative path to use to link a file to a key. -}
calcGitLink :: FilePath -> Key -> Annex FilePath
calcGitLink file key = do
g <- Annex.gitRepo
cwd <- liftIO $ getCurrentDirectory
let absfile = case absNormPath cwd file of
2010-10-17 01:03:25 +00:00
Just f -> f
Nothing -> error $ "unable to normalize " ++ file
2010-11-06 21:07:11 +00:00
return $ relPathDirToDir (parentDir absfile) (Git.workTree g) ++
2010-10-31 20:00:32 +00:00
annexLocationRelative key
2010-10-17 16:08:59 +00:00
{- Updates the LocationLog when a key's presence changes. -}
logStatus :: Key -> LogStatus -> Annex ()
logStatus key status = do
g <- Annex.gitRepo
u <- getUUID g
2010-10-31 19:12:56 +00:00
logfile <- liftIO $ logChange g key u status
Annex.queue "add" ["--"] logfile
2010-10-17 16:08:59 +00:00
2010-10-23 18:26:38 +00:00
{- Runs an action, passing it a temporary filename to download,
- and if the action succeeds, moves the temp file into
- the annex as a key's content. -}
2010-10-25 18:10:38 +00:00
getViaTmp :: Key -> (FilePath -> Annex Bool) -> Annex Bool
2010-10-23 18:26:38 +00:00
getViaTmp key action = do
g <- Annex.gitRepo
2010-11-06 21:07:11 +00:00
let tmp = annexTmpLocation g ++ keyFile key
2010-10-23 18:26:38 +00:00
liftIO $ createDirectoryIfMissing True (parentDir tmp)
success <- action tmp
if success
2010-10-23 18:26:38 +00:00
then do
moveAnnex key tmp
2010-10-23 18:26:38 +00:00
logStatus key ValuePresent
2010-10-25 18:10:38 +00:00
return True
2010-10-23 18:26:38 +00:00
else do
-- the tmp file is left behind, in case caller wants
-- to resume its transfer
2010-10-25 18:10:38 +00:00
return False
2010-10-23 18:26:38 +00:00
{- Removes the write bits from a file. -}
preventWrite :: FilePath -> IO ()
preventWrite f = unsetFileMode f writebits
where
writebits = foldl unionFileModes ownerWriteMode
[groupWriteMode, otherWriteMode]
{- Turns a file's write bit back on. -}
allowWrite :: FilePath -> IO ()
allowWrite f = do
s <- getFileStatus f
setFileMode f $ fileMode s `unionFileModes` ownerWriteMode
2010-11-08 20:47:36 +00:00
{- Moves a file into .git/annex/objects/ -}
moveAnnex :: Key -> FilePath -> Annex ()
moveAnnex key src = do
2010-11-08 20:47:36 +00:00
g <- Annex.gitRepo
let dest = annexLocation g key
let dir = parentDir dest
liftIO $ do
createDirectoryIfMissing True dir
allowWrite dir -- in case the directory already exists
renameFile src dest
preventWrite dest
preventWrite dir
{- Removes a key's file from .git/annex/objects/ -}
removeAnnex :: Key -> Annex ()
removeAnnex key = do
g <- Annex.gitRepo
let file = annexLocation g key
let dir = parentDir file
liftIO $ do
allowWrite dir
removeFile file
removeDirectory dir
{- Moves a key's file out of .git/annex/objects/ -}
fromAnnex :: Key -> FilePath -> Annex ()
fromAnnex key dest = do
g <- Annex.gitRepo
let file = annexLocation g key
let dir = parentDir file
liftIO $ do
allowWrite dir
allowWrite file
renameFile file dest
removeDirectory dir
2010-11-08 20:47:36 +00:00
{- Moves a key out of .git/annex/objects/ into .git/annex/bad, and
2010-11-13 19:42:56 +00:00
- returns the file it was moved to. -}
moveBad :: Key -> Annex FilePath
moveBad key = do
g <- Annex.gitRepo
2010-11-13 19:40:12 +00:00
let src = annexLocation g key
2010-11-13 19:42:56 +00:00
let dest = annexBadLocation g ++ takeFileName src
2010-11-13 19:40:12 +00:00
liftIO $ createDirectoryIfMissing True dest
2010-11-13 19:42:56 +00:00
liftIO $ renameFile src dest
2010-11-13 19:40:12 +00:00
liftIO $ removeDirectory (parentDir src)
return dest
2010-11-08 19:15:21 +00:00
{- List of keys whose content exists in .git/annex/objects/ -}
getKeysPresent :: Annex [Key]
getKeysPresent = do
g <- Annex.gitRepo
2010-11-08 20:47:36 +00:00
getKeysPresent' $ annexObjectDir g
getKeysPresent' :: FilePath -> Annex [Key]
getKeysPresent' dir = do
contents <- liftIO $ getDirectoryContents dir
files <- liftIO $ filterM present contents
2010-11-08 19:15:21 +00:00
return $ map fileKey files
where
present d = do
s <- getFileStatus $ dir ++ "/" ++ d ++ "/"
++ takeFileName d
2010-11-08 19:15:21 +00:00
return $ isRegularFile s
{- List of keys referenced by symlinks in the git repo. -}
getKeysReferenced :: Annex [Key]
getKeysReferenced = do
g <- Annex.gitRepo
files <- liftIO $ Git.inRepo g $ Git.workTree g
keypairs <- mapM Backend.lookupFile files
return $ map fst $ catMaybes keypairs