git-annex/Annex/Journal.hs

104 lines
3.1 KiB
Haskell
Raw Normal View History

{- management of the git-annex journal
2011-12-12 22:03:28 +00:00
-
- The journal is used to queue up changes before they are committed to the
- git-annex branch. Amoung other things, it ensures that if git-annex is
- interrupted, its recorded data is not lost.
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
2011-12-12 22:03:28 +00:00
module Annex.Journal where
import System.IO.Binary
import Common.Annex
import Annex.Exception
import qualified Git
import Annex.Perms
2011-12-12 22:03:28 +00:00
{- Records content for a file in the branch to the journal.
-
- Using the journal, rather than immediatly staging content to the index
- avoids git needing to rewrite the index after every change. -}
setJournalFile :: FilePath -> String -> Annex ()
setJournalFile file content = do
createAnnexDirectory =<< fromRepo gitAnnexJournalDir
createAnnexDirectory =<< fromRepo gitAnnexTmpDir
-- journal file is written atomically
jfile <- fromRepo $ journalFile file
tmp <- fromRepo gitAnnexTmpDir
let tmpfile = tmp </> takeFileName jfile
liftIO $ do
writeBinaryFile tmpfile content
moveFile tmpfile jfile
2011-12-12 22:03:28 +00:00
{- Gets any journalled content for a file in the branch. -}
getJournalFile :: FilePath -> Annex (Maybe String)
getJournalFile file = inRepo $ \g -> catchMaybeIO $
readFileStrict $ journalFile file g
2011-12-12 22:03:28 +00:00
{- List of files that have updated content in the journal. -}
getJournalledFiles :: Annex [FilePath]
getJournalledFiles = map fileJournal <$> getJournalFiles
{- List of existing journal files. -}
getJournalFiles :: Annex [FilePath]
getJournalFiles = do
g <- gitRepo
2012-09-17 04:18:07 +00:00
fs <- liftIO $ catchDefaultIO [] $
getDirectoryContents $ gitAnnexJournalDir g
2011-12-12 22:03:28 +00:00
return $ filter (`notElem` [".", ".."]) fs
{- Checks if there are changes in the journal. -}
journalDirty :: Annex Bool
journalDirty = not . null <$> getJournalFiles
{- Produces a filename to use in the journal for a file on the branch.
-
- The journal typically won't have a lot of files in it, so the hashing
- used in the branch is not necessary, and all the files are put directly
- in the journal directory.
-}
journalFile :: FilePath -> Git.Repo -> FilePath
journalFile file repo = gitAnnexJournalDir repo </> concatMap mangle file
2012-12-13 04:24:19 +00:00
where
2013-05-12 20:37:32 +00:00
mangle c
| c == pathSeparator = "_"
2013-05-12 20:43:59 +00:00
| c == '_' = "__"
| otherwise = [c]
2011-12-12 22:03:28 +00:00
{- Converts a journal file (relative to the journal dir) back to the
- filename on the branch. -}
fileJournal :: FilePath -> FilePath
2013-05-12 20:37:32 +00:00
fileJournal = replace [pathSeparator, pathSeparator] "_" .
replace "_" [pathSeparator]
2011-12-12 22:03:28 +00:00
{- Runs an action that modifies the journal, using locking to avoid
- contention with other git-annex processes. -}
lockJournal :: Annex a -> Annex a
lockJournal a = do
lockfile <- fromRepo gitAnnexJournalLock
createAnnexDirectory $ takeDirectory lockfile
mode <- annexFileMode
bracketIO (lock lockfile mode) unlock (const a)
2012-12-13 04:24:19 +00:00
where
lock lockfile mode = do
#ifndef mingw32_HOST_OS
l <- noUmask mode $ createFile lockfile mode
2012-12-13 04:24:19 +00:00
waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
return l
#else
writeFile lockfile ""
return lockfile
#endif
#ifndef mingw32_HOST_OS
2012-12-13 04:24:19 +00:00
unlock = closeFd
#else
unlock = removeFile
#endif