removed another 10 lines via ifM
This commit is contained in:
parent
c0c9991c9f
commit
184a69171d
9 changed files with 95 additions and 106 deletions
24
Git.hs
24
Git.hs
|
@ -31,7 +31,6 @@ module Git (
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import Network.URI (uriPath, uriScheme, unEscapeString)
|
import Network.URI (uriPath, uriScheme, unEscapeString)
|
||||||
import System.Directory
|
|
||||||
import System.Posix.Files
|
import System.Posix.Files
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
@ -83,11 +82,14 @@ repoIsLocalBare r@(Repo { location = Dir _ }) = configAvail r && configBare r
|
||||||
repoIsLocalBare _ = False
|
repoIsLocalBare _ = False
|
||||||
|
|
||||||
assertLocal :: Repo -> a -> a
|
assertLocal :: Repo -> a -> a
|
||||||
assertLocal repo action =
|
assertLocal repo action
|
||||||
if not $ repoIsUrl repo
|
| repoIsUrl repo = error $ unwords
|
||||||
then action
|
[ "acting on non-local git repo"
|
||||||
else error $ "acting on non-local git repo " ++ repoDescribe repo ++
|
, repoDescribe repo
|
||||||
" not supported"
|
, "not supported"
|
||||||
|
]
|
||||||
|
| otherwise = action
|
||||||
|
|
||||||
configBare :: Repo -> Bool
|
configBare :: Repo -> Bool
|
||||||
configBare repo = maybe unknown (fromMaybe False . configTrue) $
|
configBare repo = maybe unknown (fromMaybe False . configTrue) $
|
||||||
M.lookup "core.bare" $ config repo
|
M.lookup "core.bare" $ config repo
|
||||||
|
@ -113,12 +115,10 @@ gitDir repo
|
||||||
hookPath :: String -> Repo -> IO (Maybe FilePath)
|
hookPath :: String -> Repo -> IO (Maybe FilePath)
|
||||||
hookPath script repo = do
|
hookPath script repo = do
|
||||||
let hook = gitDir repo </> "hooks" </> script
|
let hook = gitDir repo </> "hooks" </> script
|
||||||
e <- doesFileExist hook
|
ifM (catchBoolIO $ isexecutable hook)
|
||||||
if e
|
( return $ Just hook , return Nothing )
|
||||||
then do
|
where
|
||||||
m <- fileMode <$> getFileStatus hook
|
isexecutable f = isExecutable . fileMode <$> getFileStatus f
|
||||||
return $ if isExecutable m then Just hook else Nothing
|
|
||||||
else return Nothing
|
|
||||||
|
|
||||||
{- Path to a repository's --work-tree, that is, its top.
|
{- Path to a repository's --work-tree, that is, its top.
|
||||||
-
|
-
|
||||||
|
|
|
@ -41,14 +41,14 @@ changed origbranch newbranch repo
|
||||||
-}
|
-}
|
||||||
fastForward :: Branch -> [Ref] -> Repo -> IO Bool
|
fastForward :: Branch -> [Ref] -> Repo -> IO Bool
|
||||||
fastForward _ [] _ = return True
|
fastForward _ [] _ = return True
|
||||||
fastForward branch (first:rest) repo = do
|
fastForward branch (first:rest) repo =
|
||||||
-- First, check that the branch does not contain any
|
-- First, check that the branch does not contain any
|
||||||
-- new commits that are not in the first ref. If it does,
|
-- new commits that are not in the first ref. If it does,
|
||||||
-- cannot fast-forward.
|
-- cannot fast-forward.
|
||||||
diverged <- changed first branch repo
|
ifM (changed first branch repo)
|
||||||
if diverged
|
( no_ff
|
||||||
then no_ff
|
, maybe no_ff do_ff =<< findbest first rest
|
||||||
else maybe no_ff do_ff =<< findbest first rest
|
)
|
||||||
where
|
where
|
||||||
no_ff = return False
|
no_ff = return False
|
||||||
do_ff to = do
|
do_ff to = do
|
||||||
|
|
|
@ -26,16 +26,15 @@ getMaybe key repo = M.lookup key (config repo)
|
||||||
|
|
||||||
{- Runs git config and populates a repo with its config. -}
|
{- Runs git config and populates a repo with its config. -}
|
||||||
read :: Repo -> IO Repo
|
read :: Repo -> IO Repo
|
||||||
read repo@(Repo { location = Dir d }) = do
|
read repo@(Repo { location = Dir d }) = bracketcd d $
|
||||||
{- Cannot use pipeRead because it relies on the config having
|
{- Cannot use pipeRead because it relies on the config having
|
||||||
been already read. Instead, chdir to the repo. -}
|
been already read. Instead, chdir to the repo. -}
|
||||||
cwd <- getCurrentDirectory
|
pOpen ReadFromPipe "git" ["config", "--null", "--list"] $ hRead repo
|
||||||
if dirContains d cwd
|
|
||||||
then go
|
|
||||||
else bracket_ (changeWorkingDirectory d) (changeWorkingDirectory cwd) go
|
|
||||||
where
|
where
|
||||||
go = pOpen ReadFromPipe "git" ["config", "--null", "--list"] $
|
bracketcd to a = bracketcd' to a =<< getCurrentDirectory
|
||||||
hRead repo
|
bracketcd' to a cwd
|
||||||
|
| dirContains to cwd = a
|
||||||
|
| otherwise = bracket_ (changeWorkingDirectory to) (changeWorkingDirectory cwd) a
|
||||||
read r = assertLocal r $
|
read r = assertLocal r $
|
||||||
error $ "internal error; trying to read config of " ++ show r
|
error $ "internal error; trying to read config of " ++ show r
|
||||||
|
|
||||||
|
|
|
@ -69,27 +69,25 @@ fromPath dir = fromAbsPath =<< absPath dir
|
||||||
- specified. -}
|
- specified. -}
|
||||||
fromAbsPath :: FilePath -> IO Repo
|
fromAbsPath :: FilePath -> IO Repo
|
||||||
fromAbsPath dir
|
fromAbsPath dir
|
||||||
| "/" `isPrefixOf` dir = do
|
| "/" `isPrefixOf` dir =
|
||||||
-- Git always looks for "dir.git" in preference to
|
ifM (doesDirectoryExist dir') ( ret dir' , hunt )
|
||||||
-- to "dir", even if dir ends in a "/".
|
| otherwise =
|
||||||
let canondir = dropTrailingPathSeparator dir
|
error $ "internal error, " ++ dir ++ " is not absolute"
|
||||||
let dir' = canondir ++ ".git"
|
|
||||||
e <- doesDirectoryExist dir'
|
|
||||||
if e
|
|
||||||
then ret dir'
|
|
||||||
else if "/.git" `isSuffixOf` canondir
|
|
||||||
then do
|
|
||||||
-- When dir == "foo/.git", git looks
|
|
||||||
-- for "foo/.git/.git", and failing
|
|
||||||
-- that, uses "foo" as the repository.
|
|
||||||
e' <- doesDirectoryExist $ dir </> ".git"
|
|
||||||
if e'
|
|
||||||
then ret dir
|
|
||||||
else ret $ takeDirectory canondir
|
|
||||||
else ret dir
|
|
||||||
| otherwise = error $ "internal error, " ++ dir ++ " is not absolute"
|
|
||||||
where
|
where
|
||||||
ret = newFrom . Dir
|
ret = newFrom . Dir
|
||||||
|
{- Git always looks for "dir.git" in preference to
|
||||||
|
- to "dir", even if dir ends in a "/". -}
|
||||||
|
canondir = dropTrailingPathSeparator dir
|
||||||
|
dir' = canondir ++ ".git"
|
||||||
|
{- When dir == "foo/.git", git looks for "foo/.git/.git",
|
||||||
|
- and failing that, uses "foo" as the repository. -}
|
||||||
|
hunt
|
||||||
|
| "/.git" `isSuffixOf` canondir =
|
||||||
|
ifM (doesDirectoryExist $ dir </> ".git")
|
||||||
|
( ret dir
|
||||||
|
, ret $ takeDirectory canondir
|
||||||
|
)
|
||||||
|
| otherwise = ret dir
|
||||||
|
|
||||||
{- Remote Repo constructor. Throws exception on invalid url.
|
{- Remote Repo constructor. Throws exception on invalid url.
|
||||||
-
|
-
|
||||||
|
@ -229,27 +227,20 @@ expandTilde = expandt True
|
||||||
| otherwise = findname (n++[c]) cs
|
| otherwise = findname (n++[c]) cs
|
||||||
|
|
||||||
seekUp :: (FilePath -> IO Bool) -> FilePath -> IO (Maybe FilePath)
|
seekUp :: (FilePath -> IO Bool) -> FilePath -> IO (Maybe FilePath)
|
||||||
seekUp want dir = do
|
seekUp want dir =
|
||||||
ok <- want dir
|
ifM (want dir)
|
||||||
if ok
|
( return $ Just dir
|
||||||
then return $ Just dir
|
, case parentDir dir of
|
||||||
else case parentDir dir of
|
|
||||||
"" -> return Nothing
|
"" -> return Nothing
|
||||||
d -> seekUp want d
|
d -> seekUp want d
|
||||||
|
)
|
||||||
|
|
||||||
isRepoTop :: FilePath -> IO Bool
|
isRepoTop :: FilePath -> IO Bool
|
||||||
isRepoTop dir = do
|
isRepoTop dir = ifM isRepo ( return True , isBareRepo )
|
||||||
r <- isRepo
|
|
||||||
if r
|
|
||||||
then return r
|
|
||||||
else isBareRepo
|
|
||||||
where
|
where
|
||||||
isRepo = gitSignature (".git" </> "config")
|
isRepo = gitSignature (".git" </> "config")
|
||||||
isBareRepo = do
|
isBareRepo = ifM (doesDirectoryExist $ dir </> "objects")
|
||||||
e <- doesDirectoryExist (dir </> "objects")
|
( gitSignature "config" , return False )
|
||||||
if not e
|
|
||||||
then return e
|
|
||||||
else gitSignature "config"
|
|
||||||
gitSignature file = doesFileExist (dir </> file)
|
gitSignature file = doesFileExist (dir </> file)
|
||||||
|
|
||||||
newFrom :: RepoLocation -> IO Repo
|
newFrom :: RepoLocation -> IO Repo
|
||||||
|
|
10
Init.hs
10
Init.hs
|
@ -58,13 +58,13 @@ gitPreCommitHookWrite = unlessBare $ do
|
||||||
gitPreCommitHookUnWrite :: Annex ()
|
gitPreCommitHookUnWrite :: Annex ()
|
||||||
gitPreCommitHookUnWrite = unlessBare $ do
|
gitPreCommitHookUnWrite = unlessBare $ do
|
||||||
hook <- preCommitHook
|
hook <- preCommitHook
|
||||||
whenM (liftIO $ doesFileExist hook) $ do
|
whenM (liftIO $ doesFileExist hook) $
|
||||||
c <- liftIO $ readFile hook
|
ifM (liftIO $ (==) preCommitScript <$> readFile hook)
|
||||||
if c == preCommitScript
|
( liftIO $ removeFile hook
|
||||||
then liftIO $ removeFile hook
|
, warning $ "pre-commit hook (" ++ hook ++
|
||||||
else warning $ "pre-commit hook (" ++ hook ++
|
|
||||||
") contents modified; not deleting." ++
|
") contents modified; not deleting." ++
|
||||||
" Edit it to remove call to git annex."
|
" Edit it to remove call to git annex."
|
||||||
|
)
|
||||||
|
|
||||||
unlessBare :: Annex () -> Annex ()
|
unlessBare :: Annex () -> Annex ()
|
||||||
unlessBare = unlessM $ fromRepo Git.repoIsLocalBare
|
unlessBare = unlessM $ fromRepo Git.repoIsLocalBare
|
||||||
|
|
|
@ -99,10 +99,9 @@ type LogMap = M.Map String LogLine
|
||||||
{- Inserts a log into a map of logs, if the log has better (ie, newer)
|
{- Inserts a log into a map of logs, if the log has better (ie, newer)
|
||||||
- information than the other logs in the map -}
|
- information than the other logs in the map -}
|
||||||
mapLog :: LogLine -> LogMap -> LogMap
|
mapLog :: LogLine -> LogMap -> LogMap
|
||||||
mapLog l m =
|
mapLog l m
|
||||||
if better
|
| better = M.insert i l m
|
||||||
then M.insert i l m
|
| otherwise = m
|
||||||
else m
|
|
||||||
where
|
where
|
||||||
better = maybe True newer $ M.lookup i m
|
better = maybe True newer $ M.lookup i m
|
||||||
newer l' = date l' <= date l
|
newer l' = date l' <= date l
|
||||||
|
|
|
@ -72,14 +72,15 @@ configUnEscape = unescape
|
||||||
unescape (c:rest)
|
unescape (c:rest)
|
||||||
| c == '&' = entity rest
|
| c == '&' = entity rest
|
||||||
| otherwise = c : unescape rest
|
| otherwise = c : unescape rest
|
||||||
entity s = if ok
|
entity s
|
||||||
then chr (Prelude.read num) : unescape rest
|
| not (null num) && ";" `isPrefixOf` r =
|
||||||
else '&' : unescape s
|
chr (Prelude.read num) : unescape rest
|
||||||
|
| otherwise =
|
||||||
|
'&' : unescape s
|
||||||
where
|
where
|
||||||
num = takeWhile isNumber s
|
num = takeWhile isNumber s
|
||||||
r = drop (length num) s
|
r = drop (length num) s
|
||||||
rest = drop 1 r
|
rest = drop 1 r
|
||||||
ok = not (null num) && ";" `isPrefixOf` r
|
|
||||||
|
|
||||||
{- for quickcheck -}
|
{- for quickcheck -}
|
||||||
prop_idempotent_configEscape :: String -> Bool
|
prop_idempotent_configEscape :: String -> Bool
|
||||||
|
|
|
@ -35,14 +35,11 @@ lookupFile0 :: FilePath -> Annex (Maybe (Key, Backend))
|
||||||
lookupFile0 = Upgrade.V1.lookupFile1
|
lookupFile0 = Upgrade.V1.lookupFile1
|
||||||
|
|
||||||
getKeysPresent0 :: FilePath -> Annex [Key]
|
getKeysPresent0 :: FilePath -> Annex [Key]
|
||||||
getKeysPresent0 dir = do
|
getKeysPresent0 dir = ifM (liftIO $ doesDirectoryExist dir)
|
||||||
exists <- liftIO $ doesDirectoryExist dir
|
( liftIO $ map fileKey0
|
||||||
if not exists
|
<$> (filterM present =<< getDirectoryContents dir)
|
||||||
then return []
|
, return []
|
||||||
else do
|
)
|
||||||
contents <- liftIO $ getDirectoryContents dir
|
|
||||||
files <- liftIO $ filterM present contents
|
|
||||||
return $ map fileKey0 files
|
|
||||||
where
|
where
|
||||||
present d = do
|
present d = do
|
||||||
result <- tryIO $
|
result <- tryIO $
|
||||||
|
|
|
@ -50,18 +50,18 @@ upgrade :: Annex Bool
|
||||||
upgrade = do
|
upgrade = do
|
||||||
showAction "v1 to v2"
|
showAction "v1 to v2"
|
||||||
|
|
||||||
bare <- fromRepo Git.repoIsLocalBare
|
ifM (fromRepo Git.repoIsLocalBare)
|
||||||
if bare
|
( do
|
||||||
then do
|
|
||||||
moveContent
|
moveContent
|
||||||
setVersion
|
setVersion
|
||||||
else do
|
, do
|
||||||
moveContent
|
moveContent
|
||||||
updateSymlinks
|
updateSymlinks
|
||||||
moveLocationLogs
|
moveLocationLogs
|
||||||
|
|
||||||
Annex.Queue.flush True
|
Annex.Queue.flush True
|
||||||
setVersion
|
setVersion
|
||||||
|
)
|
||||||
|
|
||||||
Upgrade.V2.upgrade
|
Upgrade.V2.upgrade
|
||||||
|
|
||||||
|
@ -104,12 +104,11 @@ moveLocationLogs = do
|
||||||
where
|
where
|
||||||
oldlocationlogs = do
|
oldlocationlogs = do
|
||||||
dir <- fromRepo Upgrade.V2.gitStateDir
|
dir <- fromRepo Upgrade.V2.gitStateDir
|
||||||
exists <- liftIO $ doesDirectoryExist dir
|
ifM (liftIO $ doesDirectoryExist dir)
|
||||||
if exists
|
( mapMaybe oldlog2key
|
||||||
then do
|
<$> (liftIO $ getDirectoryContents dir)
|
||||||
contents <- liftIO $ getDirectoryContents dir
|
, return []
|
||||||
return $ mapMaybe oldlog2key contents
|
)
|
||||||
else return []
|
|
||||||
move (l, k) = do
|
move (l, k) = do
|
||||||
dest <- fromRepo $ logFile2 k
|
dest <- fromRepo $ logFile2 k
|
||||||
dir <- fromRepo Upgrade.V2.gitStateDir
|
dir <- fromRepo Upgrade.V2.gitStateDir
|
||||||
|
@ -127,14 +126,13 @@ moveLocationLogs = do
|
||||||
Annex.Queue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f]
|
Annex.Queue.add "rm" [Param "--quiet", Param "-f", Param "--"] [f]
|
||||||
|
|
||||||
oldlog2key :: FilePath -> Maybe (FilePath, Key)
|
oldlog2key :: FilePath -> Maybe (FilePath, Key)
|
||||||
oldlog2key l =
|
oldlog2key l
|
||||||
let len = length l - 4 in
|
| drop len l == ".log" && sane = Just (l, k)
|
||||||
if drop len l == ".log"
|
| otherwise = Nothing
|
||||||
then let k = readKey1 (take len l) in
|
where
|
||||||
if null (keyName k) || null (keyBackendName k)
|
len = length l - 4
|
||||||
then Nothing
|
k = readKey1 (take len l)
|
||||||
else Just (l, k)
|
sane = (not . null $ keyName k) && (not . null $ keyBackendName k)
|
||||||
else Nothing
|
|
||||||
|
|
||||||
-- WORM backend keys: "WORM:mtime:size:filename"
|
-- WORM backend keys: "WORM:mtime:size:filename"
|
||||||
-- all the rest: "backend:key"
|
-- all the rest: "backend:key"
|
||||||
|
@ -143,10 +141,14 @@ oldlog2key l =
|
||||||
-- v2 and v1; that infelicity is worked around by treating the value
|
-- v2 and v1; that infelicity is worked around by treating the value
|
||||||
-- as the v2 key that it is.
|
-- as the v2 key that it is.
|
||||||
readKey1 :: String -> Key
|
readKey1 :: String -> Key
|
||||||
readKey1 v =
|
readKey1 v
|
||||||
if mixup
|
| mixup = fromJust $ readKey $ join ":" $ Prelude.tail bits
|
||||||
then fromJust $ readKey $ join ":" $ Prelude.tail bits
|
| otherwise = Key
|
||||||
else Key { keyName = n , keyBackendName = b, keySize = s, keyMtime = t }
|
{ keyName = n
|
||||||
|
, keyBackendName = b
|
||||||
|
, keySize = s
|
||||||
|
, keyMtime = t
|
||||||
|
}
|
||||||
where
|
where
|
||||||
bits = split ":" v
|
bits = split ":" v
|
||||||
b = Prelude.head bits
|
b = Prelude.head bits
|
||||||
|
@ -205,14 +207,14 @@ lookupFile1 file = do
|
||||||
getKeyFilesPresent1 :: Annex [FilePath]
|
getKeyFilesPresent1 :: Annex [FilePath]
|
||||||
getKeyFilesPresent1 = getKeyFilesPresent1' =<< fromRepo gitAnnexObjectDir
|
getKeyFilesPresent1 = getKeyFilesPresent1' =<< fromRepo gitAnnexObjectDir
|
||||||
getKeyFilesPresent1' :: FilePath -> Annex [FilePath]
|
getKeyFilesPresent1' :: FilePath -> Annex [FilePath]
|
||||||
getKeyFilesPresent1' dir = do
|
getKeyFilesPresent1' dir =
|
||||||
exists <- liftIO $ doesDirectoryExist dir
|
ifM (liftIO $ doesDirectoryExist dir)
|
||||||
if not exists
|
( do
|
||||||
then return []
|
|
||||||
else do
|
|
||||||
dirs <- liftIO $ getDirectoryContents dir
|
dirs <- liftIO $ getDirectoryContents dir
|
||||||
let files = map (\d -> dir ++ "/" ++ d ++ "/" ++ takeFileName d) dirs
|
let files = map (\d -> dir ++ "/" ++ d ++ "/" ++ takeFileName d) dirs
|
||||||
liftIO $ filterM present files
|
liftIO $ filterM present files
|
||||||
|
, return []
|
||||||
|
)
|
||||||
where
|
where
|
||||||
present f = do
|
present f = do
|
||||||
result <- tryIO $ getFileStatus f
|
result <- tryIO $ getFileStatus f
|
||||||
|
|
Loading…
Add table
Reference in a new issue