summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Annex/Content.hs2
-rw-r--r--Assistant/Alert.hs33
-rw-r--r--Assistant/Sync.hs87
-rw-r--r--Assistant/Threads/Pusher.hs4
-rw-r--r--Assistant/Threads/TransferScanner.hs17
-rw-r--r--Assistant/Threads/Transferrer.hs28
-rw-r--r--Assistant/Threads/XMPPClient.hs2
-rw-r--r--Config/Cost.hs2
-rw-r--r--Git/Command.hs6
-rw-r--r--Git/LsTree.hs12
-rw-r--r--Logs/Transfer.hs12
-rw-r--r--debian/changelog5
-rw-r--r--doc/bugs/Allow_syncing_to_a_specific_directory_on_a_USB_remote.mdwn31
-rw-r--r--doc/bugs/Assistant_uses_obsolete_GDU_volume_monitor.mdwn2
-rw-r--r--doc/bugs/Building_in_cabal_using_--bindir___126____47__bin_breaks_the_desktop_link.mdwn1
-rw-r--r--doc/bugs/Can__39__t_access_files_from___39__Removable_drive__39___repo_even_if_set_as_client.mdwn2
-rw-r--r--doc/bugs/Cannot_clone_an_annex.mdwn2
-rw-r--r--doc/bugs/Crash_when_adding_jabber_account_.mdwn2
-rw-r--r--doc/bugs/Creating_an_encrypted_S3_does_not_check_for_presence_of_GPG.mdwn1
-rw-r--r--doc/bugs/Enable__47__paus_syncing_to_remote_ssh_server_with_multiple_directories.mdwn2
-rw-r--r--doc/bugs/It_is_very_easy_to_turn_git-annex_into_a_zombie.mdwn2
-rw-r--r--doc/bugs/OSX_app_issues/old/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment (renamed from doc/bugs/OSX_app_issues/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment)0
-rw-r--r--doc/bugs/OSX_app_issues/old/comment_5_0d1df34f83a8dac9c438d93806236818._comment (renamed from doc/bugs/OSX_app_issues/comment_5_0d1df34f83a8dac9c438d93806236818._comment)0
-rw-r--r--doc/bugs/OSX_app_issues/old/comment_6_bc44d5aea5f77e331a32913ada293730._comment (renamed from doc/bugs/OSX_app_issues/comment_6_bc44d5aea5f77e331a32913ada293730._comment)0
-rw-r--r--doc/bugs/OSX_app_issues/old/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment (renamed from doc/bugs/OSX_app_issues/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment)0
-rw-r--r--doc/bugs/Provide_64-bit_standalone_build.mdwn5
-rw-r--r--doc/bugs/Renamed_special_remote_cannot_be_reactivated_by_the_webapp.mdwn2
-rw-r--r--doc/bugs/Rsync_encrypted_remote_asks_for_ssh_key_password_for_each_file.mdwn1
-rw-r--r--doc/bugs/Tries_to_upload_to_remote_although_remote_is_dead.mdwn2
-rw-r--r--doc/bugs/WEBDAV_443/comment_17_131a1b65c8008cf9f02c93d4fb75720b._comment (renamed from doc/bugs/Cannot_copy_to_a_git-annex_remote/comment_7_131a1b65c8008cf9f02c93d4fb75720b._comment)0
-rw-r--r--doc/bugs/__91__webapp__93___pause_syncing_with_specific_repository.mdwn3
-rw-r--r--doc/bugs/assistant_-_GTalk_collision.mdwn2
-rw-r--r--doc/bugs/creating_a_remote_server_repository.mdwn2
-rw-r--r--doc/bugs/git-annex:_Not_in_a_git_repository._.mdwn3
-rw-r--r--doc/bugs/host_with_rysnc_installed__44___not_recognized.mdwn (renamed from doc/bugs/host_with_rysnc_installed__44___not_recognized.txt)3
-rw-r--r--doc/bugs/long_running_assistant_causes_resource_starvation_on_OSX.mdwn4
-rw-r--r--doc/bugs/map_not_respecting_annex_ssh_options__63__.mdwn1
-rw-r--r--doc/bugs/uploads_queued_to_annex-ignore_remotes.mdwn2
-rw-r--r--doc/bugs/watcher_commits_unlocked_files.mdwn7
-rw-r--r--doc/bugs/webapp_hang.mdwn3
-rw-r--r--doc/design/assistant/blog/day_219__bug_triage.mdwn14
-rw-r--r--doc/todo/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn (renamed from doc/bugs/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn)4
-rw-r--r--doc/todo/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn (renamed from doc/bugs/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn)0
-rw-r--r--doc/todo/optinally_transfer_file_unencryptedly.mdwn (renamed from doc/bugs/optinally_transfer_file_unencryptedly.mdwn)0
44 files changed, 220 insertions, 93 deletions
diff --git a/Annex/Content.hs b/Annex/Content.hs
index f8c39e1bc..91ffe7a48 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -298,7 +298,7 @@ sendAnnex key rollback sendobject = go =<< prepSendAnnex key
-
- Note that the returned check action is, in some cases, run in the
- Annex monad of the remote that is receiving the object, rather than
- - the sender. So it cannot rely on Annex state, particular
+ - the sender. So it cannot rely on Annex state.
-}
prepSendAnnex :: Key -> Annex (Maybe (FilePath, Annex Bool))
prepSendAnnex key = withObjectLoc key indirect direct
diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs
index 4e733428a..206694031 100644
--- a/Assistant/Alert.hs
+++ b/Assistant/Alert.hs
@@ -35,6 +35,7 @@ data AlertName
| PairAlert String
| XMPPNeededAlert
| CloudRepoNeededAlert
+ | SyncAlert
deriving (Eq)
{- The first alert is the new alert, the second is an old alert.
@@ -237,28 +238,30 @@ commitAlert = activityAlert Nothing
[Tensed "Committing" "Committed", "changes to git"]
showRemotes :: [Remote] -> TenseChunk
-showRemotes = UnTensed . T.unwords . map (T.pack . Remote.name)
-
-pushRetryAlert :: [Remote] -> Alert
-pushRetryAlert rs = activityAlert
- (Just $ tenseWords [Tensed "Retrying" "Retried", "sync"])
- ["with", showRemotes rs]
+showRemotes = UnTensed . T.intercalate ", " . map (T.pack . Remote.name)
syncAlert :: [Remote] -> Alert
syncAlert rs = baseActivityAlert
- { alertHeader = Just $ tenseWords
+ { alertName = Just SyncAlert
+ , alertHeader = Just $ tenseWords
[Tensed "Syncing" "Synced", "with", showRemotes rs]
- , alertData = []
, alertPriority = Low
}
-scanAlert :: [Remote] -> Alert
-scanAlert rs = baseActivityAlert
- { alertHeader = Just $ tenseWords
- [Tensed "Scanning" "Scanned", showRemotes rs]
- , alertBlockDisplay = True
- , alertPriority = Low
- }
+syncResultAlert :: [Remote] -> [Remote] -> Alert
+syncResultAlert succeeded failed = makeAlertFiller (not $ null succeeded) $
+ baseActivityAlert
+ { alertName = Just SyncAlert
+ , alertHeader = Just $ tenseWords msg
+ }
+ where
+ msg
+ | null succeeded = ["Failed to sync with", showRemotes failed]
+ | null failed = ["Synced with", showRemotes succeeded]
+ | otherwise =
+ [ "Synced with", showRemotes succeeded
+ , "but not with", showRemotes failed
+ ]
sanityCheckAlert :: Alert
sanityCheckAlert = activityAlert
diff --git a/Assistant/Sync.hs b/Assistant/Sync.hs
index 39c30d108..54dcb42c2 100644
--- a/Assistant/Sync.hs
+++ b/Assistant/Sync.hs
@@ -48,31 +48,27 @@ reconnectRemotes _ [] = noop
reconnectRemotes notifypushes rs = void $ do
modifyDaemonStatus_ $ \s -> s
{ desynced = S.union (S.fromList $ map Remote.uuid xmppremotes) (desynced s) }
- if null normalremotes
- then go
- else alertWhile (syncAlert normalremotes) go
+ syncAction rs (const go)
where
gitremotes = filter (notspecialremote . Remote.repo) rs
- (xmppremotes, normalremotes) = partition isXMPPRemote gitremotes
- nonxmppremotes = snd $ partition isXMPPRemote rs
+ (xmppremotes, nonxmppremotes) = partition isXMPPRemote rs
notspecialremote r
| Git.repoIsUrl r = True
| Git.repoIsLocal r = True
+ | Git.repoIsLocalUnknown r = True
| otherwise = False
sync (Just branch) = do
- diverged <- snd <$> manualPull (Just branch) gitremotes
+ (failedpull, diverged) <- manualPull (Just branch) gitremotes
now <- liftIO getCurrentTime
- ok <- pushToRemotes' now notifypushes gitremotes
- return (ok, diverged)
+ failedpush <- pushToRemotes' now notifypushes gitremotes
+ return (nub $ failedpull ++ failedpush, diverged)
{- No local branch exists yet, but we can try pulling. -}
- sync Nothing = do
- diverged <- snd <$> manualPull Nothing gitremotes
- return (True, diverged)
+ sync Nothing = manualPull Nothing gitremotes
go = do
- (ok, diverged) <- sync
+ (failed, diverged) <- sync
=<< liftAnnex (inRepo Git.Branch.current)
addScanRemotes diverged nonxmppremotes
- return ok
+ return failed
{- Updates the local sync branch, then pushes it to all remotes, in
- parallel, along with the git-annex branch. This is the same
@@ -96,16 +92,14 @@ reconnectRemotes notifypushes rs = void $ do
- fallback mode, where our push is guarenteed to succeed if the remote is
- reachable. If the fallback fails, the push is queued to be retried
- later.
+ -
+ - Returns any remotes that it failed to push to.
-}
-pushToRemotes :: Bool -> [Remote] -> Assistant Bool
+pushToRemotes :: Bool -> [Remote] -> Assistant [Remote]
pushToRemotes notifypushes remotes = do
- now <- liftIO $ getCurrentTime
- let nonxmppremotes = snd $ partition isXMPPRemote remotes
- let go = pushToRemotes' now notifypushes remotes
- if null nonxmppremotes
- then go
- else alertWhile (syncAlert nonxmppremotes) go
-pushToRemotes' :: UTCTime -> Bool -> [Remote] -> Assistant Bool
+ now <- liftIO getCurrentTime
+ syncAction remotes (pushToRemotes' now notifypushes)
+pushToRemotes' :: UTCTime -> Bool -> [Remote] -> Assistant [Remote]
pushToRemotes' now notifypushes remotes = do
(g, branch, u) <- liftAnnex $ do
Annex.Branch.commit "update"
@@ -119,8 +113,8 @@ pushToRemotes' now notifypushes remotes = do
sendNetMessage $ Pushing (getXMPPClientID r) CanPush
return ret
where
- go _ Nothing _ _ _ = return True -- no branch, so nothing to do
- go _ _ _ _ [] = return True -- no remotes, so nothing to do
+ go _ Nothing _ _ _ = return [] -- no branch, so nothing to do
+ go _ _ _ _ [] = return [] -- no remotes, so nothing to do
go shouldretry (Just branch) g u rs = do
debug ["pushing to", show rs]
liftIO $ Command.Sync.updateBranch (Command.Sync.syncBranch branch) g
@@ -131,7 +125,7 @@ pushToRemotes' now notifypushes remotes = do
when notifypushes $
sendNetMessage $ NotifyPush $
map Remote.uuid succeeded
- return True
+ return failed
else if shouldretry
then retry branch g u failed
else fallback branch g u failed
@@ -154,30 +148,55 @@ pushToRemotes' now notifypushes remotes = do
when (notifypushes && (not $ null succeeded)) $
sendNetMessage $ NotifyPush $
map Remote.uuid succeeded
- return $ null failed
+ return failed
push g branch remote = Command.Sync.pushBranch remote branch g
-{- Manually pull from remotes and merge their branches. Returns the results
- - of all the pulls, and whether the git-annex branches of the remotes and
- - local had divierged before the pull.
+{- Displays an alert while running an action that syncs with some remotes,
+ - and returns any remotes that it failed to sync with.
+ -
+ - XMPP remotes are handled specially; since the action can only start
+ - an async process for them, they are not included in the alert, but are
+ - still passed to the action.
+ -}
+syncAction :: [Remote] -> ([Remote] -> Assistant [Remote]) -> Assistant [Remote]
+syncAction rs a
+ | null nonxmppremotes = a rs
+ | otherwise = do
+ i <- addAlert $ syncAlert nonxmppremotes
+ failed <- a rs
+ let failed' = filter (Git.repoIsLocalUnknown . Remote.repo) failed
+ let succeeded = filter (`notElem` failed) nonxmppremotes
+ updateAlertMap $ mergeAlert i $
+ syncResultAlert succeeded failed'
+ return failed
+ where
+ nonxmppremotes = filter (not . isXMPPRemote) rs
+
+{- Manually pull from remotes and merge their branches. Returns any
+ - remotes that it failed to pull from, and a Bool indicating
+ - whether the git-annex branches of the remotes and local had
+ - diverged before the pull.
-
- - After pulling from the normal git remotes, requests pushes from any XMPP
- - remotes. However, those pushes will run asynchronously, so their
+ - After pulling from the normal git remotes, requests pushes from any
+ - XMPP remotes. However, those pushes will run asynchronously, so their
- results are not included in the return data.
-}
-manualPull :: Maybe Git.Ref -> [Remote] -> Assistant ([Bool], Bool)
+manualPull :: Maybe Git.Ref -> [Remote] -> Assistant ([Remote], Bool)
manualPull currentbranch remotes = do
g <- liftAnnex gitRepo
let (xmppremotes, normalremotes) = partition isXMPPRemote remotes
- results <- liftIO $ forM normalremotes $ \r ->
- Git.Command.runBool [Param "fetch", Param $ Remote.name r] g
+ failed <- liftIO $ forM normalremotes $ \r ->
+ ifM (Git.Command.runBool [Param "fetch", Param $ Remote.name r] g)
+ ( return Nothing
+ , return $ Just r
+ )
haddiverged <- liftAnnex Annex.Branch.forceUpdate
forM_ normalremotes $ \r ->
liftAnnex $ Command.Sync.mergeRemote r currentbranch
forM_ xmppremotes $ \r ->
sendNetMessage $ Pushing (getXMPPClientID r) PushRequest
- return (results, haddiverged)
+ return (catMaybes failed, haddiverged)
{- Start syncing a newly added remote, using a background thread. -}
syncNewRemote :: Remote -> Assistant ()
diff --git a/Assistant/Threads/Pusher.hs b/Assistant/Threads/Pusher.hs
index d87aa8d3b..e90cca1ec 100644
--- a/Assistant/Threads/Pusher.hs
+++ b/Assistant/Threads/Pusher.hs
@@ -11,7 +11,6 @@ import Assistant.Common
import Assistant.Commits
import Assistant.Types.Commits
import Assistant.Pushes
-import Assistant.Alert
import Assistant.DaemonStatus
import Assistant.Sync
import Utility.ThreadScheduler
@@ -25,8 +24,7 @@ pushRetryThread = namedThread "PushRetrier" $ runEvery (Seconds halfhour) <~> do
topush <- getFailedPushesBefore (fromIntegral halfhour)
unless (null topush) $ do
debug ["retrying", show (length topush), "failed pushes"]
- void $ alertWhile (pushRetryAlert topush) $
- pushToRemotes True topush
+ void $ pushToRemotes True topush
where
halfhour = 1800
diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs
index d4ccf411a..d328ba197 100644
--- a/Assistant/Threads/TransferScanner.hs
+++ b/Assistant/Threads/TransferScanner.hs
@@ -12,7 +12,6 @@ import Assistant.Types.ScanRemotes
import Assistant.ScanRemotes
import Assistant.TransferQueue
import Assistant.DaemonStatus
-import Assistant.Alert
import Assistant.Drop
import Assistant.Sync
import Logs.Transfer
@@ -100,15 +99,13 @@ failedTransferScan r = do
expensiveScan :: [Remote] -> Assistant ()
expensiveScan rs = unless onlyweb $ do
debug ["starting scan of", show visiblers]
- void $ alertWhile (scanAlert visiblers) $ do
- g <- liftAnnex gitRepo
- (files, cleanup) <- liftIO $ LsFiles.inRepo [] g
- forM_ files $ \f -> do
- ts <- maybe (return []) (findtransfers f)
- =<< liftAnnex (Backend.lookupFile f)
- mapM_ (enqueue f) ts
- void $ liftIO cleanup
- return True
+ g <- liftAnnex gitRepo
+ (files, cleanup) <- liftIO $ LsFiles.inRepo [] g
+ forM_ files $ \f -> do
+ ts <- maybe (return []) (findtransfers f)
+ =<< liftAnnex (Backend.lookupFile f)
+ mapM_ (enqueue f) ts
+ void $ liftIO cleanup
debug ["finished scan of", show visiblers]
where
onlyweb = all (== webUUID) $ map Remote.uuid rs
diff --git a/Assistant/Threads/Transferrer.hs b/Assistant/Threads/Transferrer.hs
index 63306831f..2c487657a 100644
--- a/Assistant/Threads/Transferrer.hs
+++ b/Assistant/Threads/Transferrer.hs
@@ -18,6 +18,8 @@ import Logs.Transfer
import Logs.Location
import Annex.Content
import qualified Remote
+import qualified Types.Remote as Remote
+import qualified Git
import Types.Key
import Locations.UserConfig
import Assistant.Threads.TransferWatcher
@@ -44,18 +46,24 @@ startTransfer
-> TransferInfo
-> Assistant (Maybe (Transfer, TransferInfo, Assistant ()))
startTransfer program t info = case (transferRemote info, associatedFile info) of
- (Just remote, Just file) -> ifM (liftAnnex $ shouldTransfer t info)
- ( do
- debug [ "Transferring:" , describeTransfer t info ]
- notifyTransfer
- return $ Just (t, info, transferprocess remote file)
- , do
- debug [ "Skipping unnecessary transfer:",
- describeTransfer t info ]
+ (Just remote, Just file)
+ | Git.repoIsLocalUnknown (Remote.repo remote) -> do
+ -- optimisation for removable drives not plugged in
+ liftAnnex $ recordFailedTransfer t info
void $ removeTransfer t
- finishedTransfer t (Just info)
return Nothing
- )
+ | otherwise -> ifM (liftAnnex $ shouldTransfer t info)
+ ( do
+ debug [ "Transferring:" , describeTransfer t info ]
+ notifyTransfer
+ return $ Just (t, info, transferprocess remote file)
+ , do
+ debug [ "Skipping unnecessary transfer:",
+ describeTransfer t info ]
+ void $ removeTransfer t
+ finishedTransfer t (Just info)
+ return Nothing
+ )
_ -> return Nothing
where
direction = transferDirection t
diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs
index 79bb33b0e..1242c1d74 100644
--- a/Assistant/Threads/XMPPClient.hs
+++ b/Assistant/Threads/XMPPClient.hs
@@ -256,7 +256,7 @@ pull us = do
pullone [] _ = noop
pullone (r:rs) branch =
- unlessM (all id . fst <$> manualPull branch [r]) $
+ unlessM (null . fst <$> manualPull branch [r]) $
pullone rs branch
pairMsgReceived :: UrlRenderer -> PairStage -> UUID -> JID -> JID -> Assistant ()
diff --git a/Config/Cost.hs b/Config/Cost.hs
index 94bab1fe1..dc391a5a5 100644
--- a/Config/Cost.hs
+++ b/Config/Cost.hs
@@ -42,7 +42,7 @@ encryptedRemoteCostAdj = 50
- position longer than the list.
-}
insertCostAfter :: [Cost] -> Int -> [Cost]
-insertCostAfter [] _ = error "insertCostAfter: empty list"
+insertCostAfter [] _ = []
insertCostAfter l pos
| pos < 0 = costBetween 0 (l !! 0) : l
| nextpos > maxpos = l ++ [1 + l !! maxpos]
diff --git a/Git/Command.hs b/Git/Command.hs
index f3841c7fa..e6cec16fb 100644
--- a/Git/Command.hs
+++ b/Git/Command.hs
@@ -94,6 +94,12 @@ pipeNullSplit params repo = do
where
sep = "\0"
+pipeNullSplitStrict :: [CommandParam] -> Repo -> IO [String]
+pipeNullSplitStrict params repo = do
+ s <- pipeReadStrict params repo
+ return $ filter (not . null) $ split sep s
+ where
+ sep = "\0"
pipeNullSplitZombie :: [CommandParam] -> Repo -> IO [String]
pipeNullSplitZombie params repo = leaveZombie <$> pipeNullSplit params repo
diff --git a/Git/LsTree.hs b/Git/LsTree.hs
index c61ae7fab..6e4cd8470 100644
--- a/Git/LsTree.hs
+++ b/Git/LsTree.hs
@@ -29,15 +29,17 @@ data TreeItem = TreeItem
, file :: FilePath
} deriving Show
-{- Lists the complete contents of a tree. -}
+{- Lists the complete contents of a tree, with lazy output. -}
lsTree :: Ref -> Repo -> IO [TreeItem]
-lsTree t repo = map parseLsTree <$>
- pipeNullSplitZombie [Params "ls-tree --full-tree -z -r --", File $ show t] repo
+lsTree t repo = map parseLsTree <$> pipeNullSplitZombie ps repo
+ where
+ ps = [Params "ls-tree --full-tree -z -r --", File $ show t]
{- Lists specified files in a tree. -}
lsTreeFiles :: Ref -> [FilePath] -> Repo -> IO [TreeItem]
-lsTreeFiles t fs repo = map parseLsTree <$>
- pipeNullSplitZombie ([Params "ls-tree -z --", File $ show t] ++ map File fs) repo
+lsTreeFiles t fs repo = map parseLsTree <$> pipeNullSplitStrict ps repo
+ where
+ ps = [Params "ls-tree -z --", File $ show t] ++ map File fs
{- Parses a line of ls-tree output.
- (The --long format is not currently supported.) -}
diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs
index 6d6d3d890..c6f240be0 100644
--- a/Logs/Transfer.hs
+++ b/Logs/Transfer.hs
@@ -115,7 +115,7 @@ runTransfer t file shouldretry a = do
mode <- annexFileMode
ok <- retry info metervar $
bracketIO (prep tfile mode info) (cleanup tfile) (a meter)
- unless ok $ failed info
+ unless ok $ recordFailedTransfer t info
return ok
where
prep tfile mode info = catchMaybeIO $ do
@@ -132,10 +132,6 @@ runTransfer t file shouldretry a = do
void $ tryIO $ removeFile tfile
void $ tryIO $ removeFile $ transferLockFile tfile
closeFd fd
- failed info = do
- failedtfile <- fromRepo $ failedTransferFile t
- createAnnexDirectory $ takeDirectory failedtfile
- liftIO $ writeTransferInfoFile info failedtfile
retry oldinfo metervar run = do
v <- tryAnnex run
case v of
@@ -236,6 +232,12 @@ removeFailedTransfer t = do
f <- fromRepo $ failedTransferFile t
liftIO $ void $ tryIO $ removeFile f
+recordFailedTransfer :: Transfer -> TransferInfo -> Annex ()
+recordFailedTransfer t info = do
+ failedtfile <- fromRepo $ failedTransferFile t
+ createAnnexDirectory $ takeDirectory failedtfile
+ liftIO $ writeTransferInfoFile info failedtfile
+
{- The transfer information file to use for a given Transfer. -}
transferFile :: Transfer -> Git.Repo -> FilePath
transferFile (Transfer direction u key) r = transferDir direction r
diff --git a/debian/changelog b/debian/changelog
index d80ea4acf..8fa002604 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -21,6 +21,11 @@ git-annex (4.20130315) UNRELEASED; urgency=low
to the network, or connecting a drive.
* assistant: Fix OSX bug that prevented committing changed files to a
repository when in indirect mode.
+ * webapp: Improved alerts displayed when syncing with remotes, and
+ when syncing with a remote fails.
+ * webapp: Force wrap long filenames in transfer display.
+ * assistant: The ConfigMonitor left one zombie behind each time
+ it checked for changes, now fixed.
-- Joey Hess <joeyh@debian.org> Fri, 15 Mar 2013 00:10:07 -0400
diff --git a/doc/bugs/Allow_syncing_to_a_specific_directory_on_a_USB_remote.mdwn b/doc/bugs/Allow_syncing_to_a_specific_directory_on_a_USB_remote.mdwn
index 2bba743e4..9c6a0c9fc 100644
--- a/doc/bugs/Allow_syncing_to_a_specific_directory_on_a_USB_remote.mdwn
+++ b/doc/bugs/Allow_syncing_to_a_specific_directory_on_a_USB_remote.mdwn
@@ -1,9 +1,30 @@
-This follows up to the [comment made by Laszlo](http://git-annex.branchable.com/design/assistant/polls/what_is_preventing_me_from_using_git-annex_assistant/#comment-f26d3b6b45bb66601ecfaa883ace161c) on the [recent poll](http://git-annex.branchable.com/design/assistant/polls/what_is_preventing_me_from_using_git-annex_assistant/).
+This follows up to the [comment made by
+Laszlo](http://git-annex.branchable.com/design/assistant/polls/what_is_preventing_me_from_using_git-annex_assistant/#comment-f26d3b6b45bb66601ecfaa883ace161c)
+on the [recent
+poll](http://git-annex.branchable.com/design/assistant/polls/what_is_preventing_me_from_using_git-annex_assistant/).
-I too need to be able to select the directory on the remote drive that the annex will be synced to.
+I too need to be able to select the directory on the remote drive that the
+annex will be synced to.
-If I just add a remote drive via the web app, it syncs the repository to `/mnt/usb/annex`, and it looks like it just creates a bare repository in that folder. I need the repository to be synced to something like `/mnt/usb/subfolder/myspecifiedfoldername` and I need that remote to be a full repository.
+If I just add a remote drive via the web app, it syncs the repository to
+`/mnt/usb/annex`, and it looks like it just creates a bare repository in
+that folder. I need the repository to be synced to something like
+`/mnt/usb/subfolder/myspecifiedfoldername` and I need that remote to be a
+full repository.
-My use case is that I use the USB drive to keep annexes in sync between two computers. I have multiple annexes that need to be synced between the two computers, and none of them are in a directory called `annex`. I also need to be able to plug the drive into other computers and access the files directly, without doing a `git clone` or anything like that. I have all of this setup and working fine with just plain old git annex, but the web app does not seem to support creating new repositories with this workflow.
+My use case is that I use the USB drive to keep annexes in sync between two
+computers. I have multiple annexes that need to be synced between the two
+computers, and none of them are in a directory called `annex`. I also need
+to be able to plug the drive into other computers and access the files
+directly, without doing a `git clone` or anything like that. I have all of
+this setup and working fine with just plain old git annex, but the web app
+does not seem to support creating new repositories with this workflow.
-I think it makes a lot of sense to allow the web application to add a new remote that is simply a directory. People like me could specify the path of the directory to be on the mounted USB drive. Others may want to add a remote that is a mounted network share or something like that.
+I think it makes a lot of sense to allow the web application to add a new
+remote that is simply a directory. People like me could specify the path of
+the directory to be on the mounted USB drive. Others may want to add a
+remote that is a mounted network share or something like that.
+
+> [[done]], the webapp now has a "Add another repository" option,
+> and you can just enter the path to whatever place you like inside a USB
+> drive. --[[Joey]]
diff --git a/doc/bugs/Assistant_uses_obsolete_GDU_volume_monitor.mdwn b/doc/bugs/Assistant_uses_obsolete_GDU_volume_monitor.mdwn
index 832ad8021..c8110eaa0 100644
--- a/doc/bugs/Assistant_uses_obsolete_GDU_volume_monitor.mdwn
+++ b/doc/bugs/Assistant_uses_obsolete_GDU_volume_monitor.mdwn
@@ -24,3 +24,5 @@ Alternatively, git-annex should stop relying on any per-user services, and use k
### What version of git-annex are you using? On what operating system?
git-annex 3.20130102 on Linux 3.7.1, GNOME 3.7
+
+> [[done]] --[[Joey]]
diff --git a/doc/bugs/Building_in_cabal_using_--bindir___126____47__bin_breaks_the_desktop_link.mdwn b/doc/bugs/Building_in_cabal_using_--bindir___126____47__bin_breaks_the_desktop_link.mdwn
index 85a311716..223568ca8 100644
--- a/doc/bugs/Building_in_cabal_using_--bindir___126____47__bin_breaks_the_desktop_link.mdwn
+++ b/doc/bugs/Building_in_cabal_using_--bindir___126____47__bin_breaks_the_desktop_link.mdwn
@@ -12,3 +12,4 @@ Latest Head from git, Ubuntu 12.04
Please provide any additional information below.
I'm not sure whether this is a bug or not. I just ran into problems because I did not expect the cabal build process to create my desktop file but instead thought that git-annex will create it by it-self taking its own path. Perhaps it would make sense to produce an error if the bindir is invalid. An automatic expansion of '~' in the build script would be even better.
+> [[done]], I think it was a typo. --[[Joey]]
diff --git a/doc/bugs/Can__39__t_access_files_from___39__Removable_drive__39___repo_even_if_set_as_client.mdwn b/doc/bugs/Can__39__t_access_files_from___39__Removable_drive__39___repo_even_if_set_as_client.mdwn
index 1b90fb3f4..ef59954b7 100644
--- a/doc/bugs/Can__39__t_access_files_from___39__Removable_drive__39___repo_even_if_set_as_client.mdwn
+++ b/doc/bugs/Can__39__t_access_files_from___39__Removable_drive__39___repo_even_if_set_as_client.mdwn
@@ -17,3 +17,5 @@ What version of git-annex are you using? On what operating system?
I'm using 9e57edff287ac53fc4b1cefef7271e9ed17f2285 (Fri Feb 22 15:19:25 2013 +0000).
Ubuntu 12.10 x86_64
+
+[[!tag /design/assistant]]
diff --git a/doc/bugs/Cannot_clone_an_annex.mdwn b/doc/bugs/Cannot_clone_an_annex.mdwn
index 62e9ed27f..77989ecb6 100644
--- a/doc/bugs/Cannot_clone_an_annex.mdwn
+++ b/doc/bugs/Cannot_clone_an_annex.mdwn
@@ -65,3 +65,5 @@ the `SHA256` key is not present.
It looks like I'll have to rollback my ZFS snapshots and start over, but I'm
wondering: how was I even able to create this situation?
+
+> [[Done]]; user error. --[[Joey]]
diff --git a/doc/bugs/Crash_when_adding_jabber_account_.mdwn b/doc/bugs/Crash_when_adding_jabber_account_.mdwn
index aac1b3321..678890cad 100644
--- a/doc/bugs/Crash_when_adding_jabber_account_.mdwn
+++ b/doc/bugs/Crash_when_adding_jabber_account_.mdwn
@@ -28,3 +28,5 @@ OS: Ubuntu 12.04.1 LTS 3.2.0-35-generic-pae #55-Ubuntu SMP Wed Dec 5 18:04:39 UT
On dmesg:
[45773.212717] git-annex[26779]: segfault at b724e840 ip 09699150 sp b4cfd038 error 7 in git-annex[8048000+1762000]
+[[!tag /design/assistant]]
+> [[done]], see comments --[[Joey]]
diff --git a/doc/bugs/Creating_an_encrypted_S3_does_not_check_for_presence_of_GPG.mdwn b/doc/bugs/Creating_an_encrypted_S3_does_not_check_for_presence_of_GPG.mdwn
index aab03cd7f..f497c8756 100644
--- a/doc/bugs/Creating_an_encrypted_S3_does_not_check_for_presence_of_GPG.mdwn
+++ b/doc/bugs/Creating_an_encrypted_S3_does_not_check_for_presence_of_GPG.mdwn
@@ -15,3 +15,4 @@ What version of git-annex are you using? On what operating system?
Please provide any additional information below.
+[[!tag /design/assistant/OSX]]
diff --git a/doc/bugs/Enable__47__paus_syncing_to_remote_ssh_server_with_multiple_directories.mdwn b/doc/bugs/Enable__47__paus_syncing_to_remote_ssh_server_with_multiple_directories.mdwn
index 83ae9ccdc..6306a4bd1 100644
--- a/doc/bugs/Enable__47__paus_syncing_to_remote_ssh_server_with_multiple_directories.mdwn
+++ b/doc/bugs/Enable__47__paus_syncing_to_remote_ssh_server_with_multiple_directories.mdwn
@@ -15,3 +15,5 @@ Version: 4.20130314, Debian
Please provide any additional information below.
I am an "webinterface only" user.
+
+[[!tag /design/assistant]]
diff --git a/doc/bugs/It_is_very_easy_to_turn_git-annex_into_a_zombie.mdwn b/doc/bugs/It_is_very_easy_to_turn_git-annex_into_a_zombie.mdwn
index dd92591e6..6bf458141 100644
--- a/doc/bugs/It_is_very_easy_to_turn_git-annex_into_a_zombie.mdwn
+++ b/doc/bugs/It_is_very_easy_to_turn_git-annex_into_a_zombie.mdwn
@@ -21,3 +21,5 @@ What version of git-annex are you using? On what operating system?
Please provide any additional information below.
+[[!meta title="strange OSX behavior when killed"]]
+[[!tag /design/assistant/OSX unreproducible]]
diff --git a/doc/bugs/OSX_app_issues/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment b/doc/bugs/OSX_app_issues/old/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment
index 758140903..758140903 100644
--- a/doc/bugs/OSX_app_issues/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment
+++ b/doc/bugs/OSX_app_issues/old/comment_4_4cda124b57ddc87645d5822f14ed5c59._comment
diff --git a/doc/bugs/OSX_app_issues/comment_5_0d1df34f83a8dac9c438d93806236818._comment b/doc/bugs/OSX_app_issues/old/comment_5_0d1df34f83a8dac9c438d93806236818._comment
index 89078a7da..89078a7da 100644
--- a/doc/bugs/OSX_app_issues/comment_5_0d1df34f83a8dac9c438d93806236818._comment
+++ b/doc/bugs/OSX_app_issues/old/comment_5_0d1df34f83a8dac9c438d93806236818._comment
diff --git a/doc/bugs/OSX_app_issues/comment_6_bc44d5aea5f77e331a32913ada293730._comment b/doc/bugs/OSX_app_issues/old/comment_6_bc44d5aea5f77e331a32913ada293730._comment
index 187197e81..187197e81 100644
--- a/doc/bugs/OSX_app_issues/comment_6_bc44d5aea5f77e331a32913ada293730._comment
+++ b/doc/bugs/OSX_app_issues/old/comment_6_bc44d5aea5f77e331a32913ada293730._comment
diff --git a/doc/bugs/OSX_app_issues/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment b/doc/bugs/OSX_app_issues/old/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment
index bdbdfc9ab..bdbdfc9ab 100644
--- a/doc/bugs/OSX_app_issues/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment
+++ b/doc/bugs/OSX_app_issues/old/comment_7_acd73cc5c4caa88099e2d2f19947aadf._comment
diff --git a/doc/bugs/Provide_64-bit_standalone_build.mdwn b/doc/bugs/Provide_64-bit_standalone_build.mdwn
index 856e22b9a..7f24e0055 100644
--- a/doc/bugs/Provide_64-bit_standalone_build.mdwn
+++ b/doc/bugs/Provide_64-bit_standalone_build.mdwn
@@ -1 +1,6 @@
The 32-bit standalone build appears to require two libraries (lib32-libyaml and lib32-gsasl) that are not available on Arch Linux. [See the comments on the AUR package](https://aur.archlinux.org/packages/git-annex-bin/). I'd appreciate it if you could bring back the 64-bit build.
+
+> [[done]], based on <https://aur.archlinux.org/packages/git-annex-bin/>
+> they are managing with what I am providing. Also, Arch Linux has a
+> proper build of git-annex from source, so I'm not going to worry about
+> git-annex-bin, the rationalle for which I don't even understand. --[[Joey]]
diff --git a/doc/bugs/Renamed_special_remote_cannot_be_reactivated_by_the_webapp.mdwn b/doc/bugs/Renamed_special_remote_cannot_be_reactivated_by_the_webapp.mdwn
index 605027f28..ccf6ef1ca 100644
--- a/doc/bugs/Renamed_special_remote_cannot_be_reactivated_by_the_webapp.mdwn
+++ b/doc/bugs/Renamed_special_remote_cannot_be_reactivated_by_the_webapp.mdwn
@@ -26,3 +26,5 @@ Workaround:
* rename `metaarray` to `ma` again using the webapp
Perhaps the renaming of the remote not surviving clones is unavoidable, but the webapp should be able to cope with the situation. Thanks.
+
+[[!tag /design/assistant]]
diff --git a/doc/bugs/Rsync_encrypted_remote_asks_for_ssh_key_password_for_each_file.mdwn b/doc/bugs/Rsync_encrypted_remote_asks_for_ssh_key_password_for_each_file.mdwn
index da486c30b..65a2c8fdc 100644
--- a/doc/bugs/Rsync_encrypted_remote_asks_for_ssh_key_password_for_each_file.mdwn
+++ b/doc/bugs/Rsync_encrypted_remote_asks_for_ssh_key_password_for_each_file.mdwn
@@ -24,3 +24,4 @@ What version of git-annex are you using? On what operating system?
Please provide any additional information below.
+[[!meta title="rsync special remote does not use ssh connection caching"]]
diff --git a/doc/bugs/Tries_to_upload_to_remote_although_remote_is_dead.mdwn b/doc/bugs/Tries_to_upload_to_remote_although_remote_is_dead.mdwn
index 6b8f66d02..73f8a046a 100644
--- a/doc/bugs/Tries_to_upload_to_remote_although_remote_is_dead.mdwn
+++ b/doc/bugs/Tries_to_upload_to_remote_although_remote_is_dead.mdwn
@@ -48,4 +48,4 @@ git-annex HEAD from yesterdays git. Ubuntu 12.10
Please provide any additional information below.
-
+[[!tag /design/assistant unreproducible]]
diff --git a/doc/bugs/Cannot_copy_to_a_git-annex_remote/comment_7_131a1b65c8008cf9f02c93d4fb75720b._comment b/doc/bugs/WEBDAV_443/comment_17_131a1b65c8008cf9f02c93d4fb75720b._comment
index 515976b85..515976b85 100644
--- a/doc/bugs/Cannot_copy_to_a_git-annex_remote/comment_7_131a1b65c8008cf9f02c93d4fb75720b._comment
+++ b/doc/bugs/WEBDAV_443/comment_17_131a1b65c8008cf9f02c93d4fb75720b._comment
diff --git a/doc/bugs/__91__webapp__93___pause_syncing_with_specific_repository.mdwn b/doc/bugs/__91__webapp__93___pause_syncing_with_specific_repository.mdwn
index dad961d9f..dca16e4d3 100644
--- a/doc/bugs/__91__webapp__93___pause_syncing_with_specific_repository.mdwn
+++ b/doc/bugs/__91__webapp__93___pause_syncing_with_specific_repository.mdwn
@@ -3,3 +3,6 @@
In a red bubble it says: "Synced with rose 60justin"
That verbage is the same if they all succeed. The only difference is the red instead of green. Would be nice to know exactly which machine to kick (if I didn't already know, eg I was syncing only with repositories not under my control).
+
+> Fixed alert display. Webapp has allowed pausing syncing with a repository
+> for a while. [[done]] --[[Joey]]
diff --git a/doc/bugs/assistant_-_GTalk_collision.mdwn b/doc/bugs/assistant_-_GTalk_collision.mdwn
index 62e7062eb..b814166ae 100644
--- a/doc/bugs/assistant_-_GTalk_collision.mdwn
+++ b/doc/bugs/assistant_-_GTalk_collision.mdwn
@@ -13,3 +13,5 @@ I expect to remain invisible, but I get the following warning: "Oops! You are no
##Please provide any additional information below.
Syncing between the repositories works ok.
+
+[[!tag /design/assistant]]
diff --git a/doc/bugs/creating_a_remote_server_repository.mdwn b/doc/bugs/creating_a_remote_server_repository.mdwn
index 90e85bc8b..280b7a662 100644
--- a/doc/bugs/creating_a_remote_server_repository.mdwn
+++ b/doc/bugs/creating_a_remote_server_repository.mdwn
@@ -21,4 +21,4 @@ Version: 3.20130124
Please provide any additional information below.
[[!tag /design/assistant]]
-[[!meta title="ssh password prompting"]]
+[[!meta title="ssh password prompting issue with assistant"]]
diff --git a/doc/bugs/git-annex:_Not_in_a_git_repository._.mdwn b/doc/bugs/git-annex:_Not_in_a_git_repository._.mdwn
index fd90406cf..a2817661e 100644
--- a/doc/bugs/git-annex:_Not_in_a_git_repository._.mdwn
+++ b/doc/bugs/git-annex:_Not_in_a_git_repository._.mdwn
@@ -17,3 +17,6 @@ Debian wheezy with git-annex version: 3.20130114
Please provide any additional information below.
Its working if i start `git-annex webapp` as root. I had the same error on previous version.
+
+> I've made some improvements. Think this was user error. [[done]]
+> --[[Joey]]
diff --git a/doc/bugs/host_with_rysnc_installed__44___not_recognized.txt b/doc/bugs/host_with_rysnc_installed__44___not_recognized.mdwn
index e5dd7dd4b..e411eaf9c 100644
--- a/doc/bugs/host_with_rysnc_installed__44___not_recognized.txt
+++ b/doc/bugs/host_with_rysnc_installed__44___not_recognized.mdwn
@@ -10,3 +10,6 @@ What version of git-annex are you using? On what operating system?
Please provide any additional information below.
ssh keys were installed to allow login, when ssh-askpass was not found on osx version
+
+[[!meta title="webapp rsync probe command failed on FreeNAS box"]]
+[[!tag /design/assistant]]
diff --git a/doc/bugs/long_running_assistant_causes_resource_starvation_on_OSX.mdwn b/doc/bugs/long_running_assistant_causes_resource_starvation_on_OSX.mdwn
index 392090c9d..f556d16e9 100644
--- a/doc/bugs/long_running_assistant_causes_resource_starvation_on_OSX.mdwn
+++ b/doc/bugs/long_running_assistant_causes_resource_starvation_on_OSX.mdwn
@@ -24,3 +24,7 @@ Please provide any additional information below.
I'm really not sure what to look for next. Happy to take suggestions.
[!tag /design/assistant]]
+
+> [[done]], I found the zombie leak; the ConfigMonitor was
+> leaving one zombie every time it checked a push/pull.
+> Not a fast leak, but over time they would add up. --[[Joey]]
diff --git a/doc/bugs/map_not_respecting_annex_ssh_options__63__.mdwn b/doc/bugs/map_not_respecting_annex_ssh_options__63__.mdwn
index 0d362db21..63dfec4ac 100644
--- a/doc/bugs/map_not_respecting_annex_ssh_options__63__.mdwn
+++ b/doc/bugs/map_not_respecting_annex_ssh_options__63__.mdwn
@@ -35,3 +35,4 @@ relevant part of .git/config:
supported repository versions: 3
upgrade supported from repository versions: 0 1 2
+> [[done]], see comment --[[Joey]]
diff --git a/doc/bugs/uploads_queued_to_annex-ignore_remotes.mdwn b/doc/bugs/uploads_queued_to_annex-ignore_remotes.mdwn
index 549147dcc..6f45cb8ff 100644
--- a/doc/bugs/uploads_queued_to_annex-ignore_remotes.mdwn
+++ b/doc/bugs/uploads_queued_to_annex-ignore_remotes.mdwn
@@ -30,3 +30,5 @@ The remote in question:
url = git@git.example.com:annex-home
fetch = +refs/heads/*:refs/remotes/origin/*
annex-ignore = true
+
+> belived to be [[fixed|done]] --[[Joey]]
diff --git a/doc/bugs/watcher_commits_unlocked_files.mdwn b/doc/bugs/watcher_commits_unlocked_files.mdwn
index 37c79e353..37e50fca0 100644
--- a/doc/bugs/watcher_commits_unlocked_files.mdwn
+++ b/doc/bugs/watcher_commits_unlocked_files.mdwn
@@ -28,3 +28,10 @@ Possible approaches:
how to find the file to unlock it.
[[!meta title="assistant: watcher_commits_unlocked_files"]]
+
+> [[done]]; I just tested and somehow this no longer happens;
+> the watcher/assistant leaves the unlocked file alone, and then
+> as soon as it's modified re-adds it.
+>
+> Also, of course, there is direct mode, which avoids needing to unlock...
+> --[[Joey]]
diff --git a/doc/bugs/webapp_hang.mdwn b/doc/bugs/webapp_hang.mdwn
index 73fcbbe99..a1d296893 100644
--- a/doc/bugs/webapp_hang.mdwn
+++ b/doc/bugs/webapp_hang.mdwn
@@ -139,3 +139,6 @@ expecting a request body?
0x0020: 8010 0800 fe28 0000 0101 080a 004a dfe0 .....(.......J..
0x0030: 004a b3da .J..
</pre>
+
+[[!tag /design/assistant]]
+[[done]]
diff --git a/doc/design/assistant/blog/day_219__bug_triage.mdwn b/doc/design/assistant/blog/day_219__bug_triage.mdwn
new file mode 100644
index 000000000..82494ceca
--- /dev/null
+++ b/doc/design/assistant/blog/day_219__bug_triage.mdwn
@@ -0,0 +1,14 @@
+Triaged some of the older bugs and was able to close a lot of them.
+
+-----
+
+Should mention that I will be in Boston this weekend, attending
+[LibrePlanet 2013](http://libreplanet.org/wiki/LibrePlanet:Conference/2013).
+Drop by and find me, I'll have git-annex stickers! ;)
+
+-----
+
+Did some UI work on the webapp. Minor stuff, but stuff that needed to be
+fixed up. Like inserting zero-width spaces into filenames displayed in it
+so very long filenames always get reasonably wrapped by the browser.
+(Perhaps there's a better way to do that with CSS?)
diff --git a/doc/bugs/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn b/doc/todo/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn
index 383410704..a7b30ded5 100644
--- a/doc/bugs/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn
+++ b/doc/todo/assistant_cannot_set_up_remote_repo_via_an_ssh_alias_or_an_ip_address.mdwn
@@ -8,7 +8,9 @@ alias for a hostname at no-ip.com.) Despite the fact that "homeworld" is a
viable ssh target because of the alias, the assistant doesn't recognize it
as a valid host to ssh to.
-I had trouble with an ip address the first time I tried it but just tried it again and it worked fine, so please disregard that part of the title of this bug report.
+I had trouble with an ip address the first time I tried it but just tried
+it again and it worked fine, so please disregard that part of the title of
+this bug report.
What is the expected output? What do you see instead?
diff --git a/doc/bugs/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn b/doc/todo/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn
index 361585a78..361585a78 100644
--- a/doc/bugs/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn
+++ b/doc/todo/automatic_merge_of_synced_branches_upon___34__git_annex_sync__34__.mdwn
diff --git a/doc/bugs/optinally_transfer_file_unencryptedly.mdwn b/doc/todo/optinally_transfer_file_unencryptedly.mdwn
index d622fcdab..d622fcdab 100644
--- a/doc/bugs/optinally_transfer_file_unencryptedly.mdwn
+++ b/doc/todo/optinally_transfer_file_unencryptedly.mdwn