enable LambdaCase and convert around 10% of places that could use it
Needs ghc 7.6.1, so minimum base version increased slightly. All builds are well above this version of ghc, and debian oldstable is as well. Code that could use lambdacase can be found by running: git grep -B 1 'case ' | less and searching in less for "<-" This commit was sponsored by andrea rota.
This commit is contained in:
parent
5e6c3ba30c
commit
187b3e7780
13 changed files with 119 additions and 166 deletions
|
@ -80,9 +80,8 @@ adjustTreeItem UnlockAdjustment = ifSymlink adjustToPointer noAdjust
|
||||||
adjustTreeItem LockAdjustment = ifSymlink noAdjust adjustToSymlink
|
adjustTreeItem LockAdjustment = ifSymlink noAdjust adjustToSymlink
|
||||||
adjustTreeItem FixAdjustment = ifSymlink adjustToSymlink noAdjust
|
adjustTreeItem FixAdjustment = ifSymlink adjustToSymlink noAdjust
|
||||||
adjustTreeItem UnFixAdjustment = ifSymlink (adjustToSymlink' gitAnnexLinkCanonical) noAdjust
|
adjustTreeItem UnFixAdjustment = ifSymlink (adjustToSymlink' gitAnnexLinkCanonical) noAdjust
|
||||||
adjustTreeItem HideMissingAdjustment = \ti@(TreeItem _ _ s) -> do
|
adjustTreeItem HideMissingAdjustment = \ti@(TreeItem _ _ s) ->
|
||||||
mk <- catKey s
|
catKey s >>= \case
|
||||||
case mk of
|
|
||||||
Just k -> ifM (inAnnex k)
|
Just k -> ifM (inAnnex k)
|
||||||
( return (Just ti)
|
( return (Just ti)
|
||||||
, return Nothing
|
, return Nothing
|
||||||
|
@ -99,9 +98,7 @@ noAdjust :: TreeItem -> Annex (Maybe TreeItem)
|
||||||
noAdjust = return . Just
|
noAdjust = return . Just
|
||||||
|
|
||||||
adjustToPointer :: TreeItem -> Annex (Maybe TreeItem)
|
adjustToPointer :: TreeItem -> Annex (Maybe TreeItem)
|
||||||
adjustToPointer ti@(TreeItem f _m s) = do
|
adjustToPointer ti@(TreeItem f _m s) = catKey s >>= \case
|
||||||
mk <- catKey s
|
|
||||||
case mk of
|
|
||||||
Just k -> do
|
Just k -> do
|
||||||
Database.Keys.addAssociatedFile k f
|
Database.Keys.addAssociatedFile k f
|
||||||
Just . TreeItem f (fromBlobType FileBlob)
|
Just . TreeItem f (fromBlobType FileBlob)
|
||||||
|
@ -112,9 +109,7 @@ adjustToSymlink :: TreeItem -> Annex (Maybe TreeItem)
|
||||||
adjustToSymlink = adjustToSymlink' gitAnnexLink
|
adjustToSymlink = adjustToSymlink' gitAnnexLink
|
||||||
|
|
||||||
adjustToSymlink' :: (FilePath -> Key -> Git.Repo -> GitConfig -> IO FilePath) -> TreeItem -> Annex (Maybe TreeItem)
|
adjustToSymlink' :: (FilePath -> Key -> Git.Repo -> GitConfig -> IO FilePath) -> TreeItem -> Annex (Maybe TreeItem)
|
||||||
adjustToSymlink' gitannexlink ti@(TreeItem f _m s) = do
|
adjustToSymlink' gitannexlink ti@(TreeItem f _m s) = catKey s >>= \case
|
||||||
mk <- catKey s
|
|
||||||
case mk of
|
|
||||||
Just k -> do
|
Just k -> do
|
||||||
absf <- inRepo $ \r -> absPath $
|
absf <- inRepo $ \r -> absPath $
|
||||||
fromTopFilePath f r
|
fromTopFilePath f r
|
||||||
|
@ -438,9 +433,7 @@ updateAdjustedBranch tomerge (origbranch, adj) mergeconfig canresolvemerge commi
|
||||||
return True
|
return True
|
||||||
reparent _ _ Nothing = return False
|
reparent _ _ Nothing = return False
|
||||||
|
|
||||||
getcurrentcommit = do
|
getcurrentcommit = inRepo Git.Branch.currentUnsafe >>= \case
|
||||||
v <- inRepo Git.Branch.currentUnsafe
|
|
||||||
case v of
|
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just c -> catCommit c
|
Just c -> catCommit c
|
||||||
|
|
||||||
|
@ -463,15 +456,11 @@ propigateAdjustedCommits'
|
||||||
-> Adjustment
|
-> Adjustment
|
||||||
-> CommitsPrevented
|
-> CommitsPrevented
|
||||||
-> Annex (Maybe Sha, Annex ())
|
-> Annex (Maybe Sha, Annex ())
|
||||||
propigateAdjustedCommits' origbranch adj _commitsprevented = do
|
propigateAdjustedCommits' origbranch adj _commitsprevented =
|
||||||
ov <- inRepo $ Git.Ref.sha basis
|
inRepo (Git.Ref.sha basis) >>= \case
|
||||||
case ov of
|
Just origsha -> catCommit currbranch >>= \case
|
||||||
Just origsha -> do
|
Just currcommit ->
|
||||||
cv <- catCommit currbranch
|
newcommits >>= go origsha False >>= \case
|
||||||
case cv of
|
|
||||||
Just currcommit -> do
|
|
||||||
v <- newcommits >>= go origsha False
|
|
||||||
case v of
|
|
||||||
Left e -> do
|
Left e -> do
|
||||||
warning e
|
warning e
|
||||||
return (Nothing, return ())
|
return (Nothing, return ())
|
||||||
|
@ -492,15 +481,13 @@ propigateAdjustedCommits' origbranch adj _commitsprevented = do
|
||||||
setBasisBranch (BasisBranch basis) parent
|
setBasisBranch (BasisBranch basis) parent
|
||||||
inRepo $ Git.Branch.update' origbranch parent
|
inRepo $ Git.Branch.update' origbranch parent
|
||||||
return (Right parent)
|
return (Right parent)
|
||||||
go parent pastadjcommit (sha:l) = do
|
go parent pastadjcommit (sha:l) = catCommit sha >>= \case
|
||||||
mc <- catCommit sha
|
|
||||||
case mc of
|
|
||||||
Just c
|
Just c
|
||||||
| commitMessage c == adjustedBranchCommitMessage ->
|
| commitMessage c == adjustedBranchCommitMessage ->
|
||||||
go parent True l
|
go parent True l
|
||||||
| pastadjcommit -> do
|
| pastadjcommit ->
|
||||||
v <- reverseAdjustedCommit parent adj (sha, c) origbranch
|
reverseAdjustedCommit parent adj (sha, c) origbranch
|
||||||
case v of
|
>>= \case
|
||||||
Left e -> return (Left e)
|
Left e -> return (Left e)
|
||||||
Right commit -> go commit pastadjcommit l
|
Right commit -> go commit pastadjcommit l
|
||||||
_ -> go parent pastadjcommit l
|
_ -> go parent pastadjcommit l
|
||||||
|
|
|
@ -217,9 +217,8 @@ resolveMerge' unstagedmap (Just us) them inoverlay u = do
|
||||||
|
|
||||||
makepointer key dest destmode = do
|
makepointer key dest destmode = do
|
||||||
unless inoverlay $
|
unless inoverlay $
|
||||||
unlessM (reuseOldFile unstagedmap key file dest) $ do
|
unlessM (reuseOldFile unstagedmap key file dest) $
|
||||||
r <- linkFromAnnex key dest destmode
|
linkFromAnnex key dest destmode >>= \case
|
||||||
case r of
|
|
||||||
LinkAnnexFailed -> liftIO $
|
LinkAnnexFailed -> liftIO $
|
||||||
writePointerFile dest key destmode
|
writePointerFile dest key destmode
|
||||||
_ -> noop
|
_ -> noop
|
||||||
|
|
|
@ -446,9 +446,7 @@ stageJournal jl = withIndex $ do
|
||||||
[genstream dir h jh jlogh]
|
[genstream dir h jh jlogh]
|
||||||
return $ cleanup dir jlogh jlogf
|
return $ cleanup dir jlogh jlogf
|
||||||
where
|
where
|
||||||
genstream dir h jh jlogh streamer = do
|
genstream dir h jh jlogh streamer = readDirectory jh >>= \case
|
||||||
v <- readDirectory jh
|
|
||||||
case v of
|
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
Just file -> do
|
Just file -> do
|
||||||
unless (dirCruft file) $ do
|
unless (dirCruft file) $ do
|
||||||
|
|
|
@ -39,18 +39,15 @@ data ChangedRefsHandle = ChangedRefsHandle DirWatcherHandle (TBMChan Git.Sha)
|
||||||
-- When possible, coalesce ref writes that occur closely together
|
-- When possible, coalesce ref writes that occur closely together
|
||||||
-- in time. Delay up to 0.05 seconds to get more ref writes.
|
-- in time. Delay up to 0.05 seconds to get more ref writes.
|
||||||
waitChangedRefs :: ChangedRefsHandle -> IO ChangedRefs
|
waitChangedRefs :: ChangedRefsHandle -> IO ChangedRefs
|
||||||
waitChangedRefs (ChangedRefsHandle _ chan) = do
|
waitChangedRefs (ChangedRefsHandle _ chan) =
|
||||||
v <- atomically $ readTBMChan chan
|
atomically (readTBMChan chan) >>= \case
|
||||||
case v of
|
|
||||||
Nothing -> return $ ChangedRefs []
|
Nothing -> return $ ChangedRefs []
|
||||||
Just r -> do
|
Just r -> do
|
||||||
threadDelay 50000
|
threadDelay 50000
|
||||||
rs <- atomically $ loop []
|
rs <- atomically $ loop []
|
||||||
return $ ChangedRefs (r:rs)
|
return $ ChangedRefs (r:rs)
|
||||||
where
|
where
|
||||||
loop rs = do
|
loop rs = tryReadTBMChan chan >>= \case
|
||||||
v <- tryReadTBMChan chan
|
|
||||||
case v of
|
|
||||||
Just (Just r) -> loop (r:rs)
|
Just (Just r) -> loop (r:rs)
|
||||||
_ -> return rs
|
_ -> return rs
|
||||||
|
|
||||||
|
@ -59,9 +56,7 @@ waitChangedRefs (ChangedRefsHandle _ chan) = do
|
||||||
drainChangedRefs :: ChangedRefsHandle -> IO ()
|
drainChangedRefs :: ChangedRefsHandle -> IO ()
|
||||||
drainChangedRefs (ChangedRefsHandle _ chan) = atomically go
|
drainChangedRefs (ChangedRefsHandle _ chan) = atomically go
|
||||||
where
|
where
|
||||||
go = do
|
go = tryReadTBMChan chan >>= \case
|
||||||
v <- tryReadTBMChan chan
|
|
||||||
case v of
|
|
||||||
Just (Just _) -> go
|
Just (Just _) -> go
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
|
|
||||||
|
|
|
@ -149,17 +149,13 @@ inAnnexSafe key = inAnnex' (fromMaybe True) (Just False) go key
|
||||||
( checkOr is_unlocked lockfile
|
( checkOr is_unlocked lockfile
|
||||||
, return is_missing
|
, return is_missing
|
||||||
)
|
)
|
||||||
checkOr d lockfile = do
|
checkOr d lockfile = checkLocked lockfile >>= return . \case
|
||||||
v <- checkLocked lockfile
|
|
||||||
return $ case v of
|
|
||||||
Nothing -> d
|
Nothing -> d
|
||||||
Just True -> is_locked
|
Just True -> is_locked
|
||||||
Just False -> is_unlocked
|
Just False -> is_unlocked
|
||||||
#else
|
#else
|
||||||
checkindirect f = liftIO $ ifM (doesFileExist f)
|
checkindirect f = liftIO $ ifM (doesFileExist f)
|
||||||
( do
|
( lockShared f >>= \case
|
||||||
v <- lockShared f
|
|
||||||
case v of
|
|
||||||
Nothing -> return is_locked
|
Nothing -> return is_locked
|
||||||
Just lockhandle -> do
|
Just lockhandle -> do
|
||||||
dropLock lockhandle
|
dropLock lockhandle
|
||||||
|
@ -170,9 +166,8 @@ inAnnexSafe key = inAnnex' (fromMaybe True) (Just False) go key
|
||||||
- remove the lock file to clean up after ourselves. -}
|
- remove the lock file to clean up after ourselves. -}
|
||||||
checkdirect contentfile lockfile =
|
checkdirect contentfile lockfile =
|
||||||
ifM (liftIO $ doesFileExist contentfile)
|
ifM (liftIO $ doesFileExist contentfile)
|
||||||
( modifyContent lockfile $ liftIO $ do
|
( modifyContent lockfile $ liftIO $
|
||||||
v <- lockShared lockfile
|
lockShared >>= \case
|
||||||
case v of
|
|
||||||
Nothing -> return is_locked
|
Nothing -> return is_locked
|
||||||
Just lockhandle -> do
|
Just lockhandle -> do
|
||||||
dropLock lockhandle
|
dropLock lockhandle
|
||||||
|
@ -428,8 +423,7 @@ checkDiskSpace' need destdir key alreadythere samefilesystem = ifM (Annex.getSta
|
||||||
inprogress <- if samefilesystem
|
inprogress <- if samefilesystem
|
||||||
then sizeOfDownloadsInProgress (/= key)
|
then sizeOfDownloadsInProgress (/= key)
|
||||||
else pure 0
|
else pure 0
|
||||||
free <- liftIO . getDiskFree =<< dir
|
dir >>= liftIO . getDiskFree >>= \case
|
||||||
case free of
|
|
||||||
Just have -> do
|
Just have -> do
|
||||||
reserve <- annexDiskReserve <$> Annex.getGitConfig
|
reserve <- annexDiskReserve <$> Annex.getGitConfig
|
||||||
let delta = need + reserve - have - alreadythere + inprogress
|
let delta = need + reserve - have - alreadythere + inprogress
|
||||||
|
@ -581,9 +575,8 @@ data FromTo = From | To
|
||||||
-}
|
-}
|
||||||
linkAnnex :: FromTo -> Key -> FilePath -> Maybe InodeCache -> FilePath -> Maybe FileMode -> Annex LinkAnnexResult
|
linkAnnex :: FromTo -> Key -> FilePath -> Maybe InodeCache -> FilePath -> Maybe FileMode -> Annex LinkAnnexResult
|
||||||
linkAnnex _ _ _ Nothing _ _ = return LinkAnnexFailed
|
linkAnnex _ _ _ Nothing _ _ = return LinkAnnexFailed
|
||||||
linkAnnex fromto key src (Just srcic) dest destmode = do
|
linkAnnex fromto key src (Just srcic) dest destmode =
|
||||||
mdestic <- withTSDelta (liftIO . genInodeCache dest)
|
withTSDelta (liftIO . genInodeCache dest) >>= \case
|
||||||
case mdestic of
|
|
||||||
Just destic -> do
|
Just destic -> do
|
||||||
cs <- Database.Keys.getInodeCaches key
|
cs <- Database.Keys.getInodeCaches key
|
||||||
if null cs
|
if null cs
|
||||||
|
@ -602,9 +595,7 @@ linkAnnex fromto key src (Just srcic) dest destmode = do
|
||||||
failed = do
|
failed = do
|
||||||
Database.Keys.addInodeCaches key [srcic]
|
Database.Keys.addInodeCaches key [srcic]
|
||||||
return LinkAnnexFailed
|
return LinkAnnexFailed
|
||||||
checksrcunchanged = do
|
checksrcunchanged = withTSDelta (liftIO . genInodeCache src) >>= \case
|
||||||
mcache <- withTSDelta (liftIO . genInodeCache src)
|
|
||||||
case mcache of
|
|
||||||
Just srcic' | compareStrong srcic srcic' -> do
|
Just srcic' | compareStrong srcic srcic' -> do
|
||||||
destic <- withTSDelta (liftIO . genInodeCache dest)
|
destic <- withTSDelta (liftIO . genInodeCache dest)
|
||||||
Database.Keys.addInodeCaches key $
|
Database.Keys.addInodeCaches key $
|
||||||
|
|
|
@ -111,9 +111,8 @@ preCommitDirect = do
|
||||||
withkey (DiffTree.srcsha diff) (DiffTree.srcmode diff) removeAssociatedFile
|
withkey (DiffTree.srcsha diff) (DiffTree.srcmode diff) removeAssociatedFile
|
||||||
withkey (DiffTree.dstsha diff) (DiffTree.dstmode diff) addAssociatedFile
|
withkey (DiffTree.dstsha diff) (DiffTree.dstmode diff) addAssociatedFile
|
||||||
where
|
where
|
||||||
withkey sha _mode a = when (sha /= nullSha) $ do
|
withkey sha _mode a = when (sha /= nullSha) $
|
||||||
k <- catKey sha
|
catKey sha >>= \case
|
||||||
case k of
|
|
||||||
Nothing -> noop
|
Nothing -> noop
|
||||||
Just key -> void $ a key $
|
Just key -> void $ a key $
|
||||||
makeabs $ DiffTree.file diff
|
makeabs $ DiffTree.file diff
|
||||||
|
@ -427,9 +426,7 @@ setDirect wantdirect = do
|
||||||
then moveconfig coreworktree indirectworktree
|
then moveconfig coreworktree indirectworktree
|
||||||
else moveconfig indirectworktree coreworktree
|
else moveconfig indirectworktree coreworktree
|
||||||
setConfig (ConfigKey Git.Config.coreBare) val
|
setConfig (ConfigKey Git.Config.coreBare) val
|
||||||
moveconfig src dest = do
|
moveconfig src dest = getConfigMaybe src >>= \case
|
||||||
v <- getConfigMaybe src
|
|
||||||
case v of
|
|
||||||
Nothing -> noop
|
Nothing -> noop
|
||||||
Just wt -> do
|
Just wt -> do
|
||||||
unsetConfig src
|
unsetConfig src
|
||||||
|
@ -474,8 +471,7 @@ switchHEADBack = maybe noop switch =<< inRepo Git.Branch.currentUnsafe
|
||||||
where
|
where
|
||||||
switch currhead = do
|
switch currhead = do
|
||||||
let orighead = fromDirectBranch currhead
|
let orighead = fromDirectBranch currhead
|
||||||
v <- inRepo $ Git.Ref.sha currhead
|
inRepo (Git.Ref.sha currhead) >>= \case
|
||||||
case v of
|
|
||||||
Just headsha
|
Just headsha
|
||||||
| orighead /= currhead -> do
|
| orighead /= currhead -> do
|
||||||
inRepo $ Git.Branch.update "leaving direct mode" orighead headsha
|
inRepo $ Git.Branch.update "leaving direct mode" orighead headsha
|
||||||
|
|
|
@ -133,9 +133,7 @@ mkLargeFilesParser = do
|
||||||
#ifdef WITH_MAGICMIME
|
#ifdef WITH_MAGICMIME
|
||||||
magicmime <- liftIO $ catchMaybeIO $ do
|
magicmime <- liftIO $ catchMaybeIO $ do
|
||||||
m <- magicOpen [MagicMimeType]
|
m <- magicOpen [MagicMimeType]
|
||||||
liftIO $ do
|
liftIO $ getEnv "GIT_ANNEX_DIR" >>= \case
|
||||||
md <- getEnv "GIT_ANNEX_DIR"
|
|
||||||
case md of
|
|
||||||
Nothing -> magicLoadDefault m
|
Nothing -> magicLoadDefault m
|
||||||
Just d -> magicLoad m
|
Just d -> magicLoad m
|
||||||
(d </> "magic" </> "magic.mgc")
|
(d </> "magic" </> "magic.mgc")
|
||||||
|
|
|
@ -169,9 +169,8 @@ ingest' preferredbackend (Just (LockedDown cfg source)) mk = withTSDelta $ \delt
|
||||||
)
|
)
|
||||||
go _ _ _ = failure "failed to generate a key"
|
go _ _ _ = failure "failed to generate a key"
|
||||||
|
|
||||||
golocked key mcache s = do
|
golocked key mcache s =
|
||||||
v <- tryNonAsync (moveAnnex key $ contentLocation source)
|
tryNonAsync (moveAnnex key $ contentLocation source) >>= \case
|
||||||
case v of
|
|
||||||
Right True -> do
|
Right True -> do
|
||||||
populateAssociatedFiles key source
|
populateAssociatedFiles key source
|
||||||
success key mcache s
|
success key mcache s
|
||||||
|
@ -184,8 +183,7 @@ ingest' preferredbackend (Just (LockedDown cfg source)) mk = withTSDelta $ \delt
|
||||||
-- already has a hard link.
|
-- already has a hard link.
|
||||||
cleanCruft source
|
cleanCruft source
|
||||||
cleanOldKeys (keyFilename source) key
|
cleanOldKeys (keyFilename source) key
|
||||||
r <- linkToAnnex key (keyFilename source) (Just cache)
|
linkToAnnex key (keyFilename source) (Just cache) >>= \case
|
||||||
case r of
|
|
||||||
LinkAnnexFailed -> failure "failed to link to annex"
|
LinkAnnexFailed -> failure "failed to link to annex"
|
||||||
_ -> do
|
_ -> do
|
||||||
finishIngestUnlocked' key source
|
finishIngestUnlocked' key source
|
||||||
|
@ -259,8 +257,7 @@ cleanOldKeys file newkey = do
|
||||||
fs <- filter (/= ingestedf)
|
fs <- filter (/= ingestedf)
|
||||||
. map (`fromTopFilePath` g)
|
. map (`fromTopFilePath` g)
|
||||||
<$> Database.Keys.getAssociatedFiles key
|
<$> Database.Keys.getAssociatedFiles key
|
||||||
fs' <- filterM (`sameInodeCache` caches) fs
|
filterM (`sameInodeCache` caches) fs >>= \case
|
||||||
case fs' of
|
|
||||||
-- If linkToAnnex fails, the associated
|
-- If linkToAnnex fails, the associated
|
||||||
-- file with the content is still present,
|
-- file with the content is still present,
|
||||||
-- so no need for any recovery.
|
-- so no need for any recovery.
|
||||||
|
@ -342,9 +339,7 @@ cachedCurrentBranch = maybe cache (return . Just)
|
||||||
=<< Annex.getState Annex.cachedcurrentbranch
|
=<< Annex.getState Annex.cachedcurrentbranch
|
||||||
where
|
where
|
||||||
cache :: Annex (Maybe Git.Branch)
|
cache :: Annex (Maybe Git.Branch)
|
||||||
cache = do
|
cache = inRepo Git.Branch.currentUnsafe >>= \case
|
||||||
mb <- inRepo Git.Branch.currentUnsafe
|
|
||||||
case mb of
|
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just b -> do
|
Just b -> do
|
||||||
Annex.changeState $ \s ->
|
Annex.changeState $ \s ->
|
||||||
|
@ -389,9 +384,7 @@ addAnnexedFile file key mtmp = ifM (addUnlocked <&&> not <$> isDirect)
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
linkunlocked mode = do
|
linkunlocked mode = linkFromAnnex key file mode >>= \case
|
||||||
r <- linkFromAnnex key file mode
|
|
||||||
case r of
|
|
||||||
LinkAnnexFailed -> liftIO $
|
LinkAnnexFailed -> liftIO $
|
||||||
writePointerFile file key mode
|
writePointerFile file key mode
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
|
|
|
@ -93,8 +93,7 @@ initialize' mversion = do
|
||||||
whenM versionSupportsUnlockedPointers $ do
|
whenM versionSupportsUnlockedPointers $ do
|
||||||
configureSmudgeFilter
|
configureSmudgeFilter
|
||||||
scanUnlockedFiles
|
scanUnlockedFiles
|
||||||
v <- checkAdjustedClone
|
checkAdjustedClone >>= \case
|
||||||
case v of
|
|
||||||
NeedUpgradeForAdjustedClone ->
|
NeedUpgradeForAdjustedClone ->
|
||||||
void $ upgrade True versionForAdjustedClone
|
void $ upgrade True versionForAdjustedClone
|
||||||
InAdjustedClone -> return ()
|
InAdjustedClone -> return ()
|
||||||
|
|
|
@ -49,9 +49,7 @@ tryLockExclusive m f = tryPidLock m f $ Posix.tryLockExclusive m f
|
||||||
checkLocked :: LockFile -> Annex (Maybe Bool)
|
checkLocked :: LockFile -> Annex (Maybe Bool)
|
||||||
checkLocked f = Posix.checkLocked f `pidLockCheck` checkpid
|
checkLocked f = Posix.checkLocked f `pidLockCheck` checkpid
|
||||||
where
|
where
|
||||||
checkpid pidlock = do
|
checkpid pidlock = Pid.checkLocked pidlock >>= \case
|
||||||
v <- Pid.checkLocked pidlock
|
|
||||||
case v of
|
|
||||||
-- Only return true when the posix lock file exists.
|
-- Only return true when the posix lock file exists.
|
||||||
Just _ -> Posix.checkLocked f
|
Just _ -> Posix.checkLocked f
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
|
|
|
@ -39,8 +39,7 @@ import Data.Time.Clock.POSIX
|
||||||
-}
|
-}
|
||||||
genMetaData :: Key -> FilePath -> FileStatus -> Annex ()
|
genMetaData :: Key -> FilePath -> FileStatus -> Annex ()
|
||||||
genMetaData key file status = do
|
genMetaData key file status = do
|
||||||
v <- catKeyFileHEAD file
|
catKeyFileHEAD file >>= \case
|
||||||
case v of
|
|
||||||
Nothing -> noop
|
Nothing -> noop
|
||||||
Just oldkey ->
|
Just oldkey ->
|
||||||
whenM (copyMetaData oldkey key)
|
whenM (copyMetaData oldkey key)
|
||||||
|
|
|
@ -112,7 +112,7 @@ isContentWritePermOk file = ifM crippledFileSystem
|
||||||
go AllShared = want writeModes
|
go AllShared = want writeModes
|
||||||
go _ = return True
|
go _ = return True
|
||||||
want wantmode = do
|
want wantmode = do
|
||||||
mmode <- liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
|
liftIO $ catchMaybeIO $ fileMode <$> getFileStatus file
|
||||||
return $ case mmode of
|
return $ case mmode of
|
||||||
Nothing -> True
|
Nothing -> True
|
||||||
Just havemode -> havemode == combineModes (havemode:wantmode)
|
Just havemode -> havemode == combineModes (havemode:wantmode)
|
||||||
|
|
|
@ -306,7 +306,7 @@ source-repository head
|
||||||
Executable git-annex
|
Executable git-annex
|
||||||
Main-Is: git-annex.hs
|
Main-Is: git-annex.hs
|
||||||
Build-Depends:
|
Build-Depends:
|
||||||
base (>= 4.5 && < 5.0),
|
base (>= 4.6 && < 5.0),
|
||||||
optparse-applicative (>= 0.11.0),
|
optparse-applicative (>= 0.11.0),
|
||||||
containers (>= 0.5.0.0),
|
containers (>= 0.5.0.0),
|
||||||
exceptions (>= 0.6),
|
exceptions (>= 0.6),
|
||||||
|
@ -360,7 +360,7 @@ Executable git-annex
|
||||||
split
|
split
|
||||||
CC-Options: -Wall
|
CC-Options: -Wall
|
||||||
GHC-Options: -Wall -fno-warn-tabs
|
GHC-Options: -Wall -fno-warn-tabs
|
||||||
Extensions: PackageImports
|
Extensions: PackageImports, LambdaCase
|
||||||
-- Some things don't work with the non-threaded RTS.
|
-- Some things don't work with the non-threaded RTS.
|
||||||
GHC-Options: -threaded
|
GHC-Options: -threaded
|
||||||
Other-Extensions: TemplateHaskell
|
Other-Extensions: TemplateHaskell
|
||||||
|
|
Loading…
Reference in a new issue