git-annex/Core.hs

168 lines
4.7 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
import System.IO
import System.Directory
import Control.Monad.State (liftIO)
2010-10-17 01:03:25 +00:00
import System.Path
2010-10-17 17:13:49 +00:00
import Data.String.Utils
2010-10-28 16:40:05 +00:00
import Monad (when, unless)
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-10-17 01:03:25 +00:00
import Utility
2010-10-14 20:13:43 +00:00
2010-10-14 21:57:04 +00:00
{- Sets up a git repo for git-annex. -}
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
g <- Annex.gitRepo
2010-10-17 20:39:30 +00:00
-- Runs all queued git commands.
q <- Annex.queueGet
2010-10-28 16:40:05 +00:00
unless (q == GitQueue.empty) $ do
verbose $ liftIO $ putStrLn "Recording state in git..."
liftIO $ GitQueue.run g q
-- clean up any files left in the temp directory, but leave
-- the tmp directory itself
2010-10-17 20:39:30 +00:00
let tmp = annexTmpLocation g
exists <- liftIO $ doesDirectoryExist tmp
2010-10-28 16:40:05 +00:00
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
2010-10-14 21:57:04 +00:00
{- configure git to use union merge driver on state files, if it is not
- already -}
gitAttributes :: Git.Repo -> IO ()
gitAttributes repo = do
exists <- doesFileExist attributes
if (not exists)
then do
writeFile attributes $ attrLine ++ "\n"
commit
else do
content <- readFile attributes
2010-10-28 16:40:05 +00:00
when (all (/= attrLine) (lines content)) $ do
appendFile attributes $ attrLine ++ "\n"
commit
2010-10-14 21:57:04 +00:00
where
attrLine = stateLoc ++ "*.log merge=union"
2010-10-14 21:57:04 +00:00
attributes = Git.attributes repo
commit = do
Git.run repo ["add", attributes]
Git.run repo ["commit", "-m", "git-annex setup",
attributes]
2010-10-14 18:38:29 +00:00
2010-10-27 18:33:44 +00:00
{- set up a git pre-commit hook, if one is not already present -}
gitPreCommitHook :: Git.Repo -> IO ()
gitPreCommitHook repo = do
let hook = (Git.workTree repo) ++ "/" ++ (Git.dir repo) ++
"/hooks/pre-commit"
exists <- doesFileExist hook
if (exists)
then putStrLn $ "pre-commit hook (" ++ hook ++ ") already exists, not configuring"
else do
writeFile hook $ "#!/bin/sh\n" ++
"# automatically configured by git-annex\n" ++
"git annex pre-commit .\n"
p <- getPermissions hook
setPermissions hook $ p {executable = True}
{- Checks if a given key is currently present in the annexLocation.
-
- This can be run against a remote repository to check the key there. -}
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
if (not $ Git.repoIsUrl g)
then liftIO $ doesFileExist $ annexLocation g key
else do
showNote ("checking " ++ Git.repoDescribe g ++ "...")
liftIO $ boolSystem "ssh" [Git.urlHost g,
"test -e " ++
(shellEscape $ 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
Just f -> f
Nothing -> error $ "unable to normalize " ++ file
return $ (relPathDirToDir (parentDir absfile) (Git.workTree g)) ++
annexLocationRelative g 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
let dest = annexLocation g key
let tmp = (annexTmpLocation g) ++ (keyFile key)
liftIO $ createDirectoryIfMissing True (parentDir tmp)
success <- action tmp
if (success)
then do
liftIO $ renameFile tmp dest
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
2010-10-17 17:13:49 +00:00
{- Output logging -}
verbose :: Annex () -> Annex ()
verbose a = do
q <- Annex.flagIsSet "quiet"
2010-10-28 16:40:05 +00:00
unless q a
2010-10-17 17:13:49 +00:00
showStart :: String -> String -> Annex ()
showStart command file = verbose $ do
2010-10-23 17:59:47 +00:00
liftIO $ putStr $ command ++ " " ++ file ++ " "
2010-10-17 17:13:49 +00:00
liftIO $ hFlush stdout
showNote :: String -> Annex ()
showNote s = verbose $ do
2010-10-23 17:59:47 +00:00
liftIO $ putStr $ "(" ++ s ++ ") "
2010-10-17 17:13:49 +00:00
liftIO $ hFlush stdout
showProgress :: Annex ()
showProgress = verbose $ liftIO $ putStr $ "\n"
2010-10-17 17:13:49 +00:00
showLongNote :: String -> Annex ()
showLongNote s = verbose $ do
2010-10-31 19:12:56 +00:00
liftIO $ putStr $ "\n" ++ indented
2010-10-17 17:13:49 +00:00
where
2010-10-31 19:12:56 +00:00
indented = join "\n" $ map (\l -> " " ++ l) $ lines s
2010-10-17 17:13:49 +00:00
showEndOk :: Annex ()
showEndOk = verbose $ do
2010-10-23 17:59:47 +00:00
liftIO $ putStrLn "ok"
2010-10-19 16:55:40 +00:00
showEndFail :: Annex ()
showEndFail = verbose $ do
liftIO $ putStrLn "\nfailed"