AssociatedFile newtype

To prevent any further mistakes like 301aff34c4

This commit was sponsored by Francois Marier on Patreon.
This commit is contained in:
Joey Hess 2017-03-10 13:12:24 -04:00
parent 2cd7496210
commit c8e1e3dada
No known key found for this signature in database
GPG key ID: C910D9222512E3C7
43 changed files with 179 additions and 138 deletions

View file

@ -55,8 +55,8 @@ handleDropsFrom locs rs reason fromhere key afile preverified runner = do
map (`fromTopFilePath` g) <$> Database.Keys.getAssociatedFiles key map (`fromTopFilePath` g) <$> Database.Keys.getAssociatedFiles key
) )
let fs = case afile of let fs = case afile of
Just f -> nub (f : l) AssociatedFile (Just f) -> nub (f : l)
Nothing -> l AssociatedFile Nothing -> l
n <- getcopies fs n <- getcopies fs
void $ if fromhere && checkcopies n Nothing void $ if fromhere && checkcopies n Nothing
then go fs rs n >>= dropl fs then go fs rs n >>= dropl fs
@ -93,9 +93,9 @@ handleDropsFrom locs rs reason fromhere key afile preverified runner = do
checkdrop fs n u a checkdrop fs n u a
| null fs = check $ -- no associated files; unused content | null fs = check $ -- no associated files; unused content
wantDrop True u (Just key) Nothing wantDrop True u (Just key) (AssociatedFile Nothing)
| otherwise = check $ | otherwise = check $
allM (wantDrop True u (Just key) . Just) fs allM (wantDrop True u (Just key) . AssociatedFile . Just) fs
where where
check c = ifM c check c = ifM c
( dodrop n u a ( dodrop n u a
@ -107,7 +107,9 @@ handleDropsFrom locs rs reason fromhere key afile preverified runner = do
( do ( do
liftIO $ debugM "drop" $ unwords liftIO $ debugM "drop" $ unwords
[ "dropped" [ "dropped"
, fromMaybe (key2file key) afile , case afile of
AssociatedFile Nothing -> key2file key
AssociatedFile (Just af) -> af
, "(from " ++ maybe "here" show u ++ ")" , "(from " ++ maybe "here" show u ++ ")"
, "(copies now " ++ show (fromNumCopies have - 1) ++ ")" , "(copies now " ++ show (fromNumCopies have - 1) ++ ")"
, ": " ++ reason , ": " ++ reason

View file

@ -44,13 +44,13 @@ type GetFileMatcher = FilePath -> Annex (FileMatcher Annex)
checkFileMatcher :: GetFileMatcher -> FilePath -> Annex Bool checkFileMatcher :: GetFileMatcher -> FilePath -> Annex Bool
checkFileMatcher getmatcher file = do checkFileMatcher getmatcher file = do
matcher <- getmatcher file matcher <- getmatcher file
checkMatcher matcher Nothing (Just file) S.empty True checkMatcher matcher Nothing (AssociatedFile (Just file)) S.empty True
checkMatcher :: FileMatcher Annex -> Maybe Key -> AssociatedFile -> AssumeNotPresent -> Bool -> Annex Bool checkMatcher :: FileMatcher Annex -> Maybe Key -> AssociatedFile -> AssumeNotPresent -> Bool -> Annex Bool
checkMatcher matcher mkey afile notpresent d checkMatcher matcher mkey afile notpresent d
| isEmpty matcher = return d | isEmpty matcher = return d
| otherwise = case (mkey, afile) of | otherwise = case (mkey, afile) of
(_, Just file) -> go =<< fileMatchInfo file (_, AssociatedFile (Just file)) -> go =<< fileMatchInfo file
(Just key, _) -> go (MatchingKey key) (Just key, _) -> go (MatchingKey key)
_ -> return d _ -> return d
where where

View file

@ -28,10 +28,10 @@ noNotification = NotifyWitness
{- Wrap around an action that performs a transfer, which may run multiple {- Wrap around an action that performs a transfer, which may run multiple
- attempts. Displays notification when supported and when the user asked - attempts. Displays notification when supported and when the user asked
- for it. -} - for it. -}
notifyTransfer :: Direction -> Maybe FilePath -> (NotifyWitness -> Annex Bool) -> Annex Bool notifyTransfer :: Direction -> AssociatedFile -> (NotifyWitness -> Annex Bool) -> Annex Bool
notifyTransfer _ Nothing a = a NotifyWitness notifyTransfer _ (AssociatedFile Nothing) a = a NotifyWitness
#ifdef WITH_DBUS_NOTIFICATIONS #ifdef WITH_DBUS_NOTIFICATIONS
notifyTransfer direction (Just f) a = do notifyTransfer direction (AssociatedFile (Just f)) a = do
wanted <- Annex.getState Annex.desktopnotify wanted <- Annex.getState Annex.desktopnotify
if (notifyStart wanted || notifyFinish wanted) if (notifyStart wanted || notifyFinish wanted)
then do then do
@ -47,19 +47,19 @@ notifyTransfer direction (Just f) a = do
return ok return ok
else a NotifyWitness else a NotifyWitness
#else #else
notifyTransfer _ (Just _) a = a NotifyWitness notifyTransfer _ (AssociatedFile (Just _)) a = a NotifyWitness
#endif #endif
notifyDrop :: Maybe FilePath -> Bool -> Annex () notifyDrop :: AssociatedFile -> Bool -> Annex ()
notifyDrop Nothing _ = noop notifyDrop (AssociatedFile Nothing) _ = noop
#ifdef WITH_DBUS_NOTIFICATIONS #ifdef WITH_DBUS_NOTIFICATIONS
notifyDrop (Just f) ok = do notifyDrop (AssociatedFile (Just f)) ok = do
wanted <- Annex.getState Annex.desktopnotify wanted <- Annex.getState Annex.desktopnotify
when (notifyFinish wanted) $ liftIO $ do when (notifyFinish wanted) $ liftIO $ do
client <- DBus.Client.connectSession client <- DBus.Client.connectSession
void $ Notify.notify client (droppedNote ok f) void $ Notify.notify client (droppedNote ok f)
#else #else
notifyDrop (Just _) _ = noop notifyDrop (AssociatedFile (Just _)) _ = noop
#endif #endif
#ifdef WITH_DBUS_NOTIFICATIONS #ifdef WITH_DBUS_NOTIFICATIONS

View file

@ -77,7 +77,7 @@ guardHaveUUID u a
- An upload can be run from a read-only filesystem, and in this case - An upload can be run from a read-only filesystem, and in this case
- no transfer information or lock file is used. - no transfer information or lock file is used.
-} -}
runTransfer :: Observable v => Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v runTransfer :: Observable v => Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
runTransfer = runTransfer' False runTransfer = runTransfer' False
{- Like runTransfer, but ignores any existing transfer lock file for the {- Like runTransfer, but ignores any existing transfer lock file for the
@ -85,12 +85,12 @@ runTransfer = runTransfer' False
- -
- Note that this may result in confusing progress meter display in the - Note that this may result in confusing progress meter display in the
- webapp, if multiple processes are writing to the transfer info file. -} - webapp, if multiple processes are writing to the transfer info file. -}
alwaysRunTransfer :: Observable v => Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v alwaysRunTransfer :: Observable v => Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
alwaysRunTransfer = runTransfer' True alwaysRunTransfer = runTransfer' True
runTransfer' :: Observable v => Bool -> Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v runTransfer' :: Observable v => Bool -> Transfer -> AssociatedFile -> RetryDecider -> (MeterUpdate -> Annex v) -> Annex v
runTransfer' ignorelock t file shouldretry transferaction = checkSecureHashes t $ do runTransfer' ignorelock t afile shouldretry transferaction = checkSecureHashes t $ do
info <- liftIO $ startTransferInfo file info <- liftIO $ startTransferInfo afile
(meter, tfile, metervar) <- mkProgressUpdater t info (meter, tfile, metervar) <- mkProgressUpdater t info
mode <- annexFileMode mode <- annexFileMode
(lck, inprogress) <- prep tfile mode info (lck, inprogress) <- prep tfile mode info

View file

@ -64,7 +64,7 @@ removableRemote urlrenderer uuid = do
where where
queueremaining r k = queueremaining r k =
queueTransferWhenSmall "remaining object in unwanted remote" queueTransferWhenSmall "remaining object in unwanted remote"
Nothing (Transfer Download uuid k) r (AssociatedFile Nothing) (Transfer Download uuid k) r
{- Scanning for keys can take a long time; do not tie up {- Scanning for keys can take a long time; do not tie up
- the Annex monad while doing it, so other threads continue to - the Annex monad while doing it, so other threads continue to
- run. -} - run. -}

View file

@ -503,9 +503,10 @@ checkChangeContent change@(Change { changeInfo = i }) =
Just k -> whenM (scanComplete <$> getDaemonStatus) $ do Just k -> whenM (scanComplete <$> getDaemonStatus) $ do
present <- liftAnnex $ inAnnex k present <- liftAnnex $ inAnnex k
void $ if present void $ if present
then queueTransfers "new file created" Next k (Just f) Upload then queueTransfers "new file created" Next k af Upload
else queueTransfers "new or renamed file wanted" Next k (Just f) Download else queueTransfers "new or renamed file wanted" Next k af Download
handleDrops "file renamed" present k (Just f) [] handleDrops "file renamed" present k af []
where where
f = changeFile change f = changeFile change
af = AssociatedFile (Just f)
checkChangeContent _ = noop checkChangeContent _ = noop

View file

@ -190,7 +190,7 @@ runActivity' urlrenderer (ScheduledSelfFsck _ d) = do
void $ repairWhenNecessary urlrenderer u Nothing fsckresults void $ repairWhenNecessary urlrenderer u Nothing fsckresults
mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir) mapM_ reget =<< liftAnnex (dirKeys gitAnnexBadDir)
where where
reget k = queueTransfers "fsck found bad file; redownloading" Next k Nothing Download reget k = queueTransfers "fsck found bad file; redownloading" Next k (AssociatedFile Nothing) Download
runActivity' urlrenderer (ScheduledRemoteFsck u s d) = dispatch =<< liftAnnex (remoteFromUUID u) runActivity' urlrenderer (ScheduledRemoteFsck u s d) = dispatch =<< liftAnnex (remoteFromUUID u)
where where
dispatch Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s] dispatch Nothing = debug ["skipping remote fsck of uuid without a configured remote", fromUUID u, fromSchedule s]

View file

@ -190,8 +190,8 @@ dailyCheck urlrenderer = do
unused <- liftAnnex unusedKeys' unused <- liftAnnex unusedKeys'
void $ liftAnnex $ setUnusedKeys unused void $ liftAnnex $ setUnusedKeys unused
forM_ unused $ \k -> do forM_ unused $ \k -> do
unlessM (queueTransfers "unused" Later k Nothing Upload) $ unlessM (queueTransfers "unused" Later k (AssociatedFile Nothing) Upload) $
handleDrops "unused" True k Nothing [] handleDrops "unused" True k (AssociatedFile Nothing) []
return True return True
where where

View file

@ -154,8 +154,9 @@ expensiveScan urlrenderer rs = batch <~> do
enqueue f (r, t) = enqueue f (r, t) =
queueTransferWhenSmall "expensive scan found missing object" queueTransferWhenSmall "expensive scan found missing object"
(Just f) t r (AssociatedFile (Just f)) t r
findtransfers f unwanted key = do findtransfers f unwanted key = do
let af = AssociatedFile (Just f)
{- The syncable remotes may have changed since this {- The syncable remotes may have changed since this
- scan began. -} - scan began. -}
syncrs <- syncDataRemotes <$> getDaemonStatus syncrs <- syncDataRemotes <$> getDaemonStatus
@ -163,14 +164,14 @@ expensiveScan urlrenderer rs = batch <~> do
present <- liftAnnex $ inAnnex key present <- liftAnnex $ inAnnex key
liftAnnex $ handleDropsFrom locs syncrs liftAnnex $ handleDropsFrom locs syncrs
"expensive scan found too many copies of object" "expensive scan found too many copies of object"
present key (Just f) [] callCommandAction present key af [] callCommandAction
liftAnnex $ do liftAnnex $ do
let slocs = S.fromList locs let slocs = S.fromList locs
let use a = return $ mapMaybe (a key slocs) syncrs let use a = return $ mapMaybe (a key slocs) syncrs
ts <- if present ts <- if present
then filterM (wantSend True (Just key) (Just f) . Remote.uuid . fst) then filterM (wantSend True (Just key) af . Remote.uuid . fst)
=<< use (genTransfer Upload False) =<< use (genTransfer Upload False)
else ifM (wantGet True (Just key) (Just f)) else ifM (wantGet True (Just key) af)
( use (genTransfer Download True) , return [] ) ( use (genTransfer Download True) , return [] )
let unwanted' = S.difference unwanted slocs let unwanted' = S.difference unwanted slocs
return (unwanted', ts) return (unwanted', ts)

View file

@ -153,10 +153,11 @@ genTransfer t info = case transferRemote info of
-} -}
go remote transferrer = ifM (liftIO $ performTransfer transferrer t info) go remote transferrer = ifM (liftIO $ performTransfer transferrer t info)
( do ( do
maybe noop case associatedFile info of
(void . addAlert . makeAlertFiller True AssociatedFile Nothing -> noop
. transferFileAlert direction True) AssociatedFile (Just af) -> void $
(associatedFile info) addAlert $ makeAlertFiller True $
transferFileAlert direction True af
unless isdownload $ unless isdownload $
handleDrops handleDrops
("object uploaded to " ++ show remote) ("object uploaded to " ++ show remote)

View file

@ -85,7 +85,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
hook <- asIO1 $ distributionDownloadComplete d dest cleanup hook <- asIO1 $ distributionDownloadComplete d dest cleanup
modifyDaemonStatus_ $ \s -> s modifyDaemonStatus_ $ \s -> s
{ transferHook = M.insert k hook (transferHook s) } { transferHook = M.insert k hook (transferHook s) }
maybe noop (queueTransfer "upgrade" Next (Just f) t) maybe noop (queueTransfer "upgrade" Next (AssociatedFile (Just f)) t)
=<< liftAnnex (remoteFromUUID webUUID) =<< liftAnnex (remoteFromUUID webUUID)
startTransfer t startTransfer t
k = distributionKey d k = distributionKey d

View file

@ -43,6 +43,9 @@ transfersDisplay = do
ident = "transfers" ident = "transfers"
isrunning info = not $ isrunning info = not $
transferPaused info || isNothing (startedTime info) transferPaused info || isNothing (startedTime info)
desc transfer info = case associatedFile info of
AssociatedFile Nothing -> key2file $ transferKey transfer
AssociatedFile (Just af) -> af
{- Simplifies a list of transfers, avoiding display of redundant {- Simplifies a list of transfers, avoiding display of redundant
- equivilant transfers. -} - equivilant transfers. -}

View file

@ -148,8 +148,8 @@ trivialMigrate oldkey newbackend afile
} }
{- Fast migration from hash to hashE backend. -} {- Fast migration from hash to hashE backend. -}
| migratable && hasExt oldvariety = case afile of | migratable && hasExt oldvariety = case afile of
Nothing -> Nothing AssociatedFile Nothing -> Nothing
Just file -> Just $ oldkey AssociatedFile (Just file) -> Just $ oldkey
{ keyName = keyHash oldkey ++ selectExtension file { keyName = keyHash oldkey ++ selectExtension file
, keyVariety = newvariety , keyVariety = newvariety
} }

View file

@ -171,7 +171,9 @@ downloadRemoteFile r relaxed uri file sz = checkCanAdd file $ do
-- so that the remote knows what url it -- so that the remote knows what url it
-- should use to download it. -- should use to download it.
setTempUrl urlkey loguri setTempUrl urlkey loguri
let downloader = \dest p -> fst <$> Remote.retrieveKeyFile r urlkey (Just file) dest p let downloader = \dest p -> fst
<$> Remote.retrieveKeyFile r urlkey
(AssociatedFile (Just file)) dest p
ret <- downloadWith downloader urlkey (Remote.uuid r) loguri file ret <- downloadWith downloader urlkey (Remote.uuid r) loguri file
removeTempUrl urlkey removeTempUrl urlkey
return ret return ret
@ -255,8 +257,8 @@ addUrlFileQuvi relaxed quviurl videourl file = checkCanAdd file $ do
checkDiskSpaceToGet sizedkey Nothing $ do checkDiskSpaceToGet sizedkey Nothing $ do
tmp <- fromRepo $ gitAnnexTmpObjectLocation key tmp <- fromRepo $ gitAnnexTmpObjectLocation key
showOutput showOutput
ok <- Transfer.notifyTransfer Transfer.Download (Just file) $ ok <- Transfer.notifyTransfer Transfer.Download afile $
Transfer.download webUUID key (Just file) Transfer.forwardRetry $ \p -> do Transfer.download webUUID key afile Transfer.forwardRetry $ \p -> do
liftIO $ createDirectoryIfMissing True (parentDir tmp) liftIO $ createDirectoryIfMissing True (parentDir tmp)
downloadUrl key p [videourl] tmp downloadUrl key p [videourl] tmp
if ok if ok
@ -265,6 +267,8 @@ addUrlFileQuvi relaxed quviurl videourl file = checkCanAdd file $ do
return (Just key) return (Just key)
else return Nothing else return Nothing
) )
where
afile = AssociatedFile (Just file)
addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform addUrlChecked :: Bool -> URLString -> UUID -> (Key -> Annex (Bool, Bool)) -> Key -> CommandPerform
addUrlChecked relaxed url u checkexistssize key addUrlChecked relaxed url u checkexistssize key
@ -328,10 +332,11 @@ downloadWith downloader dummykey u url file =
, return Nothing , return Nothing
) )
where where
runtransfer tmp = Transfer.notifyTransfer Transfer.Download (Just file) $ runtransfer tmp = Transfer.notifyTransfer Transfer.Download afile $
Transfer.download u dummykey (Just file) Transfer.forwardRetry $ \p -> do Transfer.download u dummykey afile Transfer.forwardRetry $ \p -> do
liftIO $ createDirectoryIfMissing True (parentDir tmp) liftIO $ createDirectoryIfMissing True (parentDir tmp)
downloader tmp p downloader tmp p
afile = AssociatedFile (Just file)
{- Adds the url size to the Key. -} {- Adds the url size to the Key. -}
addSizeUrlKey :: Url.UrlInfo -> Key -> Key addSizeUrlKey :: Url.UrlInfo -> Key -> Key

View file

@ -53,6 +53,6 @@ start o file key = stopUnless shouldCopy $
| otherwise = return True | otherwise = return True
want = case Command.Move.fromToOptions (moveOptions o) of want = case Command.Move.fromToOptions (moveOptions o) of
ToRemote dest -> (Remote.uuid <$> getParsed dest) >>= ToRemote dest -> (Remote.uuid <$> getParsed dest) >>=
wantSend False (Just key) (Just file) wantSend False (Just key) (AssociatedFile (Just file))
FromRemote _ -> FromRemote _ ->
wantGet False (Just key) (Just file) wantGet False (Just key) (AssociatedFile (Just file))

View file

@ -65,7 +65,7 @@ seek o = allowConcurrentOutput $
start :: DropOptions -> FilePath -> Key -> CommandStart start :: DropOptions -> FilePath -> Key -> CommandStart
start o file key = start' o key afile (mkActionItem afile) start o file key = start' o key afile (mkActionItem afile)
where where
afile = Just file afile = AssociatedFile (Just file)
start' :: DropOptions -> Key -> AssociatedFile -> ActionItem -> CommandStart start' :: DropOptions -> Key -> AssociatedFile -> ActionItem -> CommandStart
start' o key afile ai = do start' o key afile ai = do
@ -85,7 +85,7 @@ start' o key afile ai = do
| otherwise = return True | otherwise = return True
startKeys :: DropOptions -> Key -> ActionItem -> CommandStart startKeys :: DropOptions -> Key -> ActionItem -> CommandStart
startKeys o key = start' o key Nothing startKeys o key = start' o key (AssociatedFile Nothing)
startLocal :: AssociatedFile -> ActionItem -> NumCopies -> Key -> [VerifiedCopy] -> CommandStart startLocal :: AssociatedFile -> ActionItem -> NumCopies -> Key -> [VerifiedCopy] -> CommandStart
startLocal afile ai numcopies key preverified = stopUnless (inAnnex key) $ do startLocal afile ai numcopies key preverified = stopUnless (inAnnex key) $ do
@ -202,7 +202,8 @@ requiredContent = do
{- In auto mode, only runs the action if there are enough {- In auto mode, only runs the action if there are enough
- copies on other semitrusted repositories. -} - copies on other semitrusted repositories. -}
checkDropAuto :: Bool -> Maybe Remote -> AssociatedFile -> Key -> (NumCopies -> CommandStart) -> CommandStart checkDropAuto :: Bool -> Maybe Remote -> AssociatedFile -> Key -> (NumCopies -> CommandStart) -> CommandStart
checkDropAuto automode mremote afile key a = go =<< maybe getNumCopies getFileNumCopies afile checkDropAuto automode mremote (AssociatedFile afile) key a =
go =<< maybe getNumCopies getFileNumCopies afile
where where
go numcopies go numcopies
| automode = do | automode = do

View file

@ -46,9 +46,9 @@ perform :: Maybe Remote -> NumCopies -> Key -> CommandPerform
perform from numcopies key = case from of perform from numcopies key = case from of
Just r -> do Just r -> do
showAction $ "from " ++ Remote.name r showAction $ "from " ++ Remote.name r
Command.Drop.performRemote key Nothing numcopies r Command.Drop.performRemote key (AssociatedFile Nothing) numcopies r
Nothing -> ifM (inAnnex key) Nothing -> ifM (inAnnex key)
( Command.Drop.performLocal key Nothing numcopies [] ( Command.Drop.performLocal key (AssociatedFile Nothing) numcopies []
, next (return True) , next (return True)
) )

View file

@ -110,9 +110,10 @@ start from inc file key = do
numcopies <- getFileNumCopies file numcopies <- getFileNumCopies file
case from of case from of
Nothing -> go $ perform key file backend numcopies Nothing -> go $ perform key file backend numcopies
Just r -> go $ performRemote key (Just file) backend numcopies r Just r -> go $ performRemote key afile backend numcopies r
where where
go = runFsck inc (mkActionItem (Just file)) key go = runFsck inc (mkActionItem afile) key
afile = AssociatedFile (Just file)
perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool
perform key file backend numcopies = do perform key file backend numcopies = do
@ -123,10 +124,12 @@ perform key file backend numcopies = do
, verifyLocationLog key keystatus file , verifyLocationLog key keystatus file
, verifyAssociatedFiles key keystatus file , verifyAssociatedFiles key keystatus file
, verifyWorkTree key file , verifyWorkTree key file
, checkKeySize key keystatus (Just file) , checkKeySize key keystatus afile
, checkBackend backend key keystatus (Just file) , checkBackend backend key keystatus afile
, checkKeyNumCopies key (Just file) numcopies , checkKeyNumCopies key afile numcopies
] ]
where
afile = AssociatedFile (Just file)
{- To fsck a remote, the content is retrieved to a tmp file, {- To fsck a remote, the content is retrieved to a tmp file,
- and checked locally. -} - and checked locally. -}
@ -148,7 +151,7 @@ performRemote key afile backend numcopies remote =
return False return False
dispatch (Right False) = go False Nothing dispatch (Right False) = go False Nothing
go present localcopy = check go present localcopy = check
[ verifyLocationLogRemote key (maybe (key2file key) id afile) remote present [ verifyLocationLogRemote key afile remote present
, withLocalCopy localcopy $ checkKeySizeRemote key remote afile , withLocalCopy localcopy $ checkKeySizeRemote key remote afile
, withLocalCopy localcopy $ checkBackendRemote backend key remote afile , withLocalCopy localcopy $ checkBackendRemote backend key remote afile
, checkKeyNumCopies key afile numcopies , checkKeyNumCopies key afile numcopies
@ -167,7 +170,7 @@ performRemote key afile backend numcopies remote =
, ifM (Annex.getState Annex.fast) , ifM (Annex.getState Annex.fast)
( return Nothing ( return Nothing
, Just . fst <$> , Just . fst <$>
Remote.retrieveKeyFile remote key Nothing tmp dummymeter Remote.retrieveKeyFile remote key (AssociatedFile Nothing) tmp dummymeter
) )
) )
, return (Just False) , return (Just False)
@ -181,16 +184,16 @@ startKey from inc key ai numcopies =
Just backend -> runFsck inc ai key $ Just backend -> runFsck inc ai key $
case from of case from of
Nothing -> performKey key backend numcopies Nothing -> performKey key backend numcopies
Just r -> performRemote key Nothing backend numcopies r Just r -> performRemote key (AssociatedFile Nothing) backend numcopies r
performKey :: Key -> Backend -> NumCopies -> Annex Bool performKey :: Key -> Backend -> NumCopies -> Annex Bool
performKey key backend numcopies = do performKey key backend numcopies = do
keystatus <- getKeyStatus key keystatus <- getKeyStatus key
check check
[ verifyLocationLog key keystatus (key2file key) [ verifyLocationLog key keystatus (key2file key)
, checkKeySize key keystatus Nothing , checkKeySize key keystatus (AssociatedFile Nothing)
, checkBackend backend key keystatus Nothing , checkBackend backend key keystatus (AssociatedFile Nothing)
, checkKeyNumCopies key Nothing numcopies , checkKeyNumCopies key (AssociatedFile Nothing) numcopies
] ]
check :: [Annex Bool] -> Annex Bool check :: [Annex Bool] -> Annex Bool
@ -249,10 +252,12 @@ verifyLocationLog key keystatus desc = do
then return True then return True
else verifyLocationLog' key desc present u (logChange key u) else verifyLocationLog' key desc present u (logChange key u)
verifyLocationLogRemote :: Key -> String -> Remote -> Bool -> Annex Bool verifyLocationLogRemote :: Key -> AssociatedFile -> Remote -> Bool -> Annex Bool
verifyLocationLogRemote key desc remote present = verifyLocationLogRemote key (AssociatedFile afile) remote present =
verifyLocationLog' key desc present (Remote.uuid remote) verifyLocationLog' key desc present (Remote.uuid remote)
(Remote.logStatus remote key) (Remote.logStatus remote key)
where
desc = fromMaybe (key2file key) afile
verifyLocationLog' :: Key -> String -> Bool -> UUID -> (LogStatus -> Annex ()) -> Annex Bool verifyLocationLog' :: Key -> String -> Bool -> UUID -> (LogStatus -> Annex ()) -> Annex Bool
verifyLocationLog' key desc present u updatestatus = do verifyLocationLog' key desc present u updatestatus = do
@ -356,7 +361,7 @@ checkKeySizeRemote key remote afile localcopy =
checkKeySizeOr (badContentRemote remote localcopy) key localcopy afile checkKeySizeOr (badContentRemote remote localcopy) key localcopy afile
checkKeySizeOr :: (Key -> Annex String) -> Key -> FilePath -> AssociatedFile -> Annex Bool checkKeySizeOr :: (Key -> Annex String) -> Key -> FilePath -> AssociatedFile -> Annex Bool
checkKeySizeOr bad key file afile = case keySize key of checkKeySizeOr bad key file (AssociatedFile afile) = case keySize key of
Nothing -> return True Nothing -> return True
Just size -> do Just size -> do
size' <- liftIO $ getFileSize file size' <- liftIO $ getFileSize file
@ -396,7 +401,9 @@ checkBackend backend key keystatus afile = go =<< isDirect
( nocheck ( nocheck
, checkBackendOr badContent backend key content afile , checkBackendOr badContent backend key content afile
) )
go True = maybe nocheck checkdirect afile go True = case afile of
AssociatedFile Nothing -> nocheck
AssociatedFile (Just f) -> checkdirect f
checkdirect file = ifM (Direct.goodContent key file) checkdirect file = ifM (Direct.goodContent key file)
( checkBackendOr' (badContentDirect file) backend key file afile ( checkBackendOr' (badContentDirect file) backend key file afile
(Direct.goodContent key file) (Direct.goodContent key file)
@ -416,7 +423,7 @@ checkBackendOr bad backend key file afile =
-- in order to detect situations where the file is changed while being -- in order to detect situations where the file is changed while being
-- verified (particularly in direct mode). -- verified (particularly in direct mode).
checkBackendOr' :: (Key -> Annex String) -> Backend -> Key -> FilePath -> AssociatedFile -> Annex Bool -> Annex Bool checkBackendOr' :: (Key -> Annex String) -> Backend -> Key -> FilePath -> AssociatedFile -> Annex Bool -> Annex Bool
checkBackendOr' bad backend key file afile postcheck = checkBackendOr' bad backend key file (AssociatedFile afile) postcheck =
case Types.Backend.verifyKeyContent backend of case Types.Backend.verifyKeyContent backend of
Nothing -> return True Nothing -> return True
Just verifier -> do Just verifier -> do
@ -436,21 +443,23 @@ checkBackendOr' bad backend key file afile postcheck =
checkKeyNumCopies :: Key -> AssociatedFile -> NumCopies -> Annex Bool checkKeyNumCopies :: Key -> AssociatedFile -> NumCopies -> Annex Bool
checkKeyNumCopies key afile numcopies = do checkKeyNumCopies key afile numcopies = do
let file = fromMaybe (key2file key) afile let (desc, hasafile) = case afile of
AssociatedFile Nothing -> (key2file key, False)
AssociatedFile (Just af) -> (af, True)
locs <- loggedLocations key locs <- loggedLocations key
(untrustedlocations, otherlocations) <- trustPartition UnTrusted locs (untrustedlocations, otherlocations) <- trustPartition UnTrusted locs
(deadlocations, safelocations) <- trustPartition DeadTrusted otherlocations (deadlocations, safelocations) <- trustPartition DeadTrusted otherlocations
let present = NumCopies (length safelocations) let present = NumCopies (length safelocations)
if present < numcopies if present < numcopies
then ifM (pure (isNothing afile) <&&> checkDead key) then ifM (pure (not hasafile) <&&> checkDead key)
( do ( do
showLongNote $ "This key is dead, skipping." showLongNote $ "This key is dead, skipping."
return True return True
, do , do
untrusted <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations untrusted <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
dead <- Remote.prettyPrintUUIDs "dead" deadlocations dead <- Remote.prettyPrintUUIDs "dead" deadlocations
warning $ missingNote file present numcopies untrusted dead warning $ missingNote desc present numcopies untrusted dead
when (fromNumCopies present == 0 && isNothing afile) $ when (fromNumCopies present == 0 && not hasafile) $
showLongNote "(Avoid this check by running: git annex dead --key )" showLongNote "(Avoid this check by running: git annex dead --key )"
return False return False
) )

View file

@ -51,14 +51,15 @@ seek o = allowConcurrentOutput $ do
start :: GetOptions -> Maybe Remote -> FilePath -> Key -> CommandStart start :: GetOptions -> Maybe Remote -> FilePath -> Key -> CommandStart
start o from file key = start' expensivecheck from key afile (mkActionItem afile) start o from file key = start' expensivecheck from key afile (mkActionItem afile)
where where
afile = Just file afile = AssociatedFile (Just file)
expensivecheck expensivecheck
| autoMode o = numCopiesCheck file key (<) <||> wantGet False (Just key) (Just file) | autoMode o = numCopiesCheck file key (<)
<||> wantGet False (Just key) afile
| otherwise = return True | otherwise = return True
startKeys :: Maybe Remote -> Key -> ActionItem -> CommandStart startKeys :: Maybe Remote -> Key -> ActionItem -> CommandStart
startKeys from key ai = checkFailedTransferDirection ai Download $ startKeys from key ai = checkFailedTransferDirection ai Download $
start' (return True) from key Nothing ai start' (return True) from key (AssociatedFile Nothing) ai
start' :: Annex Bool -> Maybe Remote -> Key -> AssociatedFile -> ActionItem -> CommandStart start' :: Annex Bool -> Maybe Remote -> Key -> AssociatedFile -> ActionItem -> CommandStart
start' expensivecheck from key afile ai = stopUnless (not <$> inAnnex key) $ start' expensivecheck from key afile ai = stopUnless (not <$> inAnnex key) $

View file

@ -39,6 +39,7 @@ import Logs.Transfer
import Types.Key import Types.Key
import Types.TrustLevel import Types.TrustLevel
import Types.FileMatcher import Types.FileMatcher
import Types.ActionItem
import qualified Limit import qualified Limit
import Messages.JSON (DualDisp(..), ObjectMap(..)) import Messages.JSON (DualDisp(..), ObjectMap(..))
import Annex.BloomFilter import Annex.BloomFilter
@ -420,7 +421,9 @@ transfer_list = stat desc $ nojson $ lift $ do
desc = "transfers in progress" desc = "transfers in progress"
line uuidmap t i = unwords line uuidmap t i = unwords
[ formatDirection (transferDirection t) ++ "ing" [ formatDirection (transferDirection t) ++ "ing"
, fromMaybe (key2file $ transferKey t) (associatedFile i) , actionItemDesc
(ActionItemAssociatedFile (associatedFile i))
(transferKey t)
, if transferDirection t == Upload then "to" else "from" , if transferDirection t == Upload then "to" else "from"
, maybe (fromUUID $ transferUUID t) Remote.name $ , maybe (fromUUID $ transferUUID t) Remote.name $
M.lookup (transferUUID t) uuidmap M.lookup (transferUUID t) uuidmap
@ -428,9 +431,11 @@ transfer_list = stat desc $ nojson $ lift $ do
jsonify t i = object $ map (\(k, v) -> (T.pack k, v)) $ jsonify t i = object $ map (\(k, v) -> (T.pack k, v)) $
[ ("transfer", toJSON (formatDirection (transferDirection t))) [ ("transfer", toJSON (formatDirection (transferDirection t)))
, ("key", toJSON (key2file (transferKey t))) , ("key", toJSON (key2file (transferKey t)))
, ("file", toJSON (associatedFile i)) , ("file", toJSON afile)
, ("remote", toJSON (fromUUID (transferUUID t))) , ("remote", toJSON (fromUUID (transferUUID t)))
] ]
where
AssociatedFile afile = associatedFile i
disk_size :: Stat disk_size :: Stat
disk_size = simpleStat "available local disk space" $ disk_size = simpleStat "available local disk space" $

View file

@ -86,7 +86,7 @@ seek o = case batchOption o of
start :: POSIXTime -> MetaDataOptions -> FilePath -> Key -> CommandStart start :: POSIXTime -> MetaDataOptions -> FilePath -> Key -> CommandStart
start now o file k = startKeys now o k (mkActionItem afile) start now o file k = startKeys now o k (mkActionItem afile)
where where
afile = Just file afile = AssociatedFile (Just file)
startKeys :: POSIXTime -> MetaDataOptions -> Key -> ActionItem -> CommandStart startKeys :: POSIXTime -> MetaDataOptions -> Key -> ActionItem -> CommandStart
startKeys now o k ai = case getSet o of startKeys now o k ai = case getSet o of
@ -155,7 +155,7 @@ startBatch (i, (MetaData m)) = case i of
Left f -> do Left f -> do
mk <- lookupFile f mk <- lookupFile f
case mk of case mk of
Just k -> go k (mkActionItem (Just f)) Just k -> go k (mkActionItem (AssociatedFile (Just f)))
Nothing -> giveup $ "not an annexed file: " ++ f Nothing -> giveup $ "not an annexed file: " ++ f
Right k -> go k (mkActionItem k) Right k -> go k (mkActionItem k)
where where

View file

@ -73,7 +73,7 @@ perform file oldkey oldbackend newbackend = go =<< genkey
go (Just (newkey, knowngoodcontent)) go (Just (newkey, knowngoodcontent))
| knowngoodcontent = finish newkey | knowngoodcontent = finish newkey
| otherwise = stopUnless checkcontent $ finish newkey | otherwise = stopUnless checkcontent $ finish newkey
checkcontent = Command.Fsck.checkBackend oldbackend oldkey Command.Fsck.KeyLocked $ Just file checkcontent = Command.Fsck.checkBackend oldbackend oldkey Command.Fsck.KeyLocked afile
finish newkey = ifM (Command.ReKey.linkKey file oldkey newkey) finish newkey = ifM (Command.ReKey.linkKey file oldkey newkey)
( do ( do
copyMetaData oldkey newkey copyMetaData oldkey newkey
@ -86,7 +86,7 @@ perform file oldkey oldbackend newbackend = go =<< genkey
next $ Command.ReKey.cleanup file oldkey newkey next $ Command.ReKey.cleanup file oldkey newkey
, error "failed" , error "failed"
) )
genkey = case maybe Nothing (\fm -> fm oldkey newbackend (Just file)) (fastMigrate oldbackend) of genkey = case maybe Nothing (\fm -> fm oldkey newbackend afile) (fastMigrate oldbackend) of
Just newkey -> return $ Just (newkey, True) Just newkey -> return $ Just (newkey, True)
Nothing -> do Nothing -> do
content <- calcRepo $ gitAnnexLocation oldkey content <- calcRepo $ gitAnnexLocation oldkey
@ -99,3 +99,4 @@ perform file oldkey oldbackend newbackend = go =<< genkey
return $ case v of return $ case v of
Just (newkey, _) -> Just (newkey, False) Just (newkey, _) -> Just (newkey, False)
_ -> Nothing _ -> Nothing
afile = AssociatedFile (Just file)

View file

@ -43,16 +43,16 @@ instance DeferredParseClass MirrorOptions where
seek :: MirrorOptions -> CommandSeek seek :: MirrorOptions -> CommandSeek
seek o = allowConcurrentOutput $ seek o = allowConcurrentOutput $
withKeyOptions (keyOptions o) False withKeyOptions (keyOptions o) False
(startKey o Nothing) (startKey o (AssociatedFile Nothing))
(withFilesInGit $ whenAnnexed $ start o) (withFilesInGit $ whenAnnexed $ start o)
(mirrorFiles o) (mirrorFiles o)
start :: MirrorOptions -> FilePath -> Key -> CommandStart start :: MirrorOptions -> FilePath -> Key -> CommandStart
start o file k = startKey o afile k (mkActionItem afile) start o file k = startKey o afile k (mkActionItem afile)
where where
afile = Just file afile = AssociatedFile (Just file)
startKey :: MirrorOptions -> Maybe FilePath -> Key -> ActionItem -> CommandStart startKey :: MirrorOptions -> AssociatedFile -> Key -> ActionItem -> CommandStart
startKey o afile key ai = case fromToOptions o of startKey o afile key ai = case fromToOptions o of
ToRemote r -> checkFailedTransferDirection ai Upload $ ifM (inAnnex key) ToRemote r -> checkFailedTransferDirection ai Upload $ ifM (inAnnex key)
( Command.Move.toStart False afile key ai =<< getParsed r ( Command.Move.toStart False afile key ai =<< getParsed r
@ -72,4 +72,6 @@ startKey o afile key ai = case fromToOptions o of
, stop , stop
) )
where where
getnumcopies = maybe getNumCopies getFileNumCopies afile getnumcopies = case afile of
AssociatedFile Nothing -> getNumCopies
AssociatedFile (Just af) -> getFileNumCopies af

View file

@ -53,10 +53,10 @@ seek o = allowConcurrentOutput $
start :: MoveOptions -> Bool -> FilePath -> Key -> CommandStart start :: MoveOptions -> Bool -> FilePath -> Key -> CommandStart
start o move f k = start' o move afile k (mkActionItem afile) start o move f k = start' o move afile k (mkActionItem afile)
where where
afile = Just f afile = AssociatedFile (Just f)
startKey :: MoveOptions -> Bool -> Key -> ActionItem -> CommandStart startKey :: MoveOptions -> Bool -> Key -> ActionItem -> CommandStart
startKey o move = start' o move Nothing startKey o move = start' o move (AssociatedFile Nothing)
start' :: MoveOptions -> Bool -> AssociatedFile -> Key -> ActionItem -> CommandStart start' :: MoveOptions -> Bool -> AssociatedFile -> Key -> ActionItem -> CommandStart
start' o move afile key ai = start' o move afile key ai =

View file

@ -46,7 +46,7 @@ start key = do
fieldTransfer :: Direction -> Key -> (MeterUpdate -> Annex Bool) -> CommandStart fieldTransfer :: Direction -> Key -> (MeterUpdate -> Annex Bool) -> CommandStart
fieldTransfer direction key a = do fieldTransfer direction key a = do
liftIO $ debugM "fieldTransfer" "transfer start" liftIO $ debugM "fieldTransfer" "transfer start"
afile <- Fields.getField Fields.associatedFile afile <- AssociatedFile <$> Fields.getField Fields.associatedFile
ok <- maybe (a $ const noop) ok <- maybe (a $ const noop)
-- Using noRetry here because we're the sender. -- Using noRetry here because we're the sender.
(\u -> runner (Transfer direction (toUUID u) key) afile noRetry a) (\u -> runner (Transfer direction (toUUID u) key) afile noRetry a)

View file

@ -519,8 +519,8 @@ seekSyncContent o rs = do
liftIO $ not <$> isEmptyMVar mvar liftIO $ not <$> isEmptyMVar mvar
where where
seekworktree mvar l bloomfeeder = seekHelper LsFiles.inRepo l >>= seekworktree mvar l bloomfeeder = seekHelper LsFiles.inRepo l >>=
mapM_ (\f -> ifAnnexed f (go (Right bloomfeeder) mvar (Just f)) noop) mapM_ (\f -> ifAnnexed f (go (Right bloomfeeder) mvar (AssociatedFile (Just f))) noop)
seekkeys mvar bloom k _ = go (Left bloom) mvar Nothing k seekkeys mvar bloom k _ = go (Left bloom) mvar (AssociatedFile Nothing) k
go ebloom mvar af k = commandAction $ do go ebloom mvar af k = commandAction $ do
whenM (syncFile ebloom rs af k) $ whenM (syncFile ebloom rs af k) $
void $ liftIO $ tryPutMVar mvar () void $ liftIO $ tryPutMVar mvar ()

View file

@ -155,8 +155,9 @@ test st r k =
Nothing -> return True Nothing -> return True
Just verifier -> verifier k (key2file k) Just verifier -> verifier k (key2file k)
get = getViaTmp (RemoteVerify r) k $ \dest -> get = getViaTmp (RemoteVerify r) k $ \dest ->
Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate Remote.retrieveKeyFile r k (AssociatedFile Nothing)
store = Remote.storeKey r k Nothing nullMeterUpdate dest nullMeterUpdate
store = Remote.storeKey r k (AssociatedFile Nothing) nullMeterUpdate
remove = Remote.removeKey r k remove = Remote.removeKey r k
testUnavailable :: Annex.AnnexState -> Remote -> Key -> [TestTree] testUnavailable :: Annex.AnnexState -> Remote -> Key -> [TestTree]
@ -164,15 +165,15 @@ testUnavailable st r k =
[ check (== Right False) "removeKey" $ [ check (== Right False) "removeKey" $
Remote.removeKey r k Remote.removeKey r k
, check (== Right False) "storeKey" $ , check (== Right False) "storeKey" $
Remote.storeKey r k Nothing nullMeterUpdate Remote.storeKey r k (AssociatedFile Nothing) nullMeterUpdate
, check (`notElem` [Right True, Right False]) "checkPresent" $ , check (`notElem` [Right True, Right False]) "checkPresent" $
Remote.checkPresent r k Remote.checkPresent r k
, check (== Right False) "retrieveKeyFile" $ , check (== Right False) "retrieveKeyFile" $
getViaTmp (RemoteVerify r) k $ \dest -> getViaTmp (RemoteVerify r) k $ \dest ->
Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate Remote.retrieveKeyFile r k (AssociatedFile Nothing) dest nullMeterUpdate
, check (== Right False) "retrieveKeyFileCheap" $ , check (== Right False) "retrieveKeyFileCheap" $
getViaTmp (RemoteVerify r) k $ \dest -> unVerified $ getViaTmp (RemoteVerify r) k $ \dest -> unVerified $
Remote.retrieveKeyFileCheap r k Nothing dest Remote.retrieveKeyFileCheap r k (AssociatedFile Nothing) dest
] ]
where where
check checkval desc a = testCase desc $ do check checkval desc a = testCase desc $ do

View file

@ -41,7 +41,7 @@ start (k:[]) = do
case file2key k of case file2key k of
Nothing -> error "bad key" Nothing -> error "bad key"
(Just key) -> whenM (inAnnex key) $ do (Just key) -> whenM (inAnnex key) $ do
file <- Fields.getField Fields.associatedFile afile <- AssociatedFile <$> Fields.getField Fields.associatedFile
u <- maybe (error "missing remoteuuid") toUUID u <- maybe (error "missing remoteuuid") toUUID
<$> Fields.getField Fields.remoteUUID <$> Fields.getField Fields.remoteUUID
let t = Transfer let t = Transfer
@ -49,7 +49,7 @@ start (k:[]) = do
, transferUUID = u , transferUUID = u
, transferKey = key , transferKey = key
} }
tinfo <- liftIO $ startTransferInfo file tinfo <- liftIO $ startTransferInfo afile
(update, tfile, _) <- mkProgressUpdater t tinfo (update, tfile, _) <- mkProgressUpdater t tinfo
liftIO $ mapM_ void liftIO $ mapM_ void
[ tryIO $ forever $ do [ tryIO $ forever $ do

View file

@ -30,10 +30,10 @@ optParser :: CmdParamsDesc -> Parser TransferKeyOptions
optParser desc = TransferKeyOptions optParser desc = TransferKeyOptions
<$> cmdParams desc <$> cmdParams desc
<*> parseFromToOptions <*> parseFromToOptions
<*> optional (strOption <*> (AssociatedFile <$> optional (strOption
( long "file" <> metavar paramFile ( long "file" <> metavar paramFile
<> help "the associated file" <> help "the associated file"
)) )))
instance DeferredParseClass TransferKeyOptions where instance DeferredParseClass TransferKeyOptions where
finishParse v = TransferKeyOptions finishParse v = TransferKeyOptions

View file

@ -116,10 +116,10 @@ instance TCSerialized Direction where
deserialize _ = Nothing deserialize _ = Nothing
instance TCSerialized AssociatedFile where instance TCSerialized AssociatedFile where
serialize (Just f) = f serialize (AssociatedFile (Just f)) = f
serialize Nothing = "" serialize (AssociatedFile Nothing) = ""
deserialize "" = Just Nothing deserialize "" = Just (AssociatedFile Nothing)
deserialize f = Just $ Just f deserialize f = Just (AssociatedFile (Just f))
instance TCSerialized RemoteName where instance TCSerialized RemoteName where
serialize n = n serialize n = n

View file

@ -49,7 +49,7 @@ seek o = do
start :: M.Map UUID Remote -> FilePath -> Key -> CommandStart start :: M.Map UUID Remote -> FilePath -> Key -> CommandStart
start remotemap file key = startKeys remotemap key (mkActionItem afile) start remotemap file key = startKeys remotemap key (mkActionItem afile)
where where
afile = Just file afile = AssociatedFile (Just file)
startKeys :: M.Map UUID Remote -> Key -> ActionItem -> CommandStart startKeys :: M.Map UUID Remote -> Key -> ActionItem -> CommandStart
startKeys remotemap key ai = do startKeys remotemap key ai = do

2
Key.hs
View file

@ -9,7 +9,7 @@
module Key ( module Key (
Key(..), Key(..),
AssociatedFile, AssociatedFile(..),
stubKey, stubKey,
key2file, key2file,
file2key, file2key,

View file

@ -13,12 +13,14 @@ import Limit
import Types.FileMatcher import Types.FileMatcher
addWantGet :: Annex () addWantGet :: Annex ()
addWantGet = addLimit $ Right $ const $ checkWant $ wantGet False Nothing addWantGet = addLimit $ Right $ const $ checkWant $
wantGet False Nothing
addWantDrop :: Annex () addWantDrop :: Annex ()
addWantDrop = addLimit $ Right $ const $ checkWant $ wantDrop False Nothing Nothing addWantDrop = addLimit $ Right $ const $ checkWant $
wantDrop False Nothing Nothing
checkWant :: (Maybe FilePath -> Annex Bool) -> MatchInfo -> Annex Bool checkWant :: (AssociatedFile -> Annex Bool) -> MatchInfo -> Annex Bool
checkWant a (MatchingFile fi) = a (Just $ matchFile fi) checkWant a (MatchingFile fi) = a (AssociatedFile (Just $ matchFile fi))
checkWant _ (MatchingKey _) = return False checkWant _ (MatchingKey _) = return False
checkWant _ (MatchingInfo {}) = return False checkWant _ (MatchingInfo {}) = return False

View file

@ -10,6 +10,7 @@
module Logs.Transfer where module Logs.Transfer where
import Types.Transfer import Types.Transfer
import Types.ActionItem
import Annex.Common import Annex.Common
import Annex.Perms import Annex.Perms
import qualified Git import qualified Git
@ -27,7 +28,9 @@ describeTransfer :: Transfer -> TransferInfo -> String
describeTransfer t info = unwords describeTransfer t info = unwords
[ show $ transferDirection t [ show $ transferDirection t
, show $ transferUUID t , show $ transferUUID t
, fromMaybe (key2file $ transferKey t) (associatedFile info) , actionItemDesc
(ActionItemAssociatedFile (associatedFile info))
(transferKey t)
, show $ bytesComplete info , show $ bytesComplete info
] ]
@ -67,8 +70,8 @@ mkProgressUpdater t info = do
Just sz -> sz `div` 100 Just sz -> sz `div` 100
Nothing -> 100 * 1024 -- arbitrarily, 100 kb Nothing -> 100 * 1024 -- arbitrarily, 100 kb
startTransferInfo :: Maybe FilePath -> IO TransferInfo startTransferInfo :: AssociatedFile -> IO TransferInfo
startTransferInfo file = TransferInfo startTransferInfo afile = TransferInfo
<$> (Just . utcTimeToPOSIXSeconds <$> getCurrentTime) <$> (Just . utcTimeToPOSIXSeconds <$> getCurrentTime)
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
<*> pure Nothing -- pid not stored in file, so omitted for speed <*> pure Nothing -- pid not stored in file, so omitted for speed
@ -78,7 +81,7 @@ startTransferInfo file = TransferInfo
<*> pure Nothing -- tid ditto <*> pure Nothing -- tid ditto
<*> pure Nothing -- not 0; transfer may be resuming <*> pure Nothing -- not 0; transfer may be resuming
<*> pure Nothing <*> pure Nothing
<*> pure file <*> pure afile
<*> pure False <*> pure False
{- If a transfer is still running, returns its TransferInfo. {- If a transfer is still running, returns its TransferInfo.
@ -228,7 +231,9 @@ writeTransferInfo info = unlines
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
, maybe "" show (transferPid info) , maybe "" show (transferPid info)
#endif #endif
, fromMaybe "" $ associatedFile info -- comes last; arbitrary content -- comes last; arbitrary content
, let AssociatedFile afile = associatedFile info
in fromMaybe "" afile
] ]
readTransferInfoFile :: Maybe PID -> FilePath -> IO (Maybe TransferInfo) readTransferInfoFile :: Maybe PID -> FilePath -> IO (Maybe TransferInfo)
@ -246,7 +251,7 @@ readTransferInfo mpid s = TransferInfo
<*> pure Nothing <*> pure Nothing
<*> pure Nothing <*> pure Nothing
<*> bytes <*> bytes
<*> pure (if null filename then Nothing else Just filename) <*> pure (AssociatedFile (if null filename then Nothing else Just filename))
<*> pure False <*> pure False
where where
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS

View file

@ -136,8 +136,9 @@ instance Proto.Serializable Service where
-- These mungings are ok, because an AssociatedFile is only ever displayed -- These mungings are ok, because an AssociatedFile is only ever displayed
-- to the user and does not need to match a file on disk. -- to the user and does not need to match a file on disk.
instance Proto.Serializable AssociatedFile where instance Proto.Serializable AssociatedFile where
serialize Nothing = "" serialize (AssociatedFile Nothing) = ""
serialize (Just af) = toInternalGitPath $ concatMap esc af serialize (AssociatedFile (Just af)) =
toInternalGitPath $ concatMap esc af
where where
esc '%' = "%%" esc '%' = "%%"
esc c esc c
@ -145,9 +146,9 @@ instance Proto.Serializable AssociatedFile where
| otherwise = [c] | otherwise = [c]
deserialize s = case fromInternalGitPath $ deesc [] s of deserialize s = case fromInternalGitPath $ deesc [] s of
[] -> Just Nothing [] -> Just (AssociatedFile Nothing)
f f
| isRelative f -> Just (Just f) | isRelative f -> Just (AssociatedFile (Just f))
| otherwise -> Nothing | otherwise -> Nothing
where where
deesc b [] = reverse b deesc b [] = reverse b

View file

@ -326,7 +326,8 @@ store r rsyncopts
return True return True
| Git.repoIsSsh (repo r) = if accessShell r | Git.repoIsSsh (repo r) = if accessShell r
then fileStorer $ \k f p -> Ssh.rsyncHelper (Just p) then fileStorer $ \k f p -> Ssh.rsyncHelper (Just p)
=<< Ssh.rsyncParamsRemote False r Upload k f Nothing =<< Ssh.rsyncParamsRemote False r Upload k f
(AssociatedFile Nothing)
else fileStorer $ Remote.Rsync.store rsyncopts else fileStorer $ Remote.Rsync.store rsyncopts
| otherwise = unsupportedUrl | otherwise = unsupportedUrl
@ -336,8 +337,10 @@ retrieve r rsyncopts
guardUsable (repo r) (return False) $ guardUsable (repo r) (return False) $
sink =<< liftIO (L.readFile $ gCryptLocation r k) sink =<< liftIO (L.readFile $ gCryptLocation r k)
| Git.repoIsSsh (repo r) = if accessShell r | Git.repoIsSsh (repo r) = if accessShell r
then fileRetriever $ \f k p -> then fileRetriever $ \f k p -> do
unlessM (Ssh.rsyncHelper (Just p) =<< Ssh.rsyncParamsRemote False r Download k f Nothing) $ ps <- Ssh.rsyncParamsRemote False r Download k f
(AssociatedFile Nothing)
unlessM (Ssh.rsyncHelper (Just p) ps) $
giveup "rsync failed" giveup "rsync failed"
else fileRetriever $ Remote.Rsync.retrieve rsyncopts else fileRetriever $ Remote.Rsync.retrieve rsyncopts
| otherwise = unsupportedUrl | otherwise = unsupportedUrl

View file

@ -479,8 +479,9 @@ copyFromRemote' r key file dest meterupdate
) )
feedprogressback' a = do feedprogressback' a = do
u <- getUUID u <- getUUID
let AssociatedFile afile = file
let fields = (Fields.remoteUUID, fromUUID u) let fields = (Fields.remoteUUID, fromUUID u)
: maybe [] (\f -> [(Fields.associatedFile, f)]) file : maybe [] (\f -> [(Fields.associatedFile, f)]) afile
Just (cmd, params) <- Ssh.git_annex_shell ConsumeStdin Just (cmd, params) <- Ssh.git_annex_shell ConsumeStdin
(repo r) "transferinfo" (repo r) "transferinfo"
[Param $ key2file key] fields [Param $ key2file key] fields

View file

@ -126,7 +126,7 @@ rsyncHelper m params = do
{- Generates rsync parameters that ssh to the remote and asks it {- Generates rsync parameters that ssh to the remote and asks it
- to either receive or send the key's content. -} - to either receive or send the key's content. -}
rsyncParamsRemote :: Bool -> Remote -> Direction -> Key -> FilePath -> AssociatedFile -> Annex [CommandParam] rsyncParamsRemote :: Bool -> Remote -> Direction -> Key -> FilePath -> AssociatedFile -> Annex [CommandParam]
rsyncParamsRemote unlocked r direction key file afile = do rsyncParamsRemote unlocked r direction key file (AssociatedFile afile) = do
u <- getUUID u <- getUUID
let fields = (Fields.remoteUUID, fromUUID u) let fields = (Fields.remoteUUID, fromUUID u)
: (Fields.unlocked, if unlocked then "1" else "") : (Fields.unlocked, if unlocked then "1" else "")

View file

@ -9,7 +9,7 @@ module Types (
Annex, Annex,
Backend, Backend,
Key, Key,
AssociatedFile, AssociatedFile(..),
UUID(..), UUID(..),
GitConfig(..), GitConfig(..),
RemoteGitConfig(..), RemoteGitConfig(..),

View file

@ -13,8 +13,6 @@ import Key
import Types.Transfer import Types.Transfer
import Git.FilePath import Git.FilePath
import Data.Maybe
data ActionItem data ActionItem
= ActionItemAssociatedFile AssociatedFile = ActionItemAssociatedFile AssociatedFile
| ActionItemKey | ActionItemKey
@ -37,15 +35,15 @@ instance MkActionItem (Transfer, TransferInfo) where
mkActionItem = uncurry ActionItemFailedTransfer mkActionItem = uncurry ActionItemFailedTransfer
actionItemDesc :: ActionItem -> Key -> String actionItemDesc :: ActionItem -> Key -> String
actionItemDesc (ActionItemAssociatedFile (Just f)) _ = f actionItemDesc (ActionItemAssociatedFile (AssociatedFile (Just f))) _ = f
actionItemDesc (ActionItemAssociatedFile Nothing) k = key2file k actionItemDesc (ActionItemAssociatedFile (AssociatedFile Nothing)) k = key2file k
actionItemDesc ActionItemKey k = key2file k actionItemDesc ActionItemKey k = key2file k
actionItemDesc (ActionItemBranchFilePath bfp) _ = descBranchFilePath bfp actionItemDesc (ActionItemBranchFilePath bfp) _ = descBranchFilePath bfp
actionItemDesc (ActionItemFailedTransfer _ i) k = actionItemDesc (ActionItemFailedTransfer _ i) k =
fromMaybe (key2file k) (associatedFile i) actionItemDesc (ActionItemAssociatedFile (associatedFile i)) k
actionItemWorkTreeFile :: ActionItem -> Maybe FilePath actionItemWorkTreeFile :: ActionItem -> Maybe FilePath
actionItemWorkTreeFile (ActionItemAssociatedFile af) = af actionItemWorkTreeFile (ActionItemAssociatedFile (AssociatedFile af)) = af
actionItemWorkTreeFile _ = Nothing actionItemWorkTreeFile _ = Nothing
actionItemTransferDirection :: ActionItem -> Maybe Direction actionItemTransferDirection :: ActionItem -> Maybe Direction

View file

@ -23,7 +23,8 @@ data Key = Key
} deriving (Eq, Ord, Read, Show) } deriving (Eq, Ord, Read, Show)
{- A filename may be associated with a Key. -} {- A filename may be associated with a Key. -}
type AssociatedFile = Maybe FilePath newtype AssociatedFile = AssociatedFile (Maybe FilePath)
deriving (Show, Eq, Ord)
{- There are several different varieties of keys. -} {- There are several different varieties of keys. -}
data KeyVariety data KeyVariety

View file

@ -36,13 +36,13 @@ data TransferInfo = TransferInfo
, transferTid :: Maybe ThreadId , transferTid :: Maybe ThreadId
, transferRemote :: Maybe Remote , transferRemote :: Maybe Remote
, bytesComplete :: Maybe Integer , bytesComplete :: Maybe Integer
, associatedFile :: Maybe FilePath , associatedFile :: AssociatedFile
, transferPaused :: Bool , transferPaused :: Bool
} }
deriving (Show, Eq, Ord) deriving (Show, Eq, Ord)
stubTransferInfo :: TransferInfo stubTransferInfo :: TransferInfo
stubTransferInfo = TransferInfo Nothing Nothing Nothing Nothing Nothing Nothing False stubTransferInfo = TransferInfo Nothing Nothing Nothing Nothing Nothing (AssociatedFile Nothing) False
data Direction = Upload | Download data Direction = Upload | Download
deriving (Eq, Ord, Show, Read) deriving (Eq, Ord, Show, Read)
@ -64,5 +64,5 @@ instance Arbitrary TransferInfo where
<*> pure Nothing -- remote not needed <*> pure Nothing -- remote not needed
<*> arbitrary <*> arbitrary
-- associated file cannot be empty (but can be Nothing) -- associated file cannot be empty (but can be Nothing)
<*> arbitrary `suchThat` (/= Just "") <*> (AssociatedFile <$> arbitrary `suchThat` (/= Just ""))
<*> arbitrary <*> arbitrary

View file

@ -6,10 +6,7 @@
<div .row> <div .row>
<div .col-sm-10> <div .col-sm-10>
<h3 .forcewrap .small-margin-top .tiny-margin-bottom> <h3 .forcewrap .small-margin-top .tiny-margin-bottom>
$maybe file <- associatedFile info #{desc transfer info}
#{file}
$nothing
#{key2file $ transferKey transfer}
$case transferDirection transfer $case transferDirection transfer
$of Upload $of Upload
&rarr; &rarr;