summaryrefslogtreecommitdiff
path: root/Git.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git.hs')
-rw-r--r--Git.hs48
1 files changed, 29 insertions, 19 deletions
diff --git a/Git.hs b/Git.hs
index 1bc789f..87a8d19 100644
--- a/Git.hs
+++ b/Git.hs
@@ -5,7 +5,7 @@
-
- Copyright 2010-2012 Joey Hess <id@joeyh.name>
-
- - Licensed under the GNU GPL version 3 or higher.
+ - Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
@@ -26,8 +26,10 @@ module Git (
repoDescribe,
repoLocation,
repoPath,
+ repoWorkTree,
localGitDir,
attributes,
+ attributesLocal,
hookPath,
assertLocal,
adjustPath,
@@ -49,31 +51,35 @@ import Utility.FileMode
repoDescribe :: Repo -> String
repoDescribe Repo { remoteName = Just name } = name
repoDescribe Repo { location = Url url } = show url
-repoDescribe Repo { location = Local { worktree = Just dir } } = dir
-repoDescribe Repo { location = Local { gitdir = dir } } = dir
-repoDescribe Repo { location = LocalUnknown dir } = dir
+repoDescribe Repo { location = Local { worktree = Just dir } } = fromRawFilePath dir
+repoDescribe Repo { location = Local { gitdir = dir } } = fromRawFilePath dir
+repoDescribe Repo { location = LocalUnknown dir } = fromRawFilePath dir
repoDescribe Repo { location = Unknown } = "UNKNOWN"
{- Location of the repo, either as a path or url. -}
repoLocation :: Repo -> String
repoLocation Repo { location = Url url } = show url
-repoLocation Repo { location = Local { worktree = Just dir } } = dir
-repoLocation Repo { location = Local { gitdir = dir } } = dir
-repoLocation Repo { location = LocalUnknown dir } = dir
+repoLocation Repo { location = Local { worktree = Just dir } } = fromRawFilePath dir
+repoLocation Repo { location = Local { gitdir = dir } } = fromRawFilePath dir
+repoLocation Repo { location = LocalUnknown dir } = fromRawFilePath dir
repoLocation Repo { location = Unknown } = error "unknown repoLocation"
{- Path to a repository. For non-bare, this is the worktree, for bare,
- it's the gitdir, and for URL repositories, is the path on the remote
- host. -}
-repoPath :: Repo -> FilePath
-repoPath Repo { location = Url u } = unEscapeString $ uriPath u
+repoPath :: Repo -> RawFilePath
+repoPath Repo { location = Url u } = toRawFilePath $ unEscapeString $ uriPath u
repoPath Repo { location = Local { worktree = Just d } } = d
repoPath Repo { location = Local { gitdir = d } } = d
repoPath Repo { location = LocalUnknown dir } = dir
repoPath Repo { location = Unknown } = error "unknown repoPath"
+repoWorkTree :: Repo -> Maybe RawFilePath
+repoWorkTree Repo { location = Local { worktree = Just d } } = Just d
+repoWorkTree _ = Nothing
+
{- Path to a local repository's .git directory. -}
-localGitDir :: Repo -> FilePath
+localGitDir :: Repo -> RawFilePath
localGitDir Repo { location = Local { gitdir = d } } = d
localGitDir _ = error "unknown localGitDir"
@@ -125,14 +131,18 @@ assertLocal repo action
{- Path to a repository's gitattributes file. -}
attributes :: Repo -> FilePath
attributes repo
- | repoIsLocalBare repo = repoPath repo ++ "/info/.gitattributes"
- | otherwise = repoPath repo ++ "/.gitattributes"
+ | repoIsLocalBare repo = attributesLocal repo
+ | otherwise = fromRawFilePath (repoPath repo) </> ".gitattributes"
+
+attributesLocal :: Repo -> FilePath
+attributesLocal repo = fromRawFilePath (localGitDir repo)
+ </> "info" </> "attributes"
{- Path to a given hook script in a repository, only if the hook exists
- and is executable. -}
hookPath :: String -> Repo -> IO (Maybe FilePath)
hookPath script repo = do
- let hook = localGitDir repo </> "hooks" </> script
+ let hook = fromRawFilePath (localGitDir repo) </> "hooks" </> script
ifM (catchBoolIO $ isexecutable hook)
( return $ Just hook , return Nothing )
where
@@ -148,22 +158,22 @@ relPath = adjustPath torel
where
torel p = do
p' <- relPathCwdToFile p
- if null p'
- then return "."
- else return p'
+ return $ if null p' then "." else p'
{- Adusts the path to a local Repo using the provided function. -}
adjustPath :: (FilePath -> IO FilePath) -> Repo -> IO Repo
adjustPath f r@(Repo { location = l@(Local { gitdir = d, worktree = w }) }) = do
- d' <- f d
- w' <- maybe (pure Nothing) (Just <$$> f) w
+ d' <- f' d
+ w' <- maybe (pure Nothing) (Just <$$> f') w
return $ r
{ location = l
{ gitdir = d'
, worktree = w'
}
}
+ where
+ f' v = toRawFilePath <$> f (fromRawFilePath v)
adjustPath f r@(Repo { location = LocalUnknown d }) = do
- d' <- f d
+ d' <- toRawFilePath <$> f (fromRawFilePath d)
return $ r { location = LocalUnknown d' }
adjustPath _ r = pure r