git-annex/Init.hs
Joey Hess 3802f2f270 work around lack of receive.denyCurrentBranch in direct mode
Now that direct mode sets core.bare=true, git's normal prohibition about
pushing into the currently checked out branch doesn't work.

A simple fix for this would be an update hook which blocks the pushes..
but git hooks must be executable, and git-annex needs to be usable on eg,
FAT, which lacks x bits.

Instead, enabling direct mode switches the branch (eg master) to a special
purpose branch (eg annex/direct/master). This branch is not pushed when
syncing; instead any changes that git annex sync commits get written to
master, and it's pushed (along with synced/master) to the remote.

Note that initialization has been changed to always call setDirect,
even if it's just setDirect False for indirect mode. This is needed because
if the user has just cloned a direct mode repo, that nothing has synced
with before, it may have no master branch, and only a annex/direct/master.
Resulting in that branch being checked out locally too. Calling setDirect False
for indirect mode moves back out of this branch, to a new master branch,
and ensures that a manual "git push" doesn't push changes directly to
the annex/direct/master of the remote. (It's possible that the user
makes a commit w/o using git-annex and pushes it, but nothing I can do
about that really.)

This commit was sponsored by Jonathan Harrington.
2013-11-05 21:08:31 -04:00

175 lines
4.5 KiB
Haskell

{- git-annex repository initialization
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Init (
ensureInitialized,
isInitialized,
initialize,
uninitialize,
probeCrippledFileSystem,
) where
import Common.Annex
import Utility.Network
import qualified Annex
import qualified Git
import qualified Git.LsFiles
import qualified Git.Config
import qualified Annex.Branch
import Logs.UUID
import Annex.Version
import Annex.UUID
import Config
import Annex.Direct
import Annex.Content.Direct
import Annex.Environment
import Backend
#ifndef mingw32_HOST_OS
import Utility.UserInfo
import Utility.FileMode
#endif
import Annex.Hook
import Upgrade
genDescription :: Maybe String -> Annex String
genDescription (Just d) = return d
genDescription Nothing = do
reldir <- liftIO . relHome =<< fromRepo Git.repoPath
hostname <- fromMaybe "" <$> liftIO getHostname
#ifndef mingw32_HOST_OS
let at = if null hostname then "" else "@"
username <- liftIO myUserName
return $ concat [username, at, hostname, ":", reldir]
#else
return $ concat [hostname, ":", reldir]
#endif
initialize :: Maybe String -> Annex ()
initialize mdescription = do
prepUUID
checkFifoSupport
checkCrippledFileSystem
unlessM isBare $
hookWrite preCommitHook
ifM (crippledFileSystem <&&> not <$> isBare)
( do
enableDirectMode
setDirect True
setVersion directModeVersion
, do
setVersion defaultVersion
setDirect False
)
createInodeSentinalFile
u <- getUUID
{- This will make the first commit to git, so ensure git is set up
- properly to allow commits when running it. -}
ensureCommit $ do
Annex.Branch.create
describeUUID u =<< genDescription mdescription
uninitialize :: Annex ()
uninitialize = do
hookUnWrite preCommitHook
removeRepoUUID
removeVersion
{- Will automatically initialize if there is already a git-annex
- branch from somewhere. Otherwise, require a manual init
- to avoid git-annex accidentially being run in git
- repos that did not intend to use it.
-
- Checks repository version and handles upgrades too.
-}
ensureInitialized :: Annex ()
ensureInitialized = getVersion >>= maybe needsinit checkUpgrade
where
needsinit = ifM Annex.Branch.hasSibling
( initialize Nothing
, error "First run: git-annex init"
)
{- Checks if a repository is initialized. Does not check version for ugrade. -}
isInitialized :: Annex Bool
isInitialized = maybe Annex.Branch.hasSibling (const $ return True) =<< getVersion
isBare :: Annex Bool
isBare = fromRepo Git.repoIsLocalBare
{- A crippled filesystem is one that does not allow making symlinks,
- or removing write access from files. -}
probeCrippledFileSystem :: Annex Bool
probeCrippledFileSystem = do
#ifdef mingw32_HOST_OS
return True
#else
tmp <- fromRepo gitAnnexTmpDir
let f = tmp </> "gaprobe"
liftIO $ do
createDirectoryIfMissing True tmp
writeFile f ""
uncrippled <- liftIO $ probe f
liftIO $ removeFile f
return $ not uncrippled
where
probe f = catchBoolIO $ do
let f2 = f ++ "2"
nukeFile f2
createSymbolicLink f f2
nukeFile f2
preventWrite f
allowWrite f
return True
#endif
checkCrippledFileSystem :: Annex ()
checkCrippledFileSystem = whenM probeCrippledFileSystem $ do
warning "Detected a crippled filesystem."
setCrippledFileSystem True
{- Normally git disables core.symlinks itself when the
- filesystem does not support them, but in Cygwin, git
- does support symlinks, while git-annex, not linking
- with Cygwin, does not. -}
whenM (coreSymlinks <$> Annex.getGitConfig) $ do
warning "Disabling core.symlinks."
setConfig (ConfigKey "core.symlinks")
(Git.Config.boolConfig False)
probeFifoSupport :: Annex Bool
probeFifoSupport = do
#ifdef mingw32_HOST_OS
return False
#else
tmp <- fromRepo gitAnnexTmpDir
let f = tmp </> "gaprobe"
liftIO $ do
createDirectoryIfMissing True tmp
nukeFile f
ms <- tryIO $ do
createNamedPipe f ownerReadMode
getFileStatus f
nukeFile f
return $ either (const False) isNamedPipe ms
#endif
checkFifoSupport :: Annex ()
checkFifoSupport = unlessM probeFifoSupport $ do
warning "Detected a filesystem without fifo support."
warning "Disabling ssh connection caching."
setConfig (annexConfig "sshcaching") (Git.Config.boolConfig False)
enableDirectMode :: Annex ()
enableDirectMode = unlessM isDirect $ do
warning "Enabling direct mode."
top <- fromRepo Git.repoPath
(l, clean) <- inRepo $ Git.LsFiles.inRepo [top]
forM_ l $ \f ->
maybe noop (`toDirect` f) =<< isAnnexLink f
void $ liftIO clean