2011-12-13 19:05:07 +00:00
|
|
|
{- Construction of Git Repo objects
|
|
|
|
-
|
2021-01-18 18:52:56 +00:00
|
|
|
- Copyright 2010-2021 Joey Hess <id@joeyh.name>
|
2011-12-13 19:05:07 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2011-12-13 19:05:07 +00:00
|
|
|
-}
|
|
|
|
|
2020-10-28 19:40:50 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2013-05-10 21:29:59 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2011-12-13 19:05:07 +00:00
|
|
|
module Git.Construct (
|
|
|
|
fromCwd,
|
|
|
|
fromAbsPath,
|
2012-01-26 00:42:01 +00:00
|
|
|
fromPath,
|
2011-12-13 19:05:07 +00:00
|
|
|
fromUrl,
|
|
|
|
fromUnknown,
|
|
|
|
localToUrl,
|
2011-12-14 19:30:14 +00:00
|
|
|
remoteNamed,
|
|
|
|
remoteNamedFromKey,
|
2011-12-13 19:05:07 +00:00
|
|
|
fromRemotes,
|
|
|
|
fromRemoteLocation,
|
|
|
|
repoAbsPath,
|
2013-03-12 12:09:31 +00:00
|
|
|
checkForRepo,
|
2015-02-12 19:33:05 +00:00
|
|
|
newFrom,
|
2020-10-23 18:56:12 +00:00
|
|
|
adjustGitDirFile,
|
2011-12-13 19:05:07 +00:00
|
|
|
) where
|
|
|
|
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2011-12-13 19:05:07 +00:00
|
|
|
import System.Posix.User
|
2013-05-10 21:29:59 +00:00
|
|
|
#endif
|
2017-01-31 22:40:42 +00:00
|
|
|
import qualified Data.Map as M
|
2011-12-13 19:05:07 +00:00
|
|
|
import Network.URI
|
|
|
|
|
|
|
|
import Common
|
|
|
|
import Git.Types
|
|
|
|
import Git
|
2013-09-26 21:26:13 +00:00
|
|
|
import Git.Remote
|
2014-02-08 19:31:03 +00:00
|
|
|
import Git.FilePath
|
2011-12-14 19:30:14 +00:00
|
|
|
import qualified Git.Url as Url
|
2012-10-25 22:17:32 +00:00
|
|
|
import Utility.UserInfo
|
2020-10-28 19:40:50 +00:00
|
|
|
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified System.FilePath.ByteString as P
|
2011-12-13 19:05:07 +00:00
|
|
|
|
2012-09-16 02:40:04 +00:00
|
|
|
{- Finds the git repository used for the cwd, which may be in a parent
|
2012-01-13 16:52:09 +00:00
|
|
|
- directory. -}
|
Additional GIT_DIR support bugfixes. May actually work now.
Two fixes. First, and most importantly, relax the isLinkToAnnex check
to only look for /annex/objects/, not [^|/].git/annex/objects. If
GIT_DIR is used with a detached work tree, the git directory is
not necessarily named .git.
There are important caveats with doing that at all, since git-annex will
make symlinks that point at GIT_DIR, which means that the relative path
between GIT_DIR and GIT_WORK_TREE needs to remain stable across all clones
of the repository.
----
The other fix is just fixing crazy and wrong code that, when GIT_DIR is
set, expects to still find a git repository in the path below the work
tree, and uses some of its configuration, and some of GIT_DIR. What was I
thinking, and why can't I seem to get this code right?
2013-02-23 16:32:09 +00:00
|
|
|
fromCwd :: IO (Maybe Repo)
|
|
|
|
fromCwd = getCurrentDirectory >>= seekUp
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
Additional GIT_DIR support bugfixes. May actually work now.
Two fixes. First, and most importantly, relax the isLinkToAnnex check
to only look for /annex/objects/, not [^|/].git/annex/objects. If
GIT_DIR is used with a detached work tree, the git directory is
not necessarily named .git.
There are important caveats with doing that at all, since git-annex will
make symlinks that point at GIT_DIR, which means that the relative path
between GIT_DIR and GIT_WORK_TREE needs to remain stable across all clones
of the repository.
----
The other fix is just fixing crazy and wrong code that, when GIT_DIR is
set, expects to still find a git repository in the path below the work
tree, and uses some of its configuration, and some of GIT_DIR. What was I
thinking, and why can't I seem to get this code right?
2013-02-23 16:32:09 +00:00
|
|
|
seekUp dir = do
|
|
|
|
r <- checkForRepo dir
|
2012-12-13 04:24:19 +00:00
|
|
|
case r of
|
2020-10-28 19:40:50 +00:00
|
|
|
Nothing -> case upFrom (toRawFilePath dir) of
|
2015-01-09 18:26:52 +00:00
|
|
|
Nothing -> return Nothing
|
2020-10-28 19:40:50 +00:00
|
|
|
Just d -> seekUp (fromRawFilePath d)
|
2015-02-12 19:33:05 +00:00
|
|
|
Just loc -> pure $ Just $ newFrom loc
|
2011-12-13 19:05:07 +00:00
|
|
|
|
2012-01-13 18:40:36 +00:00
|
|
|
{- Local Repo constructor, accepts a relative or absolute path. -}
|
2020-10-28 19:40:50 +00:00
|
|
|
fromPath :: RawFilePath -> IO Repo
|
avoid making absolute git remote path relative
When a git remote is configured with an absolute path, use that path,
rather than making it relative. If it's configured with a relative path,
use that.
Git.Construct.fromPath changed to preserve the path as-is,
rather than making it absolute. And Annex.new changed to not
convert the path to relative. Instead, Git.CurrentRepo.get
generates a relative path.
A few things that used fromAbsPath unncessarily were changed in passing to
use fromPath instead. I'm seeing fromAbsPath as a security check,
while before it was being used in some cases when the path was
known absolute already. It may be that fromAbsPath is not really needed,
but only git-annex-shell uses it now, and I'm not 100% sure that there's
not some input that would cause a relative path to be used, opening a
security hole, without the security check. So left it as-is.
Test suite passes and strace shows the configured remote url is used
unchanged in the path into it. I can't be 100% sure there's not some code
somewhere that takes an absolute path to the repo and converts it to
relative and uses it, but it seems pretty unlikely that the code paths used
for a git remote would call such code. One place I know of is gitAnnexLink,
but I'm pretty sure that git remotes never deal with annex symlinks. If
that did get called, it generates a path relative to cwd, which would have
been wrong before this change as well, when operating on a remote.
2021-02-08 17:18:01 +00:00
|
|
|
fromPath dir
|
|
|
|
-- When dir == "foo/.git", git looks for "foo/.git/.git",
|
|
|
|
-- and failing that, uses "foo" as the repository.
|
|
|
|
| (P.pathSeparator `B.cons` ".git") `B.isSuffixOf` canondir =
|
|
|
|
ifM (doesDirectoryExist $ fromRawFilePath dir </> ".git")
|
|
|
|
( ret dir
|
|
|
|
, ret (P.takeDirectory canondir)
|
|
|
|
)
|
|
|
|
| otherwise = ifM (doesDirectoryExist (fromRawFilePath dir))
|
|
|
|
( checkGitDirFile dir >>= maybe (ret dir) (pure . newFrom)
|
|
|
|
-- git falls back to dir.git when dir doesn't
|
|
|
|
-- exist, as long as dir didn't end with a
|
|
|
|
-- path separator
|
|
|
|
, if dir == canondir
|
|
|
|
then ret (dir <> ".git")
|
|
|
|
else ret dir
|
|
|
|
)
|
|
|
|
where
|
|
|
|
ret = pure . newFrom . LocalUnknown
|
|
|
|
canondir = P.dropTrailingPathSeparator dir
|
2012-01-13 18:40:36 +00:00
|
|
|
|
2011-12-13 19:05:07 +00:00
|
|
|
{- Local Repo constructor, requires an absolute path to the repo be
|
|
|
|
- specified. -}
|
2020-10-28 19:40:50 +00:00
|
|
|
fromAbsPath :: RawFilePath -> IO Repo
|
2011-12-13 19:05:07 +00:00
|
|
|
fromAbsPath dir
|
avoid making absolute git remote path relative
When a git remote is configured with an absolute path, use that path,
rather than making it relative. If it's configured with a relative path,
use that.
Git.Construct.fromPath changed to preserve the path as-is,
rather than making it absolute. And Annex.new changed to not
convert the path to relative. Instead, Git.CurrentRepo.get
generates a relative path.
A few things that used fromAbsPath unncessarily were changed in passing to
use fromPath instead. I'm seeing fromAbsPath as a security check,
while before it was being used in some cases when the path was
known absolute already. It may be that fromAbsPath is not really needed,
but only git-annex-shell uses it now, and I'm not 100% sure that there's
not some input that would cause a relative path to be used, opening a
security hole, without the security check. So left it as-is.
Test suite passes and strace shows the configured remote url is used
unchanged in the path into it. I can't be 100% sure there's not some code
somewhere that takes an absolute path to the repo and converts it to
relative and uses it, but it seems pretty unlikely that the code paths used
for a git remote would call such code. One place I know of is gitAnnexLink,
but I'm pretty sure that git remotes never deal with annex symlinks. If
that did get called, it generates a path relative to cwd, which would have
been wrong before this change as well, when operating on a remote.
2021-02-08 17:18:01 +00:00
|
|
|
| absoluteGitPath dir = fromPath dir
|
2012-03-16 05:59:07 +00:00
|
|
|
| otherwise =
|
2020-10-28 19:40:50 +00:00
|
|
|
error $ "internal error, " ++ show dir ++ " is not absolute"
|
2011-12-13 19:05:07 +00:00
|
|
|
|
2021-01-18 18:52:56 +00:00
|
|
|
{- Construct a Repo for a remote's url.
|
2012-01-05 18:32:20 +00:00
|
|
|
-
|
|
|
|
- Git is somewhat forgiving about urls to repositories, allowing
|
2021-01-18 18:52:56 +00:00
|
|
|
- eg spaces that are not normally allowed unescaped in urls. Such
|
|
|
|
- characters get escaped.
|
|
|
|
-
|
|
|
|
- This will always succeed, even if the url cannot be parsed
|
|
|
|
- or is invalid, because git can also function despite remotes having
|
|
|
|
- such urls, only failing if such a remote is used.
|
2012-01-05 18:32:20 +00:00
|
|
|
-}
|
2011-12-13 19:05:07 +00:00
|
|
|
fromUrl :: String -> IO Repo
|
|
|
|
fromUrl url
|
2021-01-18 18:52:56 +00:00
|
|
|
| not (isURI url) = fromUrl' $ escapeURIString isUnescapedInURI url
|
|
|
|
| otherwise = fromUrl' url
|
2012-01-05 18:32:20 +00:00
|
|
|
|
2021-01-18 18:52:56 +00:00
|
|
|
fromUrl' :: String -> IO Repo
|
|
|
|
fromUrl' url
|
|
|
|
| "file://" `isPrefixOf` url = case parseURI url of
|
|
|
|
Just u -> fromAbsPath $ toRawFilePath $ unEscapeString $ uriPath u
|
|
|
|
Nothing -> pure $ newFrom $ UnparseableUrl url
|
|
|
|
| otherwise = case parseURI url of
|
|
|
|
Just u -> pure $ newFrom $ Url u
|
|
|
|
Nothing -> pure $ newFrom $ UnparseableUrl url
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Creates a repo that has an unknown location. -}
|
2015-02-12 19:33:05 +00:00
|
|
|
fromUnknown :: Repo
|
2012-01-14 01:06:00 +00:00
|
|
|
fromUnknown = newFrom Unknown
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Converts a local Repo into a remote repo, using the reference repo
|
|
|
|
- which is assumed to be on the same host. -}
|
|
|
|
localToUrl :: Repo -> Repo -> Repo
|
|
|
|
localToUrl reference r
|
|
|
|
| not $ repoIsUrl reference = error "internal error; reference repo not url"
|
|
|
|
| repoIsUrl r = r
|
2021-01-18 19:07:23 +00:00
|
|
|
| otherwise = case (Url.authority reference, Url.scheme reference) of
|
|
|
|
(Just auth, Just s) ->
|
2013-11-04 18:14:44 +00:00
|
|
|
let absurl = concat
|
2021-01-18 19:07:23 +00:00
|
|
|
[ s
|
2013-11-04 18:14:44 +00:00
|
|
|
, "//"
|
|
|
|
, auth
|
2019-12-09 17:49:05 +00:00
|
|
|
, fromRawFilePath (repoPath r)
|
2013-11-04 18:14:44 +00:00
|
|
|
]
|
|
|
|
in r { location = Url $ fromJust $ parseURI absurl }
|
2021-01-18 19:07:23 +00:00
|
|
|
_ -> r
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Calculates a list of a repo's configured remotes, by parsing its config. -}
|
|
|
|
fromRemotes :: Repo -> IO [Repo]
|
2021-04-23 17:28:23 +00:00
|
|
|
fromRemotes repo = catMaybes <$> mapM construct remotepairs
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
filterconfig f = filter f $ M.toList $ config repo
|
|
|
|
filterkeys f = filterconfig (\(k,_) -> f k)
|
2021-04-23 17:28:23 +00:00
|
|
|
remotepairs = filterkeys isRemoteUrlKey
|
2020-11-02 20:31:28 +00:00
|
|
|
construct (k,v) = remoteNamedFromKey k $
|
|
|
|
fromRemoteLocation (fromConfigValue v) repo
|
2011-12-14 19:30:14 +00:00
|
|
|
|
|
|
|
{- Sets the name of a remote when constructing the Repo to represent it. -}
|
|
|
|
remoteNamed :: String -> IO Repo -> IO Repo
|
|
|
|
remoteNamed n constructor = do
|
|
|
|
r <- constructor
|
|
|
|
return $ r { remoteName = Just n }
|
|
|
|
|
|
|
|
{- Sets the name of a remote based on the git config key, such as
|
2012-12-13 04:45:27 +00:00
|
|
|
- "remote.foo.url". -}
|
2021-04-23 17:28:23 +00:00
|
|
|
remoteNamedFromKey :: ConfigKey -> IO Repo -> IO (Maybe Repo)
|
|
|
|
remoteNamedFromKey k r = case remoteKeyToRemoteName k of
|
|
|
|
Nothing -> pure Nothing
|
|
|
|
Just n -> Just <$> remoteNamed n r
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Constructs a new Repo for one of a Repo's remotes using a given
|
|
|
|
- location (ie, an url). -}
|
|
|
|
fromRemoteLocation :: String -> Repo -> IO Repo
|
2013-09-26 21:26:13 +00:00
|
|
|
fromRemoteLocation s repo = gen $ parseRemoteLocation s repo
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
2013-09-26 21:26:13 +00:00
|
|
|
gen (RemotePath p) = fromRemotePath p repo
|
|
|
|
gen (RemoteUrl u) = fromUrl u
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Constructs a Repo from the path specified in the git remotes of
|
|
|
|
- another Repo. -}
|
|
|
|
fromRemotePath :: FilePath -> Repo -> IO Repo
|
|
|
|
fromRemotePath dir repo = do
|
|
|
|
dir' <- expandTilde dir
|
2020-10-28 19:40:50 +00:00
|
|
|
fromPath $ repoPath repo P.</> toRawFilePath dir'
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
{- Git remotes can have a directory that is specified relative
|
|
|
|
- to the user's home directory, or that contains tilde expansions.
|
|
|
|
- This converts such a directory to an absolute path.
|
|
|
|
- Note that it has to run on the system where the remote is.
|
|
|
|
-}
|
2020-11-04 18:20:37 +00:00
|
|
|
repoAbsPath :: RawFilePath -> IO RawFilePath
|
2011-12-13 19:05:07 +00:00
|
|
|
repoAbsPath d = do
|
2020-11-04 18:20:37 +00:00
|
|
|
d' <- expandTilde (fromRawFilePath d)
|
2011-12-13 19:05:07 +00:00
|
|
|
h <- myHomeDir
|
2020-11-04 18:20:37 +00:00
|
|
|
return $ toRawFilePath $ h </> d'
|
2011-12-13 19:05:07 +00:00
|
|
|
|
|
|
|
expandTilde :: FilePath -> IO FilePath
|
2013-08-02 16:27:32 +00:00
|
|
|
#ifdef mingw32_HOST_OS
|
2013-05-11 20:03:00 +00:00
|
|
|
expandTilde = return
|
|
|
|
#else
|
2021-10-13 01:17:13 +00:00
|
|
|
expandTilde p = expandt True p
|
|
|
|
-- If unable to expand a tilde, eg due to a user not existing,
|
|
|
|
-- use the path as given.
|
|
|
|
`catchNonAsync` (const (return p))
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
expandt _ [] = return ""
|
|
|
|
expandt _ ('/':cs) = do
|
|
|
|
v <- expandt True cs
|
|
|
|
return ('/':v)
|
|
|
|
expandt True ('~':'/':cs) = do
|
|
|
|
h <- myHomeDir
|
|
|
|
return $ h </> cs
|
2021-01-18 16:22:48 +00:00
|
|
|
expandt True "~" = myHomeDir
|
2012-12-13 04:24:19 +00:00
|
|
|
expandt True ('~':cs) = do
|
|
|
|
let (name, rest) = findname "" cs
|
|
|
|
u <- getUserEntryForName name
|
|
|
|
return $ homeDirectory u </> rest
|
|
|
|
expandt _ (c:cs) = do
|
|
|
|
v <- expandt False cs
|
|
|
|
return (c:v)
|
|
|
|
findname n [] = (n, "")
|
|
|
|
findname n (c:cs)
|
|
|
|
| c == '/' = (n, cs)
|
|
|
|
| otherwise = findname (n++[c]) cs
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2011-12-13 19:05:07 +00:00
|
|
|
|
2013-03-12 12:09:31 +00:00
|
|
|
{- Checks if a git repository exists in a directory. Does not find
|
|
|
|
- git repositories in parent directories. -}
|
2012-09-16 02:40:04 +00:00
|
|
|
checkForRepo :: FilePath -> IO (Maybe RepoLocation)
|
|
|
|
checkForRepo dir =
|
|
|
|
check isRepo $
|
2020-10-28 19:40:50 +00:00
|
|
|
check (checkGitDirFile (toRawFilePath dir)) $
|
2012-09-16 02:40:04 +00:00
|
|
|
check isBareRepo $
|
|
|
|
return Nothing
|
2012-12-13 04:24:19 +00:00
|
|
|
where
|
|
|
|
check test cont = maybe cont (return . Just) =<< test
|
|
|
|
checkdir c = ifM c
|
2019-12-09 17:49:05 +00:00
|
|
|
( return $ Just $ LocalUnknown $ toRawFilePath dir
|
2012-12-13 04:24:19 +00:00
|
|
|
, return Nothing
|
|
|
|
)
|
2018-07-18 18:25:03 +00:00
|
|
|
isRepo = checkdir $
|
|
|
|
gitSignature (".git" </> "config")
|
|
|
|
<||>
|
|
|
|
-- A git-worktree lacks .git/config, but has .git/commondir.
|
|
|
|
-- (Normally the .git is a file, not a symlink, but it can
|
|
|
|
-- be converted to a symlink and git will still work;
|
|
|
|
-- this handles that case.)
|
|
|
|
gitSignature (".git" </> "gitdir")
|
2012-12-13 04:24:19 +00:00
|
|
|
isBareRepo = checkdir $ gitSignature "config"
|
|
|
|
<&&> doesDirectoryExist (dir </> "objects")
|
|
|
|
gitSignature file = doesFileExist $ dir </> file
|
2011-12-13 19:05:07 +00:00
|
|
|
|
2020-10-23 18:56:12 +00:00
|
|
|
-- Check for a .git file.
|
2020-10-28 19:40:50 +00:00
|
|
|
checkGitDirFile :: RawFilePath -> IO (Maybe RepoLocation)
|
2020-10-23 18:56:12 +00:00
|
|
|
checkGitDirFile dir = adjustGitDirFile' $ Local
|
2020-10-28 19:40:50 +00:00
|
|
|
{ gitdir = dir P.</> ".git"
|
|
|
|
, worktree = Just dir
|
2020-10-23 18:56:12 +00:00
|
|
|
}
|
|
|
|
|
2020-08-28 19:08:14 +00:00
|
|
|
-- git-submodule, git-worktree, and --separate-git-dir
|
|
|
|
-- make .git be a file pointing to the real git directory.
|
|
|
|
-- Detect that, and return a RepoLocation with gitdir pointing
|
|
|
|
-- to the real git directory.
|
2020-10-23 18:56:12 +00:00
|
|
|
adjustGitDirFile :: RepoLocation -> IO RepoLocation
|
|
|
|
adjustGitDirFile loc = fromMaybe loc <$> adjustGitDirFile' loc
|
|
|
|
|
|
|
|
adjustGitDirFile' :: RepoLocation -> IO (Maybe RepoLocation)
|
|
|
|
adjustGitDirFile' loc = do
|
2020-10-28 19:40:50 +00:00
|
|
|
let gd = gitdir loc
|
|
|
|
c <- firstLine <$> catchDefaultIO "" (readFile (fromRawFilePath gd))
|
2020-10-23 18:56:12 +00:00
|
|
|
if gitdirprefix `isPrefixOf` c
|
|
|
|
then do
|
2020-10-28 19:40:50 +00:00
|
|
|
top <- fromRawFilePath . P.takeDirectory <$> absPath gd
|
2020-10-23 18:56:12 +00:00
|
|
|
return $ Just $ loc
|
2020-10-28 19:40:50 +00:00
|
|
|
{ gitdir = absPathFrom
|
|
|
|
(toRawFilePath top)
|
|
|
|
(toRawFilePath
|
|
|
|
(drop (length gitdirprefix) c))
|
2020-10-23 18:56:12 +00:00
|
|
|
}
|
|
|
|
else return Nothing
|
2020-08-28 19:08:14 +00:00
|
|
|
where
|
|
|
|
gitdirprefix = "gitdir: "
|
|
|
|
|
2020-10-23 18:56:12 +00:00
|
|
|
|
2015-02-12 19:33:05 +00:00
|
|
|
newFrom :: RepoLocation -> Repo
|
|
|
|
newFrom l = Repo
|
2012-01-14 01:06:00 +00:00
|
|
|
{ location = l
|
|
|
|
, config = M.empty
|
|
|
|
, fullconfig = M.empty
|
|
|
|
, remoteName = Nothing
|
2012-08-25 00:50:39 +00:00
|
|
|
, gitEnv = Nothing
|
2016-04-08 18:24:00 +00:00
|
|
|
, gitEnvOverridesGitDir = False
|
2013-11-05 17:38:37 +00:00
|
|
|
, gitGlobalOpts = []
|
2011-12-13 19:05:07 +00:00
|
|
|
}
|
2012-05-18 22:20:53 +00:00
|
|
|
|