fix local dropping to not require extra locking of copies, but only that the local copy be locked for removal
This commit is contained in:
parent
1043880432
commit
6a72045707
12 changed files with 73 additions and 49 deletions
|
@ -13,7 +13,8 @@ module Annex.Content (
|
||||||
inAnnexSafe,
|
inAnnexSafe,
|
||||||
inAnnexCheck,
|
inAnnexCheck,
|
||||||
lockContentShared,
|
lockContentShared,
|
||||||
lockContentExclusive,
|
lockContentForRemoval,
|
||||||
|
ContentRemovalLock,
|
||||||
getViaTmp,
|
getViaTmp,
|
||||||
getViaTmp',
|
getViaTmp',
|
||||||
checkDiskSpaceToGet,
|
checkDiskSpaceToGet,
|
||||||
|
@ -192,14 +193,12 @@ lockContentShared key a = lockContentUsing lock key $ do
|
||||||
lock = winLocker lockShared
|
lock = winLocker lockShared
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
newtype ContentLockExclusive = ContentLockExclusive Key
|
|
||||||
|
|
||||||
{- Exclusively locks content, while performing an action that
|
{- Exclusively locks content, while performing an action that
|
||||||
- might remove it.
|
- might remove it.
|
||||||
-}
|
-}
|
||||||
lockContentExclusive :: Key -> (ContentLockExclusive -> Annex a) -> Annex a
|
lockContentForRemoval :: Key -> (ContentRemovalLock -> Annex a) -> Annex a
|
||||||
lockContentExclusive key a = lockContentUsing lock key $
|
lockContentForRemoval key a = lockContentUsing lock key $
|
||||||
a (ContentLockExclusive key)
|
a (ContentRemovalLock key)
|
||||||
where
|
where
|
||||||
#ifndef mingw32_HOST_OS
|
#ifndef mingw32_HOST_OS
|
||||||
{- Since content files are stored with the write bit disabled, have
|
{- Since content files are stored with the write bit disabled, have
|
||||||
|
@ -547,8 +546,8 @@ cleanObjectLoc key cleaner = do
|
||||||
- In direct mode, deletes the associated files or files, and replaces
|
- In direct mode, deletes the associated files or files, and replaces
|
||||||
- them with symlinks.
|
- them with symlinks.
|
||||||
-}
|
-}
|
||||||
removeAnnex :: ContentLockExclusive -> Annex ()
|
removeAnnex :: ContentRemovalLock -> Annex ()
|
||||||
removeAnnex (ContentLockExclusive key) = withObjectLoc key remove removedirect
|
removeAnnex (ContentRemovalLock key) = withObjectLoc key remove removedirect
|
||||||
where
|
where
|
||||||
remove file = cleanObjectLoc key $ do
|
remove file = cleanObjectLoc key $ do
|
||||||
secureErase file
|
secureErase file
|
||||||
|
|
|
@ -104,12 +104,13 @@ data UnVerifiedCopy = UnVerifiedRemote Remote | UnVerifiedHere
|
||||||
deriving (Ord, Eq)
|
deriving (Ord, Eq)
|
||||||
|
|
||||||
{- Verifies that enough copies of a key exist amoung the listed remotes,
|
{- Verifies that enough copies of a key exist amoung the listed remotes,
|
||||||
- running an action with a proof if so, and printing an informative
|
- to safely drop it, running an action with a proof if so, and
|
||||||
- message if not.
|
- printing an informative message if not.
|
||||||
-}
|
-}
|
||||||
verifyEnoughCopiesToDrop
|
verifyEnoughCopiesToDrop
|
||||||
:: String -- message to print when there are no known locations
|
:: String -- message to print when there are no known locations
|
||||||
-> Key
|
-> Key
|
||||||
|
-> Maybe ContentRemovalLock
|
||||||
-> NumCopies
|
-> NumCopies
|
||||||
-> [UUID] -- repos to skip considering (generally untrusted remotes)
|
-> [UUID] -- repos to skip considering (generally untrusted remotes)
|
||||||
-> [VerifiedCopy] -- copies already verified to exist
|
-> [VerifiedCopy] -- copies already verified to exist
|
||||||
|
@ -117,19 +118,19 @@ verifyEnoughCopiesToDrop
|
||||||
-> (SafeDropProof -> Annex a) -- action to perform to drop
|
-> (SafeDropProof -> Annex a) -- action to perform to drop
|
||||||
-> Annex a -- action to perform when unable to drop
|
-> Annex a -- action to perform when unable to drop
|
||||||
-> Annex a
|
-> Annex a
|
||||||
verifyEnoughCopiesToDrop nolocmsg key need skip preverified tocheck dropaction nodropaction =
|
verifyEnoughCopiesToDrop nolocmsg key removallock need skip preverified tocheck dropaction nodropaction =
|
||||||
helper [] [] preverified (nub tocheck)
|
helper [] [] preverified (nub tocheck)
|
||||||
where
|
where
|
||||||
helper bad missing have [] = do
|
helper bad missing have [] = do
|
||||||
p <- liftIO $ mkSafeDropProof need have
|
p <- liftIO $ mkSafeDropProof need have removallock
|
||||||
case p of
|
case p of
|
||||||
Right proof -> dropaction proof
|
Right proof -> dropaction proof
|
||||||
Left stillhave -> do
|
Left stillhave -> do
|
||||||
notEnoughCopies key need stillhave (skip++missing) bad nolocmsg
|
notEnoughCopies key need stillhave (skip++missing) bad nolocmsg
|
||||||
nodropaction
|
nodropaction
|
||||||
helper bad missing have (c:cs)
|
helper bad missing have (c:cs)
|
||||||
| isSafeDrop need have = do
|
| isSafeDrop need have removallock = do
|
||||||
p <- liftIO $ mkSafeDropProof need have
|
p <- liftIO $ mkSafeDropProof need have removallock
|
||||||
case p of
|
case p of
|
||||||
Right proof -> dropaction proof
|
Right proof -> dropaction proof
|
||||||
Left stillhave -> helper bad missing stillhave (c:cs)
|
Left stillhave -> helper bad missing stillhave (c:cs)
|
||||||
|
|
|
@ -77,7 +77,7 @@ expireUnused duration = do
|
||||||
forM_ oldkeys $ \k -> do
|
forM_ oldkeys $ \k -> do
|
||||||
debug ["removing old unused key", key2file k]
|
debug ["removing old unused key", key2file k]
|
||||||
liftAnnex $ do
|
liftAnnex $ do
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
logStatus k InfoMissing
|
logStatus k InfoMissing
|
||||||
where
|
where
|
||||||
boundry = durationToPOSIXTime <$> duration
|
boundry = durationToPOSIXTime <$> duration
|
||||||
|
|
|
@ -97,7 +97,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
|
||||||
, transferKey = k
|
, transferKey = k
|
||||||
}
|
}
|
||||||
cleanup = liftAnnex $ do
|
cleanup = liftAnnex $ do
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
setUrlMissing webUUID k u
|
setUrlMissing webUUID k u
|
||||||
logStatus k InfoMissing
|
logStatus k InfoMissing
|
||||||
|
|
||||||
|
|
|
@ -91,15 +91,11 @@ startRemote afile numcopies key remote = do
|
||||||
showStart' ("drop " ++ Remote.name remote) key afile
|
showStart' ("drop " ++ Remote.name remote) key afile
|
||||||
next $ performRemote key afile numcopies remote
|
next $ performRemote key afile numcopies remote
|
||||||
|
|
||||||
-- Note that lockContentExclusive is called before checking if the key is
|
|
||||||
-- present on enough remotes to allow removal. This avoids a scenario where two
|
|
||||||
-- or more remotes are trying to remove a key at the same time, and each
|
|
||||||
-- sees the key is present on the other.
|
|
||||||
performLocal :: Key -> AssociatedFile -> NumCopies -> [VerifiedCopy] -> CommandPerform
|
performLocal :: Key -> AssociatedFile -> NumCopies -> [VerifiedCopy] -> CommandPerform
|
||||||
performLocal key afile numcopies preverified = lockContentExclusive key $ \contentlock -> do
|
performLocal key afile numcopies preverified = lockContentForRemoval key $ \contentlock -> do
|
||||||
u <- getUUID
|
u <- getUUID
|
||||||
(tocheck, verified) <- verifiableCopies key [u]
|
(tocheck, verified) <- verifiableCopies key [u]
|
||||||
doDrop u key afile numcopies [] (preverified ++ verified) tocheck
|
doDrop u (Just contentlock) key afile numcopies [] (preverified ++ verified) tocheck
|
||||||
( \proof -> do
|
( \proof -> do
|
||||||
liftIO $ debugM "drop" $ unwords
|
liftIO $ debugM "drop" $ unwords
|
||||||
[ "Dropping from here"
|
[ "Dropping from here"
|
||||||
|
@ -121,7 +117,7 @@ performRemote key afile numcopies remote = do
|
||||||
-- When the local repo has the key, that's one additional copy,
|
-- When the local repo has the key, that's one additional copy,
|
||||||
-- as long as the local repo is not untrusted.
|
-- as long as the local repo is not untrusted.
|
||||||
(tocheck, verified) <- verifiableCopies key [uuid]
|
(tocheck, verified) <- verifiableCopies key [uuid]
|
||||||
doDrop uuid key afile numcopies [uuid] verified tocheck
|
doDrop uuid Nothing key afile numcopies [uuid] verified tocheck
|
||||||
( \proof -> do
|
( \proof -> do
|
||||||
liftIO $ debugM "drop" $ unwords
|
liftIO $ debugM "drop" $ unwords
|
||||||
[ "Dropping from remote"
|
[ "Dropping from remote"
|
||||||
|
@ -159,6 +155,7 @@ cleanupRemote key remote ok = do
|
||||||
-}
|
-}
|
||||||
doDrop
|
doDrop
|
||||||
:: UUID
|
:: UUID
|
||||||
|
-> Maybe ContentRemovalLock
|
||||||
-> Key
|
-> Key
|
||||||
-> AssociatedFile
|
-> AssociatedFile
|
||||||
-> NumCopies
|
-> NumCopies
|
||||||
|
@ -167,11 +164,12 @@ doDrop
|
||||||
-> [UnVerifiedCopy]
|
-> [UnVerifiedCopy]
|
||||||
-> (Maybe SafeDropProof -> CommandPerform, CommandPerform)
|
-> (Maybe SafeDropProof -> CommandPerform, CommandPerform)
|
||||||
-> CommandPerform
|
-> CommandPerform
|
||||||
doDrop dropfrom key afile numcopies skip preverified check (dropaction, nodropaction) =
|
doDrop dropfrom contentlock key afile numcopies skip preverified check (dropaction, nodropaction) =
|
||||||
ifM (Annex.getState Annex.force)
|
ifM (Annex.getState Annex.force)
|
||||||
( dropaction Nothing
|
( dropaction Nothing
|
||||||
, ifM (checkRequiredContent dropfrom key afile)
|
, ifM (checkRequiredContent dropfrom key afile)
|
||||||
( verifyEnoughCopiesToDrop nolocmsg key numcopies
|
( verifyEnoughCopiesToDrop nolocmsg key
|
||||||
|
contentlock numcopies
|
||||||
skip preverified check
|
skip preverified check
|
||||||
(dropaction . Just)
|
(dropaction . Just)
|
||||||
(forcehint nodropaction)
|
(forcehint nodropaction)
|
||||||
|
|
|
@ -31,7 +31,7 @@ start key = stopUnless (inAnnex key) $ do
|
||||||
next $ perform key
|
next $ perform key
|
||||||
|
|
||||||
perform :: Key -> CommandPerform
|
perform :: Key -> CommandPerform
|
||||||
perform key = lockContentExclusive key $ \contentlock -> do
|
perform key = lockContentForRemoval key $ \contentlock -> do
|
||||||
removeAnnex contentlock
|
removeAnnex contentlock
|
||||||
next $ cleanup key
|
next $ cleanup key
|
||||||
|
|
||||||
|
|
|
@ -139,5 +139,5 @@ verifyExisting key destfile (yes, no) = do
|
||||||
need <- getFileNumCopies destfile
|
need <- getFileNumCopies destfile
|
||||||
|
|
||||||
(tocheck, preverified) <- verifiableCopies key []
|
(tocheck, preverified) <- verifiableCopies key []
|
||||||
verifyEnoughCopiesToDrop [] key need [] preverified tocheck
|
verifyEnoughCopiesToDrop [] key Nothing need [] preverified tocheck
|
||||||
(const yes) no
|
(const yes) no
|
||||||
|
|
|
@ -123,7 +123,7 @@ toPerform dest move key afile fastcheck isthere =
|
||||||
finish
|
finish
|
||||||
where
|
where
|
||||||
finish
|
finish
|
||||||
| move = lockContentExclusive key $ \contentlock -> do
|
| move = lockContentForRemoval key $ \contentlock -> do
|
||||||
removeAnnex contentlock
|
removeAnnex contentlock
|
||||||
next $ Command.Drop.cleanupLocal key
|
next $ Command.Drop.cleanupLocal key
|
||||||
| otherwise = next $ return True
|
| otherwise = next $ return True
|
||||||
|
|
|
@ -120,7 +120,7 @@ test st r k =
|
||||||
, check "storeKey when already present" store
|
, check "storeKey when already present" store
|
||||||
, present True
|
, present True
|
||||||
, check "retrieveKeyFile" $ do
|
, check "retrieveKeyFile" $ do
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from 33%" $ do
|
, check "retrieveKeyFile resume from 33%" $ do
|
||||||
|
@ -130,20 +130,20 @@ test st r k =
|
||||||
sz <- hFileSize h
|
sz <- hFileSize h
|
||||||
L.hGet h $ fromInteger $ sz `div` 3
|
L.hGet h $ fromInteger $ sz `div` 3
|
||||||
liftIO $ L.writeFile tmp partial
|
liftIO $ L.writeFile tmp partial
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from 0" $ do
|
, check "retrieveKeyFile resume from 0" $ do
|
||||||
tmp <- prepTmp k
|
tmp <- prepTmp k
|
||||||
liftIO $ writeFile tmp ""
|
liftIO $ writeFile tmp ""
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "retrieveKeyFile resume from end" $ do
|
, check "retrieveKeyFile resume from end" $ do
|
||||||
loc <- Annex.calcRepo (gitAnnexLocation k)
|
loc <- Annex.calcRepo (gitAnnexLocation k)
|
||||||
tmp <- prepTmp k
|
tmp <- prepTmp k
|
||||||
void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp
|
void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
get
|
get
|
||||||
, check "fsck downloaded object" fsck
|
, check "fsck downloaded object" fsck
|
||||||
, check "removeKey when present" remove
|
, check "removeKey when present" remove
|
||||||
|
@ -189,7 +189,7 @@ testUnavailable st r k =
|
||||||
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
||||||
cleanup rs ks ok = do
|
cleanup rs ks ok = do
|
||||||
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
||||||
forM_ ks $ \k -> lockContentExclusive k removeAnnex
|
forM_ ks $ \k -> lockContentForRemoval k removeAnnex
|
||||||
return ok
|
return ok
|
||||||
|
|
||||||
chunkSizes :: Int -> Bool -> [Int]
|
chunkSizes :: Int -> Bool -> [Int]
|
||||||
|
|
|
@ -105,7 +105,7 @@ removeUnannexed = go []
|
||||||
go c [] = return c
|
go c [] = return c
|
||||||
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
|
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
|
||||||
( do
|
( do
|
||||||
lockContentExclusive k removeAnnex
|
lockContentForRemoval k removeAnnex
|
||||||
go c ks
|
go c ks
|
||||||
, go (k:c) ks
|
, go (k:c) ks
|
||||||
)
|
)
|
||||||
|
|
|
@ -352,7 +352,7 @@ dropKey r key
|
||||||
commitOnCleanup r $ onLocal r $ do
|
commitOnCleanup r $ onLocal r $ do
|
||||||
ensureInitialized
|
ensureInitialized
|
||||||
whenM (Annex.Content.inAnnex key) $ do
|
whenM (Annex.Content.inAnnex key) $ do
|
||||||
Annex.Content.lockContentExclusive key
|
Annex.Content.lockContentForRemoval key
|
||||||
Annex.Content.removeAnnex
|
Annex.Content.removeAnnex
|
||||||
logStatus key InfoMissing
|
logStatus key InfoMissing
|
||||||
Annex.Content.saveState True
|
Annex.Content.saveState True
|
||||||
|
|
|
@ -19,9 +19,11 @@ module Types.NumCopies (
|
||||||
isSafeDrop,
|
isSafeDrop,
|
||||||
SafeDropProof,
|
SafeDropProof,
|
||||||
mkSafeDropProof,
|
mkSafeDropProof,
|
||||||
|
ContentRemovalLock(..),
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types.UUID
|
import Types.UUID
|
||||||
|
import Types.Key
|
||||||
import Utility.Exception (bracketIO)
|
import Utility.Exception (bracketIO)
|
||||||
|
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -36,6 +38,11 @@ newtype NumCopies = NumCopies Int
|
||||||
fromNumCopies :: NumCopies -> Int
|
fromNumCopies :: NumCopies -> Int
|
||||||
fromNumCopies (NumCopies n) = n
|
fromNumCopies (NumCopies n) = n
|
||||||
|
|
||||||
|
-- Indicates that a key's content is exclusively
|
||||||
|
-- locked locally, pending removal.
|
||||||
|
newtype ContentRemovalLock = ContentRemovalLock Key
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
-- A verification that a copy of a key exists in a repository.
|
-- A verification that a copy of a key exists in a repository.
|
||||||
data VerifiedCopy
|
data VerifiedCopy
|
||||||
{- Represents a recent verification that a copy of an
|
{- Represents a recent verification that a copy of an
|
||||||
|
@ -48,7 +55,7 @@ data VerifiedCopy
|
||||||
{- The strongest proof of the existence of a copy.
|
{- The strongest proof of the existence of a copy.
|
||||||
- Until its associated action is called to unlock it,
|
- Until its associated action is called to unlock it,
|
||||||
- the copy is locked in the repository and is guaranteed
|
- the copy is locked in the repository and is guaranteed
|
||||||
- not to be dropped by any git-annex process. -}
|
- not to be removed by any git-annex process. -}
|
||||||
| LockedCopy V
|
| LockedCopy V
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
@ -116,20 +123,39 @@ withVerifiedCopy mk u = bracketIO setup cleanup
|
||||||
{- Check whether enough verification has been done of copies to allow
|
{- Check whether enough verification has been done of copies to allow
|
||||||
- dropping content safely.
|
- dropping content safely.
|
||||||
-
|
-
|
||||||
- Unless numcopies is 0, at least one LockedCopy or TrustedCopy
|
- This is carefully balanced to prevent data loss when there are races
|
||||||
- is required. A LockedCopy prevents races between concurrent
|
- between concurrent drops of the same content in different repos,
|
||||||
- drops from dropping the last copy, no matter what.
|
- without requiring impractical amounts of locking.
|
||||||
|
-
|
||||||
|
- In particular, concurrent drop races may cause the number of copies
|
||||||
|
- to fall below NumCopies, but it will never fall below 1.
|
||||||
|
-}
|
||||||
|
isSafeDrop :: NumCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> Bool
|
||||||
|
{- When a ContentRemovalLock is provided, the content is being
|
||||||
|
- dropped from the local repo. That lock will prevent other git repos
|
||||||
|
- that are concurrently dropping from using the local copy as a VerifiedCopy.
|
||||||
|
- So, no additional locking is needed; all we need is verifications
|
||||||
|
- of any kind of N other copies of the content. -}
|
||||||
|
isSafeDrop (NumCopies n) l (Just (ContentRemovalLock _)) =
|
||||||
|
length (deDupVerifiedCopies l) >= n
|
||||||
|
{- Dropping from a remote repo.
|
||||||
|
-
|
||||||
|
- Unless numcopies is 0, at least one LockedCopy or TrustedCopy is required.
|
||||||
|
- A LockedCopy prevents races between concurrent drops from
|
||||||
|
- dropping the last copy, no matter what.
|
||||||
-
|
-
|
||||||
- The other N-1 copies can be less strong verifications, like
|
- The other N-1 copies can be less strong verifications, like
|
||||||
- RecentlyVerifiedCopy. While those are subject to concurrent drop races,
|
- RecentlyVerifiedCopy. While those are subject to concurrent drop races,
|
||||||
- and so could be dropped all at once, causing numcopies to be violated,
|
- and so could be dropped all at once, causing numcopies to be violated,
|
||||||
- this is the best that can be done without requiring all special remotes
|
- this is the best that can be done without requiring that
|
||||||
- to support locking.
|
- all special remotes support locking.
|
||||||
-}
|
-}
|
||||||
isSafeDrop :: NumCopies -> [VerifiedCopy] -> Bool
|
isSafeDrop (NumCopies n) l Nothing
|
||||||
isSafeDrop (NumCopies n) l
|
|
||||||
| n == 0 = True
|
| n == 0 = True
|
||||||
| otherwise = length (deDupVerifiedCopies l) >= n && any fullVerification l
|
| otherwise = and
|
||||||
|
[ length (deDupVerifiedCopies l) >= n
|
||||||
|
, any fullVerification l
|
||||||
|
]
|
||||||
|
|
||||||
fullVerification :: VerifiedCopy -> Bool
|
fullVerification :: VerifiedCopy -> Bool
|
||||||
fullVerification (LockedCopy _) = True
|
fullVerification (LockedCopy _) = True
|
||||||
|
@ -137,14 +163,14 @@ fullVerification (TrustedCopy _) = True
|
||||||
fullVerification (RecentlyVerifiedCopy _) = False
|
fullVerification (RecentlyVerifiedCopy _) = False
|
||||||
|
|
||||||
-- A proof that it's currently safe to drop an object.
|
-- A proof that it's currently safe to drop an object.
|
||||||
data SafeDropProof = SafeDropProof NumCopies [VerifiedCopy]
|
data SafeDropProof = SafeDropProof NumCopies [VerifiedCopy] (Maybe ContentRemovalLock)
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
-- Make sure that none of the VerifiedCopies have become invalidated
|
-- Make sure that none of the VerifiedCopies have become invalidated
|
||||||
-- before constructing proof.
|
-- before constructing proof.
|
||||||
mkSafeDropProof :: NumCopies -> [VerifiedCopy] -> IO (Either [VerifiedCopy] SafeDropProof)
|
mkSafeDropProof :: NumCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> IO (Either [VerifiedCopy] SafeDropProof)
|
||||||
mkSafeDropProof need have = do
|
mkSafeDropProof need have removallock = do
|
||||||
stillhave <- filterM checkVerifiedCopy have
|
stillhave <- filterM checkVerifiedCopy have
|
||||||
return $ if isSafeDrop need stillhave
|
return $ if isSafeDrop need stillhave removallock
|
||||||
then Right (SafeDropProof need stillhave)
|
then Right (SafeDropProof need stillhave removallock)
|
||||||
else Left stillhave
|
else Left stillhave
|
||||||
|
|
Loading…
Reference in a new issue