diff --git a/Annex/CatFile.hs b/Annex/CatFile.hs index f90e74509c..f708003022 100644 --- a/Annex/CatFile.hs +++ b/Annex/CatFile.hs @@ -12,6 +12,7 @@ module Annex.CatFile ( catFileHandle, catKey, catKeyFile, + catKeyFileHEAD, ) where import qualified Data.ByteString.Lazy as L @@ -87,6 +88,9 @@ catKey ref = do -} catKeyFile :: FilePath -> Annex (Maybe Key) catKeyFile f = ifM (Annex.getState Annex.daemon) - ( catKey $ Ref $ "HEAD:./" ++ f + ( catKeyFileHEAD f , catKey $ Ref $ ":./" ++ f ) + +catKeyFileHEAD :: FilePath -> Annex (Maybe Key) +catKeyFileHEAD f = catKey $ Ref $ "HEAD:./" ++ f diff --git a/Annex/Quvi.hs b/Annex/Quvi.hs new file mode 100644 index 0000000000..a79b17d619 --- /dev/null +++ b/Annex/Quvi.hs @@ -0,0 +1,20 @@ +{- quvi options for git-annex + - + - Copyright 2013 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE Rank2Types #-} + +module Annex.Quvi where + +import Common.Annex +import qualified Annex +import Utility.Quvi +import Utility.Url + +withQuviOptions :: forall a. (Query a) -> [CommandParam] -> URLString -> Annex a +withQuviOptions a ps url = do + opts <- map Param . annexQuviOptions <$> Annex.getGitConfig + liftIO $ a (ps++opts) url diff --git a/Assistant/NetMessager.hs b/Assistant/NetMessager.hs index 329d808fcf..acb18b6484 100644 --- a/Assistant/NetMessager.hs +++ b/Assistant/NetMessager.hs @@ -29,6 +29,10 @@ notifyNetMessagerRestart :: Assistant () notifyNetMessagerRestart = flip writeSV () <<~ (netMessagerRestart . netMessager) +{- This can be used to get an early indication if the network has + - changed, to immediately restart a connection. However, that is not + - available on all systems, so clients also need to deal with + - restarting dropped connections in the usual way. -} waitNetMessagerRestart :: Assistant () waitNetMessagerRestart = readSV <<~ (netMessagerRestart . netMessager) diff --git a/Assistant/Threads/NetWatcher.hs b/Assistant/Threads/NetWatcher.hs index 5974de11d3..0d8442c696 100644 --- a/Assistant/Threads/NetWatcher.hs +++ b/Assistant/Threads/NetWatcher.hs @@ -39,7 +39,11 @@ netWatcherThread = thread noop - network connection changes, but it also ensures that - any networked remotes that may have not been routable for a - while (despite the local network staying up), are synced with - - periodically. -} + - periodically. + - + - Note that it does not call notifyNetMessagerRestart, because + - it doesn't know that the network has changed. + -} netWatcherFallbackThread :: NamedThread netWatcherFallbackThread = namedThread "NetWatcherFallback" $ runEvery (Seconds 3600) <~> handleConnection diff --git a/Assistant/Threads/PairListener.hs b/Assistant/Threads/PairListener.hs index 8fc015c223..882c95cc21 100644 --- a/Assistant/Threads/PairListener.hs +++ b/Assistant/Threads/PairListener.hs @@ -27,7 +27,7 @@ pairListenerThread :: UrlRenderer -> NamedThread pairListenerThread urlrenderer = namedThread "PairListener" $ do listener <- asIO1 $ go [] [] liftIO $ withSocketsDo $ - runEvery (Seconds 1) $ void $ tryIO $ + runEvery (Seconds 60) $ void $ tryIO $ listener =<< getsock where {- Note this can crash if there's no network interface, diff --git a/Build/Configure.hs b/Build/Configure.hs index 15b90ebe3d..31fbbf1dd7 100644 --- a/Build/Configure.hs +++ b/Build/Configure.hs @@ -32,6 +32,7 @@ tests = , TestCase "curl" $ testCmd "curl" "curl --version >/dev/null" , TestCase "wget" $ testCmd "wget" "wget --version >/dev/null" , TestCase "bup" $ testCmd "bup" "bup --version >/dev/null" + , TestCase "quvi" $ testCmd "quvi" "quvi --version >/dev/null" , TestCase "ionice" $ testCmd "ionice" "ionice -c3 true >/dev/null" , TestCase "gpg" $ maybeSelectCmd "gpg" [ ("gpg", "--version >/dev/null") diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs index d172a6869a..0309a6a598 100644 --- a/Command/AddUrl.hs +++ b/Command/AddUrl.hs @@ -27,6 +27,8 @@ import Annex.Content.Direct import Logs.Location import qualified Logs.Transfer as Transfer import Utility.Daemon (checkDaemon) +import Annex.Quvi +import qualified Utility.Quvi as Quvi def :: [Command] def = [notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption] $ @@ -51,15 +53,51 @@ seek = [withField fileOption return $ \f -> start :: Bool -> Maybe FilePath -> Maybe Int -> String -> CommandStart start relaxed optfile pathdepth s = go $ fromMaybe bad $ parseURI s where - bad = fromMaybe (error $ "bad url " ++ s) $ - parseURI $ escapeURIString isUnescapedInURI s - go url = do - pathmax <- liftIO $ fileNameLengthLimit "." - let file = fromMaybe (url2file url pathdepth pathmax) optfile + (s', downloader) = getDownloader s + bad = fromMaybe (error $ "bad url " ++ s') $ + parseURI $ escapeURIString isUnescapedInURI s' + badquvi = error $ "quvi does not know how to download url " ++ s' + choosefile = flip fromMaybe optfile + go url = case downloader of + QuviDownloader -> usequvi + DefaultDownloader -> ifM (liftIO $ Quvi.supported s') + ( usequvi + , do + pathmax <- liftIO $ fileNameLengthLimit "." + let file = choosefile $ url2file url pathdepth pathmax + showStart "addurl" file + next $ perform relaxed s' file + ) + usequvi = do + page <- fromMaybe badquvi + <$> withQuviOptions Quvi.forceQuery [Quvi.quiet, Quvi.httponly] s' + let link = fromMaybe badquvi $ headMaybe $ Quvi.pageLinks page + let file = choosefile $ sanitizeFilePath $ + Quvi.pageTitle page ++ "." ++ Quvi.linkSuffix link showStart "addurl" file - next $ perform relaxed s file + next $ performQuvi relaxed s' (Quvi.linkUrl link) file -perform :: Bool -> String -> FilePath -> CommandPerform +performQuvi :: Bool -> URLString -> URLString -> FilePath -> CommandPerform +performQuvi relaxed pageurl videourl file = ifAnnexed file addurl geturl + where + quviurl = setDownloader pageurl QuviDownloader + addurl (key, _backend) = next $ cleanup quviurl file key Nothing + geturl = do + key <- Backend.URL.fromUrl quviurl Nothing + ifM (pure relaxed <||> Annex.getState Annex.fast) + ( next $ cleanup quviurl file key Nothing + , do + tmp <- fromRepo $ gitAnnexTmpLocation key + showOutput + ok <- Transfer.download webUUID key (Just file) Transfer.forwardRetry $ const $ do + liftIO $ createDirectoryIfMissing True (parentDir tmp) + downloadUrl [videourl] tmp + if ok + then next $ cleanup quviurl file key (Just tmp) + else stop + ) + +perform :: Bool -> URLString -> FilePath -> CommandPerform perform relaxed url file = ifAnnexed file addurl geturl where geturl = next $ addUrlFile relaxed url file @@ -78,7 +116,7 @@ perform relaxed url file = ifAnnexed file addurl geturl stop ) -addUrlFile :: Bool -> String -> FilePath -> Annex Bool +addUrlFile :: Bool -> URLString -> FilePath -> Annex Bool addUrlFile relaxed url file = do liftIO $ createDirectoryIfMissing True (parentDir file) ifM (Annex.getState Annex.fast <||> pure relaxed) @@ -88,7 +126,7 @@ addUrlFile relaxed url file = do download url file ) -download :: String -> FilePath -> Annex Bool +download :: URLString -> FilePath -> Annex Bool download url file = do dummykey <- genkey tmp <- fromRepo $ gitAnnexTmpLocation dummykey @@ -130,7 +168,7 @@ download url file = do downloadUrl [url] tmp -cleanup :: String -> FilePath -> Key -> Maybe FilePath -> Annex Bool +cleanup :: URLString -> FilePath -> Key -> Maybe FilePath -> Annex Bool cleanup url file key mtmp = do when (isJust mtmp) $ logStatus key InfoPresent @@ -144,7 +182,7 @@ cleanup url file key mtmp = do maybe noop (moveAnnex key) mtmp return True -nodownload :: Bool -> String -> FilePath -> Annex Bool +nodownload :: Bool -> URLString -> FilePath -> Annex Bool nodownload relaxed url file = do headers <- getHttpHeaders (exists, size) <- if relaxed diff --git a/Command/Copy.hs b/Command/Copy.hs index 4e1646ad1e..9fd97334ad 100644 --- a/Command/Copy.hs +++ b/Command/Copy.hs @@ -9,6 +9,7 @@ module Command.Copy where import Common.Annex import Command +import GitAnnex.Options import qualified Command.Move import qualified Remote import Annex.Wanted @@ -19,8 +20,8 @@ def = [withOptions Command.Move.moveOptions $ command "copy" paramPaths seek seek :: [CommandSeek] seek = - [ withField Command.Move.toOption Remote.byNameWithUUID $ \to -> - withField Command.Move.fromOption Remote.byNameWithUUID $ \from -> + [ withField toOption Remote.byNameWithUUID $ \to -> + withField fromOption Remote.byNameWithUUID $ \from -> withKeyOptions (Command.Move.startKey to from False) $ withFilesInGit $ whenAnnexed $ start to from ] diff --git a/Command/Fsck.hs b/Command/Fsck.hs index 6464fc002f..35d6fc7b61 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -33,7 +33,7 @@ import qualified Option import Types.Key import Utility.HumanTime import Git.FilePath -import GitAnnex.Options +import GitAnnex.Options hiding (fromOption) #ifndef mingw32_HOST_OS import System.Posix.Process (getProcessID) diff --git a/Command/Get.hs b/Command/Get.hs index 31a75c3e1b..981c2245b8 100644 --- a/Command/Get.hs +++ b/Command/Get.hs @@ -11,10 +11,10 @@ import Common.Annex import Command import qualified Remote import Annex.Content -import qualified Command.Move import Logs.Transfer import Annex.Wanted import GitAnnex.Options +import qualified Command.Move import Types.Key def :: [Command] @@ -22,11 +22,11 @@ def = [withOptions getOptions $ command "get" paramPaths seek SectionCommon "make content of annexed files available"] getOptions :: [Option] -getOptions = [Command.Move.fromOption] ++ keyOptions +getOptions = fromOption : keyOptions seek :: [CommandSeek] seek = - [ withField Command.Move.fromOption Remote.byNameWithUUID $ \from -> + [ withField fromOption Remote.byNameWithUUID $ \from -> withKeyOptions (startKeys from) $ withFilesInGit $ whenAnnexed $ start from ] diff --git a/Command/Import.hs b/Command/Import.hs index 518666af91..dcadd96ce4 100644 --- a/Command/Import.hs +++ b/Command/Import.hs @@ -1,6 +1,6 @@ {- git-annex command - - - Copyright 2012 Joey Hess + - Copyright 2012-2013 Joey Hess - - Licensed under the GNU GPL version 3 or higher. -} @@ -13,30 +13,92 @@ import Common.Annex import Command import qualified Annex import qualified Command.Add +import qualified Option +import Utility.CopyFile +import Backend +import Remote +import Types.KeySource def :: [Command] -def = [notBareRepo $ command "import" paramPaths seek +def = [withOptions opts $ notBareRepo $ command "import" paramPaths seek SectionCommon "move and add files from outside git working copy"] -seek :: [CommandSeek] -seek = [withPathContents start] +opts :: [Option] +opts = + [ duplicateOption + , deduplicateOption + , cleanDuplicatesOption + ] -start :: (FilePath, FilePath) -> CommandStart -start (srcfile, destfile) = +duplicateOption :: Option +duplicateOption = Option.flag [] "duplicate" "do not delete outside files" + +deduplicateOption :: Option +deduplicateOption = Option.flag [] "deduplicate" "do not add files whose content has been seen" + +cleanDuplicatesOption :: Option +cleanDuplicatesOption = Option.flag [] "clean-duplicates" "delete outside duplicate files (import nothing)" + +data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates + deriving (Eq) + +getDuplicateMode :: Annex DuplicateMode +getDuplicateMode = gen + <$> getflag duplicateOption + <*> getflag deduplicateOption + <*> getflag cleanDuplicatesOption + where + getflag = Annex.getFlag . Option.name + gen False False False = Default + gen True False False = Duplicate + gen False True False = DeDuplicate + gen False False True = CleanDuplicates + gen _ _ _ = error "bad combination of --duplicate, --deduplicate, --clean-duplicates" + +seek :: [CommandSeek] +seek = [withValue getDuplicateMode $ \mode -> withPathContents $ start mode] + +start :: DuplicateMode -> (FilePath, FilePath) -> CommandStart +start mode (srcfile, destfile) = ifM (liftIO $ isRegularFile <$> getSymbolicLinkStatus srcfile) ( do showStart "import" destfile - next $ perform srcfile destfile + next $ perform mode srcfile destfile , stop ) -perform :: FilePath -> FilePath -> CommandPerform -perform srcfile destfile = do - whenM (liftIO $ doesFileExist destfile) $ - unlessM (Annex.getState Annex.force) $ - error $ "not overwriting existing " ++ destfile ++ - " (use --force to override)" - - liftIO $ createDirectoryIfMissing True (parentDir destfile) - liftIO $ moveFile srcfile destfile - Command.Add.perform destfile +perform :: DuplicateMode -> FilePath -> FilePath -> CommandPerform +perform mode srcfile destfile = + case mode of + DeDuplicate -> ifM isdup + ( deletedup + , go + ) + CleanDuplicates -> ifM isdup + ( deletedup + , next $ return True + ) + _ -> go + where + isdup = do + backend <- chooseBackend destfile + let ks = KeySource srcfile srcfile Nothing + v <- genKey ks backend + case v of + Just (k, _) -> not . null <$> keyLocations k + _ -> return False + deletedup = do + showNote "duplicate" + liftIO $ removeFile srcfile + next $ return True + go = do + whenM (liftIO $ doesFileExist destfile) $ + unlessM (Annex.getState Annex.force) $ + error $ "not overwriting existing " ++ destfile ++ + " (use --force to override)" + + liftIO $ createDirectoryIfMissing True (parentDir destfile) + liftIO $ if mode == Duplicate + then void $ copyFileExternal srcfile destfile + else moveFile srcfile destfile + Command.Add.perform destfile diff --git a/Command/ImportFeed.hs b/Command/ImportFeed.hs index 5ad5686479..816865e8c6 100644 --- a/Command/ImportFeed.hs +++ b/Command/ImportFeed.hs @@ -12,7 +12,6 @@ import Text.Feed.Query import Text.Feed.Types import qualified Data.Set as S import qualified Data.Map as M -import Data.Char import Data.Time.Clock import Common.Annex @@ -172,20 +171,15 @@ feedFile tmpl i = Utility.Format.format tmpl $ M.fromList , fieldMaybe "itemdescription" $ getItemDescription $ item i , fieldMaybe "itemrights" $ getItemRights $ item i , fieldMaybe "itemid" $ snd <$> getItemId (item i) - , ("extension", map sanitize $ takeExtension $ location i) + , ("extension", sanitizeFilePath $ takeExtension $ location i) ] where field k v = - let s = map sanitize v in + let s = sanitizeFilePath v in if null s then (k, "none") else (k, s) fieldMaybe k Nothing = (k, "none") fieldMaybe k (Just v) = field k v - sanitize c - | c == '.' = c - | isSpace c || isPunctuation c || c == '/' = '_' - | otherwise = c - {- Called when there is a problem with a feed. - Throws an error if the feed is broken, otherwise shows a warning. -} feedProblem :: URLString -> String -> Annex () diff --git a/Command/Mirror.hs b/Command/Mirror.hs new file mode 100644 index 0000000000..c0dd8a51fd --- /dev/null +++ b/Command/Mirror.hs @@ -0,0 +1,58 @@ +{- git-annex command + - + - Copyright 2013 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Command.Mirror where + +import Common.Annex +import Command +import GitAnnex.Options +import qualified Command.Move +import qualified Command.Drop +import qualified Command.Get +import qualified Remote +import Annex.Content +import qualified Annex + +def :: [Command] +def = [withOptions fromToOptions $ command "mirror" paramPaths seek + SectionCommon "mirror content of files to/from another repository"] + +seek :: [CommandSeek] +seek = + [ withField toOption Remote.byNameWithUUID $ \to -> + withField fromOption Remote.byNameWithUUID $ \from -> + withFilesInGit $ whenAnnexed $ start to from + ] + +start :: Maybe Remote -> Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart +start to from file (key, _backend) = do + noAuto + case (from, to) of + (Nothing, Nothing) -> error "specify either --from or --to" + (Nothing, Just r) -> mirrorto r + (Just r, Nothing) -> mirrorfrom r + _ -> error "only one of --from or --to can be specified" + where + noAuto = whenM (Annex.getState Annex.auto) $ + error "--auto is not supported for mirror" + mirrorto r = ifM (inAnnex key) + ( Command.Move.toStart r False (Just file) key + , do + numcopies <- numCopies file + Command.Drop.startRemote file numcopies key r + ) + mirrorfrom r = do + haskey <- Remote.hasKey r key + case haskey of + Left _ -> stop + Right True -> Command.Get.start' (return True) Nothing key (Just file) + Right False -> ifM (inAnnex key) + ( do + numcopies <- numCopies file + Command.Drop.startLocal file numcopies key Nothing + , stop + ) diff --git a/Command/Move.hs b/Command/Move.hs index 357ccc21ea..ea8cd7163f 100644 --- a/Command/Move.hs +++ b/Command/Move.hs @@ -14,7 +14,6 @@ import qualified Annex import Annex.Content import qualified Remote import Annex.UUID -import qualified Option import Logs.Presence import Logs.Transfer import GitAnnex.Options @@ -24,14 +23,8 @@ def :: [Command] def = [withOptions moveOptions $ command "move" paramPaths seek SectionCommon "move content of files to/from another repository"] -fromOption :: Option -fromOption = Option.field ['f'] "from" paramRemote "source remote" - -toOption :: Option -toOption = Option.field ['t'] "to" paramRemote "destination remote" - moveOptions :: [Option] -moveOptions = [fromOption, toOption] ++ keyOptions +moveOptions = fromToOptions ++ keyOptions seek :: [CommandSeek] seek = @@ -54,7 +47,7 @@ start' to from move afile key = do (Nothing, Nothing) -> error "specify either --from or --to" (Nothing, Just dest) -> toStart dest move afile key (Just src, Nothing) -> fromStart src move afile key - (_ , _) -> error "only one of --from or --to can be specified" + _ -> error "only one of --from or --to can be specified" where noAuto = when move $ whenM (Annex.getState Annex.auto) $ error "--auto is not supported for move" diff --git a/Command/PreCommit.hs b/Command/PreCommit.hs index 565344d257..c6d9dd278a 100644 --- a/Command/PreCommit.hs +++ b/Command/PreCommit.hs @@ -12,6 +12,7 @@ import Command import qualified Command.Add import qualified Command.Fix import qualified Git.DiffTree +import qualified Git.Ref import Annex.CatFile import Annex.Content.Direct import Git.Sha @@ -38,7 +39,7 @@ startIndirect file = next $ do startDirect :: [String] -> CommandStart startDirect _ = next $ do - (diffs, clean) <- inRepo $ Git.DiffTree.diffIndex + (diffs, clean) <- inRepo $ Git.DiffTree.diffIndex Git.Ref.headRef forM_ diffs go next $ liftIO clean where diff --git a/Command/Sync.hs b/Command/Sync.hs index a6ae610f84..551c2fa694 100644 --- a/Command/Sync.hs +++ b/Command/Sync.hs @@ -101,10 +101,13 @@ mergeLocal :: Git.Ref -> CommandStart mergeLocal branch = go =<< needmerge where syncbranch = syncBranch branch - needmerge = do - unlessM (inRepo $ Git.Ref.exists syncbranch) $ - inRepo $ updateBranch syncbranch - inRepo $ Git.Branch.changed branch syncbranch + needmerge = ifM isBareRepo + ( return False + , do + unlessM (inRepo $ Git.Ref.exists syncbranch) $ + inRepo $ updateBranch syncbranch + inRepo $ Git.Branch.changed branch syncbranch + ) go False = stop go True = do showStart "merge" $ Git.Ref.describe syncbranch diff --git a/Command/TransferKey.hs b/Command/TransferKey.hs index 849cbc12b3..3270ad8f79 100644 --- a/Command/TransferKey.hs +++ b/Command/TransferKey.hs @@ -15,23 +15,23 @@ import Logs.Location import Logs.Transfer import qualified Remote import Types.Remote -import qualified Command.Move +import GitAnnex.Options import qualified Option def :: [Command] -def = [withOptions options $ +def = [withOptions transferKeyOptions $ noCommit $ command "transferkey" paramKey seek SectionPlumbing "transfers a key from or to a remote"] -options :: [Option] -options = [fileOption, Command.Move.fromOption, Command.Move.toOption] +transferKeyOptions :: [Option] +transferKeyOptions = fileOption : fromToOptions fileOption :: Option fileOption = Option.field [] "file" paramFile "the associated file" seek :: [CommandSeek] -seek = [withField Command.Move.toOption Remote.byNameWithUUID $ \to -> - withField Command.Move.fromOption Remote.byNameWithUUID $ \from -> +seek = [withField toOption Remote.byNameWithUUID $ \to -> + withField fromOption Remote.byNameWithUUID $ \from -> withField fileOption return $ \file -> withKeys $ start to from file] diff --git a/Command/Unused.hs b/Command/Unused.hs index 0a060aae61..e6c8e225ca 100644 --- a/Command/Unused.hs +++ b/Command/Unused.hs @@ -21,15 +21,15 @@ import Common.Annex import Command import Logs.Unused import Annex.Content -import Utility.FileMode import Logs.Location import Logs.Transfer import qualified Annex import qualified Git import qualified Git.Command import qualified Git.Ref +import qualified Git.Branch import qualified Git.LsFiles as LsFiles -import qualified Git.LsTree as LsTree +import qualified Git.DiffTree as DiffTree import qualified Backend import qualified Remote import qualified Annex.Branch @@ -241,7 +241,7 @@ withKeysReferenced' mdir initial a = do ( return ([], return True) , do top <- fromRepo Git.repoPath - inRepo $ LsFiles.inRepo [top] + inRepo $ LsFiles.allFiles [top] ) Just dir -> inRepo $ LsFiles.inRepo [dir] go v [] = return v @@ -255,35 +255,48 @@ withKeysReferenced' mdir initial a = do withKeysReferencedInGit :: (Key -> Annex ()) -> Annex () withKeysReferencedInGit a = do - rs <- relevantrefs <$> showref - forM_ rs (withKeysReferencedInGitRef a) + current <- inRepo Git.Branch.currentUnsafe + shaHead <- maybe (return Nothing) (inRepo . Git.Ref.sha) current + showref >>= mapM_ (withKeysReferencedInGitRef a) . + relevantrefs (shaHead, current) where showref = inRepo $ Git.Command.pipeReadStrict [Param "show-ref"] - relevantrefs = map (Git.Ref . snd) . - nubBy uniqref . + relevantrefs headRef = addHead headRef . filter ourbranches . - map (separate (== ' ')) . lines - uniqref (x, _) (y, _) = x == y + map (separate (== ' ')) . + lines + nubRefs = map (Git.Ref . snd) . nubBy (\(x, _) (y, _) -> x == y) ourbranchend = '/' : show Annex.Branch.name ourbranches (_, b) = not (ourbranchend `isSuffixOf` b) && not ("refs/synced/" `isPrefixOf` b) + addHead headRef refs = case headRef of + -- if HEAD diverges from all branches (except the branch it + -- points to), run the actions on staged keys (and keys + -- that are only present in the work tree if the repo is + -- non bare) + (Just (Git.Ref x), Just (Git.Ref b)) + | all (\(x',b') -> x /= x' || b == b') refs -> + Git.Ref.headRef + : nubRefs (filter ((/= x) . fst) refs) + _ -> nubRefs refs +{- Runs an action on keys referenced in the given Git reference which + - differ from those referenced in the index. -} withKeysReferencedInGitRef :: (Key -> Annex ()) -> Git.Ref -> Annex () withKeysReferencedInGitRef a ref = do showAction $ "checking " ++ Git.Ref.describe ref - go <=< inRepo $ LsTree.lsTree ref + bare <- isBareRepo + (ts,clean) <- inRepo $ if bare + then DiffTree.diffIndex ref + else DiffTree.diffWorkTree ref + let lookAtWorkingTree = not bare && ref == Git.Ref.headRef + forM_ ts $ tKey lookAtWorkingTree >=> maybe noop a + liftIO $ void clean where - go [] = noop - go (l:ls) - | isSymLink (LsTree.mode l) = do - content <- encodeW8 . L.unpack - <$> catFile ref (LsTree.file l) - case fileKey (takeFileName content) of - Nothing -> go ls - Just k -> do - a k - go ls - | otherwise = go ls + tKey True = Backend.lookupFile . DiffTree.file >=*> + fmap fst + tKey False = catFile ref . DiffTree.file >=*> + fileKey . takeFileName . encodeW8 . L.unpack {- Looks in the specified directory for bad/tmp keys, and returns a list - of those that might still have value, or might be stale and removable. diff --git a/Config.hs b/Config.hs index 4d93a2af51..c37481ead9 100644 --- a/Config.hs +++ b/Config.hs @@ -18,6 +18,9 @@ import Config.Cost type UnqualifiedConfigKey = String data ConfigKey = ConfigKey String +instance Show ConfigKey where + show (ConfigKey s) = s + {- Looks up a setting in git config. -} getConfig :: ConfigKey -> String -> Annex String getConfig (ConfigKey key) def = fromRepo $ Git.Config.get key def diff --git a/Git/Construct.hs b/Git/Construct.hs index 586fa8c03c..35c77e9d2a 100644 --- a/Git/Construct.hs +++ b/Git/Construct.hs @@ -91,7 +91,7 @@ fromUrl url fromUrlStrict :: String -> IO Repo fromUrlStrict url - | startswith "file://" url = fromAbsPath $ uriPath u + | startswith "file://" url = fromAbsPath $ unEscapeString $ uriPath u | otherwise = newFrom $ Url u where u = fromMaybe bad $ parseURI url diff --git a/Git/DiffTree.hs b/Git/DiffTree.hs index cf8a376008..62330612cf 100644 --- a/Git/DiffTree.hs +++ b/Git/DiffTree.hs @@ -10,6 +10,7 @@ module Git.DiffTree ( diffTree, diffTreeRecursive, diffIndex, + diffWorkTree, ) where import Numeric @@ -41,15 +42,26 @@ diffTreeRecursive :: Ref -> Ref -> Repo -> IO ([DiffTreeItem], IO Bool) diffTreeRecursive src dst = getdiff (Param "diff-tree") [Param "-r", Param (show src), Param (show dst)] -{- Diffs between the repository and index. Does nothing if there is not - - yet a commit in the repository. -} -diffIndex :: Repo -> IO ([DiffTreeItem], IO Bool) -diffIndex repo = do +{- Diffs between a tree and the index. Does nothing if there is not yet a + - commit in the repository. -} +diffIndex :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool) +diffIndex ref = diffIndex' ref [Param "--cached"] + +{- Diffs between a tree and the working tree. Does nothing if there is not + - yet a commit in the repository, of if the repository is bare. -} +diffWorkTree :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool) +diffWorkTree ref repo = + ifM (Git.Ref.headExists repo) + ( diffIndex' ref [] repo + , return ([], return True) + ) + +diffIndex' :: Ref -> [CommandParam] -> Repo -> IO ([DiffTreeItem], IO Bool) +diffIndex' ref params repo = ifM (Git.Ref.headExists repo) ( getdiff (Param "diff-index") - [ Param "--cached" - , Param $ show Git.Ref.headRef - ] repo + ( params ++ [Param $ show ref] ) + repo , return ([], return True) ) diff --git a/Git/LsFiles.hs b/Git/LsFiles.hs index f4e4672158..e2e29ea36f 100644 --- a/Git/LsFiles.hs +++ b/Git/LsFiles.hs @@ -8,6 +8,7 @@ module Git.LsFiles ( inRepo, notInRepo, + allFiles, deleted, modified, staged, @@ -41,6 +42,11 @@ notInRepo include_ignored l repo = pipeNullSplit params repo | include_ignored = [] | otherwise = [Param "--exclude-standard"] +{- Finds all files in the specified locations, whether checked into git or + - not. -} +allFiles :: [FilePath] -> Repo -> IO ([FilePath], IO Bool) +allFiles l = pipeNullSplit $ Params "ls-files --cached --others -z --" : map File l + {- Returns a list of files in the specified locations that have been - deleted. -} deleted :: [FilePath] -> Repo -> IO ([FilePath], IO Bool) diff --git a/GitAnnex.hs b/GitAnnex.hs index 9553f22774..05565e643b 100644 --- a/GitAnnex.hs +++ b/GitAnnex.hs @@ -56,6 +56,7 @@ import qualified Command.Content import qualified Command.Ungroup import qualified Command.Vicfg import qualified Command.Sync +import qualified Command.Mirror import qualified Command.AddUrl #ifdef WITH_FEED import qualified Command.ImportFeed @@ -93,6 +94,7 @@ cmds = concat , Command.Unlock.def , Command.Lock.def , Command.Sync.def + , Command.Mirror.def , Command.AddUrl.def #ifdef WITH_FEED , Command.ImportFeed.def diff --git a/GitAnnex/Options.hs b/GitAnnex/Options.hs index 2cfdfafd2c..459ee3bf44 100644 --- a/GitAnnex/Options.hs +++ b/GitAnnex/Options.hs @@ -65,3 +65,12 @@ keyOptions = , Option ['U'] ["unused"] (NoArg (Annex.setFlag "unused")) "operate on files found by last run of git-annex unused" ] + +fromOption :: Option +fromOption = Option.field ['f'] "from" paramRemote "source remote" + +toOption :: Option +toOption = Option.field ['t'] "to" paramRemote "destination remote" + +fromToOptions :: [Option] +fromToOptions = [fromOption, toOption] diff --git a/Logs/Web.hs b/Logs/Web.hs index cbce7a36e7..47ab61943d 100644 --- a/Logs/Web.hs +++ b/Logs/Web.hs @@ -13,7 +13,10 @@ module Logs.Web ( setUrlMissing, urlLog, urlLogKey, - knownUrls + knownUrls, + Downloader(..), + getDownloader, + setDownloader, ) where import qualified Data.ByteString.Lazy.Char8 as L @@ -101,3 +104,19 @@ knownUrls = do where geturls Nothing = return [] geturls (Just logsha) = getLog . L.unpack <$> catObject logsha + +data Downloader = DefaultDownloader | QuviDownloader + +{- Determines the downloader for an URL. + - + - Some URLs are not downloaded by normal means, and this is indicated + - by prefixing them with downloader: when they are recorded in the url + - logs. -} +getDownloader :: URLString -> (URLString, Downloader) +getDownloader u = case separate (== ':') u of + ("quvi", u') -> (u', QuviDownloader) + _ -> (u, DefaultDownloader) + +setDownloader :: URLString -> Downloader -> URLString +setDownloader u DefaultDownloader = u +setDownloader u QuviDownloader = "quvi:" ++ u diff --git a/Remote.hs b/Remote.hs index ea93172825..5dec6f3e54 100644 --- a/Remote.hs +++ b/Remote.hs @@ -55,6 +55,7 @@ import Logs.UUID import Logs.Trust import Logs.Location hiding (logStatus) import Remote.List +import Config {- Map from UUIDs of Remotes to a calculated value. -} remoteMap :: (Remote -> a) -> Annex (M.Map UUID a) @@ -81,13 +82,16 @@ byName (Just n) = either error Just <$> byName' n {- Like byName, but the remote must have a configured UUID. -} byNameWithUUID :: Maybe String -> Annex (Maybe Remote) -byNameWithUUID n = do - v <- byName n - return $ checkuuid <$> v +byNameWithUUID = checkuuid <=< byName where - checkuuid r - | uuid r == NoUUID = error $ "cannot determine uuid for " ++ name r - | otherwise = r + checkuuid Nothing = return Nothing + checkuuid (Just r) + | uuid r == NoUUID = do + let e = "cannot determine uuid for " ++ name r + if remoteAnnexIgnore (gitconfig r) + then error $ e ++ " (" ++ show (remoteConfig (repo r) "ignore") ++ " is set)" + else error e + | otherwise = return $ Just r byName' :: String -> Annex (Either String Remote) byName' "" = return $ Left "no remote specified" diff --git a/Remote/Web.hs b/Remote/Web.hs index 2c59528ef9..42ae032e92 100644 --- a/Remote/Web.hs +++ b/Remote/Web.hs @@ -15,9 +15,11 @@ import Annex.Content import Config import Config.Cost import Logs.Web -import qualified Utility.Url as Url import Types.Key import Utility.Metered +import qualified Utility.Url as Url +import Annex.Quvi +import qualified Utility.Quvi as Quvi import qualified Data.Map as M @@ -67,7 +69,12 @@ downloadKey key _file dest _p = get =<< getUrls key return False get urls = do showOutput -- make way for download progress bar - downloadUrl urls dest + untilTrue urls $ \u -> do + let (u', downloader) = getDownloader u + case downloader of + QuviDownloader -> flip downloadUrl dest + =<< withQuviOptions Quvi.queryLinks [Quvi.httponly, Quvi.quiet] u' + DefaultDownloader -> downloadUrl [u'] dest downloadKeyCheap :: Key -> FilePath -> Annex Bool downloadKeyCheap _ _ = return False @@ -90,6 +97,11 @@ checkKey key = do else return . Right =<< checkKey' key us checkKey' :: Key -> [URLString] -> Annex Bool checkKey' key us = untilTrue us $ \u -> do - showAction $ "checking " ++ u - headers <- getHttpHeaders - liftIO $ Url.check u headers (keySize key) + let (u', downloader) = getDownloader u + showAction $ "checking " ++ u' + case downloader of + QuviDownloader -> + withQuviOptions Quvi.check [Quvi.httponly, Quvi.quiet] u' + DefaultDownloader -> do + headers <- getHttpHeaders + liftIO $ Url.check u' headers (keySize key) diff --git a/Seek.hs b/Seek.hs index 817687b453..b0a6345641 100644 --- a/Seek.hs +++ b/Seek.hs @@ -26,6 +26,7 @@ import qualified Option import Config import Logs.Location import Logs.Unused +import Annex.CatFile seekHelper :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> [FilePath] -> Annex [FilePath] seekHelper a params = do @@ -86,12 +87,16 @@ withFilesUnlocked = withFilesUnlocked' LsFiles.typeChanged withFilesUnlockedToBeCommitted :: (FilePath -> CommandStart) -> CommandSeek withFilesUnlockedToBeCommitted = withFilesUnlocked' LsFiles.typeChangedStaged +{- Unlocked files have changed type from a symlink to a regular file. + - + - Furthermore, unlocked files used to be a git-annex symlink, + - not some other sort of symlink. + -} withFilesUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (FilePath -> CommandStart) -> CommandSeek -withFilesUnlocked' typechanged a params = do - -- unlocked files have changed type from a symlink to a regular file - typechangedfiles <- seekHelper typechanged params - let unlockedfiles = liftIO $ filterM notSymlink typechangedfiles - prepFiltered a unlockedfiles +withFilesUnlocked' typechanged a params = prepFiltered a unlockedfiles + where + check f = liftIO (notSymlink f) <&&> isJust <$> catKeyFileHEAD f + unlockedfiles = filterM check =<< seekHelper typechanged params {- Finds files that may be modified. -} withFilesMaybeModified :: (FilePath -> CommandStart) -> CommandSeek diff --git a/Test.hs b/Test.hs index ef3f4e9753..3eb330c226 100644 --- a/Test.hs +++ b/Test.hs @@ -587,6 +587,37 @@ test_unused env = "git-annex unused/dropunused" ~: intmpclonerepoInDirect env $ checkunused [] "after dropunused" not <$> git_annex env "dropunused" ["--force", "10", "501"] @? "dropunused failed to fail on bogus numbers" + -- unused used to miss symlinks that were not staged and pointed + -- at annexed content, and think that content was unused + writeFile "unusedfile" "unusedcontent" + git_annex env "add" ["unusedfile"] @? "add of unusedfile failed" + unusedfilekey <- annexeval $ findkey "unusedfile" + renameFile "unusedfile" "unusedunstagedfile" + boolSystem "git" [Params "rm -qf", File "unusedfile"] @? "git rm failed" + checkunused [] "with unstaged link" + removeFile "unusedunstagedfile" + checkunused [unusedfilekey] "with unstaged link deleted" + + -- unused used to miss symlinks that were deleted or modified + -- manually, but commited as such. + writeFile "unusedfile" "unusedcontent" + git_annex env "add" ["unusedfile"] @? "add of unusedfile failed" + boolSystem "git" [Param "add", File "unusedfile"] @? "git add failed" + unusedfilekey' <- annexeval $ findkey "unusedfile" + checkunused [] "with staged deleted link" + boolSystem "git" [Params "rm -qf", File "unusedfile"] @? "git rm failed" + checkunused [unusedfilekey'] "with staged link deleted" + + -- unused used to miss symlinks that were deleted or modified + -- manually, but not staged as such. + writeFile "unusedfile" "unusedcontent" + git_annex env "add" ["unusedfile"] @? "add of unusedfile failed" + boolSystem "git" [Param "add", File "unusedfile"] @? "git add failed" + unusedfilekey'' <- annexeval $ findkey "unusedfile" + checkunused [] "with unstaged deleted link" + removeFile "unusedfile" + checkunused [unusedfilekey''] "with unstaged link deleted" + where checkunused expectedkeys desc = do git_annex env "unused" [] @? "unused failed" diff --git a/Types/GitConfig.hs b/Types/GitConfig.hs index d5d234ca93..4f2e913319 100644 --- a/Types/GitConfig.hs +++ b/Types/GitConfig.hs @@ -37,6 +37,7 @@ data GitConfig = GitConfig , annexAutoCommit :: Bool , annexDebug :: Bool , annexWebOptions :: [String] + , annexQuviOptions :: [String] , annexWebDownloadCommand :: Maybe String , annexCrippledFileSystem :: Bool , annexLargeFiles :: Maybe String @@ -62,6 +63,7 @@ extractGitConfig r = GitConfig , annexAutoCommit = getbool (annex "autocommit") True , annexDebug = getbool (annex "debug") False , annexWebOptions = getwords (annex "web-options") + , annexQuviOptions = getwords (annex "quvi-options") , annexWebDownloadCommand = getmaybe (annex "web-download-command") , annexCrippledFileSystem = getbool (annex "crippledfilesystem") False , annexLargeFiles = getmaybe (annex "largefiles") diff --git a/Utility/Monad.hs b/Utility/Monad.hs index b66419f76a..4f5a6d2449 100644 --- a/Utility/Monad.hs +++ b/Utility/Monad.hs @@ -8,7 +8,7 @@ module Utility.Monad where import Data.Maybe -import Control.Monad (liftM) +import Control.Monad {- Return the first value from a list, if any, satisfying the given - predicate -} @@ -53,6 +53,16 @@ ma <&&> mb = ifM ma ( mb , return False ) infixr 3 <&&> infixr 2 <||> +{- Left-to-right Kleisli composition with a pure left/right hand side. -} +(*>=>) :: Monad m => (a -> b) -> (b -> m c) -> (a -> m c) +f *>=> g = return . f >=> g + +(>=*>) :: Monad m => (a -> m b) -> (b -> c) -> (a -> m c) +f >=*> g = f >=> return . g + +{- Same fixity as >=> and <=< -} +infixr 1 *>=>, >=*> + {- Runs an action, passing its value to an observer before returning it. -} observe :: Monad m => (a -> m b) -> m a -> m a observe observer a = do diff --git a/Utility/Path.hs b/Utility/Path.hs index 79e8e80895..b6214b2478 100644 --- a/Utility/Path.hs +++ b/Utility/Path.hs @@ -14,6 +14,7 @@ import System.FilePath import System.Directory import Data.List import Data.Maybe +import Data.Char import Control.Applicative #ifdef mingw32_HOST_OS @@ -236,3 +237,18 @@ fileNameLengthLimit dir = do else return $ minimum [l, 255] where #endif + +{- Given a string that we'd like to use as the basis for FilePath, but that + - was provided by a third party and is not to be trusted, returns the closest + - sane FilePath. + - + - All spaces and punctuation are replaced with '_', except for '.' + - "../" will thus turn into ".._", which is safe. + -} +sanitizeFilePath :: String -> FilePath +sanitizeFilePath = map sanitize + where + sanitize c + | c == '.' = c + | isSpace c || isPunctuation c || c == '/' = '_' + | otherwise = c diff --git a/Utility/Quvi.hs b/Utility/Quvi.hs new file mode 100644 index 0000000000..5df1a4da72 --- /dev/null +++ b/Utility/Quvi.hs @@ -0,0 +1,81 @@ +{- querying quvi (import qualified) + - + - Copyright 2013 Joey Hess + - + - Licensed under the GNU GPL version 3 or higher. + -} + +{-# LANGUAGE OverloadedStrings #-} + +module Utility.Quvi where + +import Common +import Utility.Url + +import Data.Aeson +import Data.ByteString.Lazy.UTF8 (fromString) + +data Page = Page + { pageTitle :: String + , pageLinks :: [Link] + } deriving (Show) + +data Link = Link + { linkSuffix :: String + , linkUrl :: URLString + } deriving (Show) + +instance FromJSON Page where + parseJSON (Object v) = Page + <$> v .: "page_title" + <*> v .: "link" + parseJSON _ = mzero + +instance FromJSON Link where + parseJSON (Object v) = Link + <$> v .: "file_suffix" + <*> v .: "url" + parseJSON _ = mzero + +type Query a = [CommandParam] -> URLString -> IO a + +{- Throws an error when quvi is not installed. -} +forceQuery :: Query (Maybe Page) +forceQuery ps url = query' ps url `catchNonAsync` onerr + where + onerr _ = ifM (inPath "quvi") + ( error "quvi failed" + , error "quvi is not installed" + ) + +{- Returns Nothing if the page is not a video page, or quvi is not + - installed. -} +query :: Query (Maybe Page) +query ps url = flip catchNonAsync (const $ return Nothing) (query' ps url) + +query' :: Query (Maybe Page) +query' ps url = decode . fromString + <$> readProcess "quvi" (toCommand $ ps ++ [Param url]) + +queryLinks :: Query [URLString] +queryLinks ps url = maybe [] (map linkUrl . pageLinks) <$> query ps url + +{- Checks if quvi can still find a download link for an url. + - If quvi is not installed, returns False. -} +check :: Query Bool +check ps url = maybe False (not . null . pageLinks) <$> query ps url + +{- Checks if an url is supported by quvi, without hitting it, or outputting + - anything. Also returns False if quvi is not installed. -} +supported :: URLString -> IO Bool +supported url = boolSystem "quvi" [Params "-v mute --support", Param url] + +quiet :: CommandParam +quiet = Params "-v quiet" + +noredir :: CommandParam +noredir = Params "-e -resolve" + +{- Only return http results, not streaming protocols. -} +httponly :: CommandParam +httponly = Params "-c http" diff --git a/Utility/Url.hs b/Utility/Url.hs index 508b9eeb44..2f2ec1dc06 100644 --- a/Utility/Url.hs +++ b/Utility/Url.hs @@ -110,7 +110,7 @@ download' quiet url headers options file = _ -> return False where headerparams = map (\h -> Param $ "--header=" ++ h) headers - wget = go "wget" $ headerparams ++ quietopt "-q" ++ [Params "-c -O"] + wget = go "wget" $ headerparams ++ quietopt "-q" ++ [Params "--clobber -c -O"] {- Uses the -# progress display, because the normal - one is very confusing when resuming, showing - the remainder to download as the whole file, diff --git a/debian/changelog b/debian/changelog index e72af40f47..0c6b65df55 100644 --- a/debian/changelog +++ b/debian/changelog @@ -1,3 +1,33 @@ +git-annex (4.20130827) unstable; urgency=low + + * Youtube support! (And 53 other video hosts). When quvi is installed, + git-annex addurl automatically uses it to detect when an page is + a video, and downloads the video file. + * web special remote: Also support using quvi, for getting files, + or checking if files exist in the web. + * unused: Is now a minimum of 30 times faster, and typically many + more times than that (when a repository has several branches). + (Thanks, guilhem for the patch.) + * unused: Fix bugs in two edge cases involving manually staged changes. + (Thanks, guilhem for the patch.) + * Android: Fix bug in terminal app that caused it to spin using much + CPU and battery. This problem was introduced in version 4.20130601. + * sync, merge: Bug fix: Don't try to merge into master when in a bare repo. + * import: Add options to control handling of duplicate files: + --duplicate, --deduplicate, and --clean-duplicates + * mirror: New command, makes two repositories contain the same set of files. + * Set --clobber when running wget to ensure resuming works properly. + * Unescape characters in 'file://...' URIs. (Thanks, guilhem for the patch.) + * Better error message when trying to use a git remote that has annex.ignore + set. + * Fix bug that caused typechanged symlinks to be assumed to be unlocked + files, so they were added to the annex by the pre-commit hook. + * Debian: Run the builtin test suite as an autopkgtest. + * Debian: Recommend ssh-askpass, which ssh will use when the assistant + is run w/o a tty. Closes: #719832 + + -- Joey Hess Tue, 27 Aug 2013 11:03:00 -0400 + git-annex (4.20130815~bpo70+1) wheezy-backports; urgency=low * assistant, watcher: .gitignore files and other git ignores are now diff --git a/debian/control b/debian/control index 69c8da2af3..8f3be64e68 100644 --- a/debian/control +++ b/debian/control @@ -20,6 +20,7 @@ Build-Depends: libghc-dlist-dev, libghc-uuid-dev, libghc-json-dev, + libghc-aeson-dev, libghc-ifelse-dev, libghc-bloomfilter-dev, libghc-edit-distance-dev, @@ -59,6 +60,7 @@ Maintainer: Joey Hess Standards-Version: 3.9.4 Vcs-Git: git://git.kitenet.net/git-annex Homepage: http://git-annex.branchable.com/ +XS-Testsuite: autopkgtest Package: git-annex Architecture: any @@ -69,7 +71,7 @@ Depends: ${misc:Depends}, ${shlibs:Depends}, wget, curl, openssh-client (>= 1:5.6p1) -Recommends: lsof, gnupg, bind9-host +Recommends: lsof, gnupg, bind9-host, ssh-askpass, quvi Suggests: graphviz, bup, libnss-mdns Description: manage files with git, without checking their contents into git git-annex allows managing files with git, without checking the file diff --git a/debian/tests/basics b/debian/tests/basics new file mode 100644 index 0000000000..2e4ea43fc1 --- /dev/null +++ b/debian/tests/basics @@ -0,0 +1,4 @@ +#!/bin/sh +testdir="$(mktemp -d)" +cd "$testdir" +exec git-annex test diff --git a/debian/tests/control b/debian/tests/control new file mode 100644 index 0000000000..928caf8e31 --- /dev/null +++ b/debian/tests/control @@ -0,0 +1,4 @@ +Tests: basics +Depends: @, git, rsync, gnupg +Restrictions: allow-stderr + diff --git a/doc/backends.mdwn b/doc/backends.mdwn index 4e9776ff00..9abe6eac03 100644 --- a/doc/backends.mdwn +++ b/doc/backends.mdwn @@ -14,7 +14,7 @@ can use different ones for different files. lead to better deduplication but can confuse some programs. * `WORM` ("Write Once, Read Many") This assumes that any file with the same basename, size, and modification time has the same content. - This is the the least expensive backend, recommended for really large + This is the least expensive backend, recommended for really large files or slow systems. * `SHA512`, `SHA512E` -- Best currently available hash, for the very paranoid. * `SHA1`, `SHA1E` -- Smaller hash than `SHA256` for those who want a checksum diff --git a/doc/bugs/400_mode_leakage.mdwn b/doc/bugs/400_mode_leakage.mdwn new file mode 100644 index 0000000000..e0228a18a5 --- /dev/null +++ b/doc/bugs/400_mode_leakage.mdwn @@ -0,0 +1,17 @@ +git-annex tends to preserve files that are added to an annex with +a mode such as 400. (Happens to me sometimes with email attachments.) +As these files are rsynced around, and end up on eg, a +publically visible repo with a webserver frontend, or a repo that is +acessible to a whole group of users, they will not be readable. + +I think it would make sense for git-annex to normalize file permissions +when adding them. Of course, there's some tension here with generally +storing file metadata when possible. Perhaps the normalization should only +ensure that group and other have read access? + +(Security: We can assume that a repo that is not intended to be public is +in a 700 directory. And since git-annex cannot preserve file modes when +files transit through a special remote, using modes to limit access to +individual files is not wise.) + +--[[Joey]] diff --git a/doc/bugs/Can__39__t_clone_on_Windows_because_some_filenames_have_a_colon_in_them/comment_3_f34d996827f5e7662bec409cbcce961b._comment b/doc/bugs/Can__39__t_clone_on_Windows_because_some_filenames_have_a_colon_in_them/comment_3_f34d996827f5e7662bec409cbcce961b._comment new file mode 100644 index 0000000000..14cfa2686e --- /dev/null +++ b/doc/bugs/Can__39__t_clone_on_Windows_because_some_filenames_have_a_colon_in_them/comment_3_f34d996827f5e7662bec409cbcce961b._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 3" + date="2013-08-24T19:27:57Z" + content=""" +Leonardo, you made me boot up my windows machine just to check if cygwin git truncated files at the colon. It does not. + +AFAIK, Cygwin transliterates colons to another unicode character or something like that. I would be highly surprised if the Cygwin people consider this feature to be a bug. + +Since you need Cygwin to build git-annex on Windows anyway (though not to run it!), this remains WONTFIX. +"""]] diff --git a/doc/bugs/Can__39__t_start_on_Cyanogenmod_10.2_nightly.mdwn b/doc/bugs/Can__39__t_start_on_Cyanogenmod_10.2_nightly.mdwn new file mode 100644 index 0000000000..c28794622a --- /dev/null +++ b/doc/bugs/Can__39__t_start_on_Cyanogenmod_10.2_nightly.mdwn @@ -0,0 +1,158 @@ +### Please describe the problem. +The android app won't start on Cyanogenmod 10.2. Not sure if this is cyanogenmod specific or if it is because the underlying android is now version 4.3 + +### What steps will reproduce the problem? +Install the apk and start the program + +### What version of git-annex are you using? On what operating system? +A 7 day old nightly as of this post(can't get specific number since it won't run) + +### Please provide any additional information below. + +Tested this on both a samsung galaxy S and a samsung galaxy note 2. With different nightlies of cyanogenmod 10.2 + +[[!format sh """ +# If you can, paste a complete transcript of the problem occurring here. +# If the problem is with the git-annex assistant, paste in .git/annex/daemon.log + +Falling back to hardcoded app location; cannot find expected files in /data/app-lib +git annex webapp +u0_a115@android:/sdcard/git-annex.home $ git annex webapp +CANNOT LINK EXECUTABLE: git-annex invalid R_ARM_COPY relocation against DT_SYMBOLIC shared library libc.so (built with -Bsymbolic?) +1|u0_a115@android:/sdcard/git-annex.home $ + +--- + + +cat git-annex-install.log + +Installation starting to /data/data/ga.androidterm +34c88243533e9b0a725ebe33533d990e628dc44b +installing busybox +installing git-annex +installing git-shell +installing git-upload-pack +installing git +installing gpg +installing rsync +installing ssh +installing ssh-keygen +linking ./libexec/git-core/git-config to git +linking ./libexec/git-core/git-fetch to git +linking ./libexec/git-core/git-fsck to git +linking ./libexec/git-core/git-unpack-file to git +linking ./libexec/git-core/git-get-tar-commit-id to git +linking ./libexec/git-core/git-fmt-merge-msg to git +linking ./libexec/git-core/git-push to git +linking ./libexec/git-core/git-for-each-ref to git +linking ./libexec/git-core/git-pack-redundant to git +linking ./libexec/git-core/git-mv to git +linking ./libexec/git-core/git-ls-remote to git +linking ./libexec/git-core/git-prune-packed to git +linking ./libexec/git-core/git-apply to git +linking ./libexec/git-core/git-check-ignore to git +linking ./libexec/git-core/git-log to git +linking ./libexec/git-core/git-cherry-pick to git +linking ./libexec/git-core/git-diff-files to git +linking ./libexec/git-core/git-commit-tree to git +linking ./libexec/git-core/git-index-pack to git +linking ./libexec/git-core/git-reflog to git +linking ./libexec/git-core/git-merge-index to git +linking ./libexec/git-core/git-column to git +linking ./libexec/git-core/git-checkout-index to git +linking ./libexec/git-core/git-diff-index to git +linking ./libexec/git-core/git-count-objects to git +linking ./libexec/git-core/git-fast-export to git +linking ./libexec/git-core/git-fetch-pack to git +linking ./libexec/git-core/git-merge-file to git +linking ./libexec/git-core/git-init to git +linking ./libexec/git-core/git-remote to git +linking ./libexec/git-core/git-init-db to git +linking ./libexec/git-core/git-ls-tree to git +linking ./libexec/git-core/git-merge-subtree to git +linking ./libexec/git-core/git-rev-parse to git +linking ./libexec/git-core/git-bundle to git +linking ./libexec/git-core/git-prune to git +linking ./libexec/git-core/git-peek-remote to git +linking ./libexec/git-core/git-tar-tree to git +linking ./libexec/git-core/git-describe to git +linking ./libexec/git-core/git-update-index to git +linking ./libexec/git-core/git to git +linking ./libexec/git-core/git-revert to git +linking ./libexec/git-core/git-show-ref to git +linking ./libexec/git-core/git-upload-archive to git +linking ./libexec/git-core/git-add to git +linking ./libexec/git-core/git-verify-tag to git +linking ./libexec/git-core/git-format-patch to git +linking ./libexec/git-core/git-show-branch to git +linking ./libexec/git-core/git-remote-fd to git +linking ./libexec/git-core/git-pack-refs to git +linking ./libexec/git-core/git-replace to git +linking ./libexec/git-core/git-pack-objects to git +linking ./libexec/git-core/git-notes to git +linking ./libexec/git-core/git-tag to git +linking ./libexec/git-core/git-var to git +linking ./libexec/git-core/git-help to git +linking ./libexec/git-core/git-gc to git +linking ./libexec/git-core/git-check-ref-format to git +linking ./libexec/git-core/git-shortlog to git +linking ./libexec/git-core/git-stage to git +linking ./libexec/git-core/git-mktree to git +linking ./libexec/git-core/git-merge-recursive to git +linking ./libexec/git-core/git-grep to git +linking ./libexec/git-core/git-clean to git +linking ./libexec/git-core/git-merge-base to git +linking ./libexec/git-core/git-repo-config to git +linking ./libexec/git-core/git-hash-object to git +linking ./libexec/git-core/git-read-tree to git +linking ./libexec/git-core/git-rm to git +linking ./libexec/git-core/git-fsck-objects to git +linking ./libexec/git-core/git-ls-files to git +linking ./libexec/git-core/git-mktag to git +linking ./libexec/git-core/git-stripspace to git +linking ./libexec/git-core/git-mailsplit to git +linking ./libexec/git-core/git-diff-tree to git +linking ./libexec/git-core/git-merge-ours to git +linking ./libexec/git-core/git-cherry to git +linking ./libexec/git-core/git-checkout to git +linking ./libexec/git-core/git-rev-list to git +linking ./libexec/git-core/git-write-tree to git +linking ./libexec/git-core/git-update-ref to git +linking ./libexec/git-core/git-blame to git +linking ./libexec/git-core/git-archive to git +linking ./libexec/git-core/git-update-server-info to git +linking ./libexec/git-core/git-merge-tree to git +linking ./libexec/git-core/git-show to git +linking ./libexec/git-core/git-remote-ext to git +linking ./libexec/git-core/git-merge to git +linking ./libexec/git-core/git-name-rev to git +linking ./libexec/git-core/git-bisect--helper to git +linking ./libexec/git-core/git-clone to git +linking ./libexec/git-core/git-symbolic-ref to git +linking ./libexec/git-core/git-send-pack to git +linking ./libexec/git-core/git-commit to git +linking ./libexec/git-core/git-mailinfo to git +linking ./libexec/git-core/git-credential to git +linking ./libexec/git-core/git-diff to git +linking ./libexec/git-core/git-patch-id to git +linking ./libexec/git-core/git-rerere to git +linking ./libexec/git-core/git-branch to git +linking ./libexec/git-core/git-reset to git +linking ./libexec/git-core/git-receive-pack to git +linking ./libexec/git-core/git-verify-pack to git +linking ./libexec/git-core/git-unpack-objects to git +linking ./libexec/git-core/git-check-attr to git +linking ./libexec/git-core/git-whatchanged to git +linking ./libexec/git-core/git-status to git +linking ./libexec/git-core/git-cat-file to git +linking ./libexec/git-core/git-annotate to git +linking ./bin/git-upload-archive to git +linking ./bin/git-receive-pack to git +linking ./libexec/git-core/git-shell to git-shell +linking ./libexec/git-core/git-upload-pack to git-upload-pack +Installation complete + +# End of transcript or log. +"""]] + +> [[dup|done]] of [[git-annex_broken_on_Android_4.3]].--[[Joey]] diff --git a/doc/bugs/Creating_second_repository_leads_to_wrong_ip___40__using_git-annex_webapp_--listen__41__.mdwn b/doc/bugs/Creating_second_repository_leads_to_wrong_ip___40__using_git-annex_webapp_--listen__41__.mdwn index 30ec9be3d3..28b74bd989 100644 --- a/doc/bugs/Creating_second_repository_leads_to_wrong_ip___40__using_git-annex_webapp_--listen__41__.mdwn +++ b/doc/bugs/Creating_second_repository_leads_to_wrong_ip___40__using_git-annex_webapp_--listen__41__.mdwn @@ -31,3 +31,5 @@ Linux nas 3.8.0-27-generic #40-Ubuntu SMP Tue Jul 9 00:19:35 UTC 2013 i686 i686 # End of transcript or log. """]] + +> This is a different effect of the same bug in [[Hangs on creating repository when using --listen]]. Closing as [[dup|done]] --[[Joey]] diff --git a/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_1_b3197993dbdfaf2db5e4651ac54a896e._comment b/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_1_b3197993dbdfaf2db5e4651ac54a896e._comment new file mode 100644 index 0000000000..8ff2321591 --- /dev/null +++ b/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_1_b3197993dbdfaf2db5e4651ac54a896e._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T18:49:18Z" + content=""" +git-annex assumes that it can make a stable symlink from a file in the working tree to a file in the .git directory. There are several ways to break this. One, as noted, is sometimes using a repository as a submodule, and sometimes not. Another would be to play around with `GIT_DIR`. + +I don't see a way git-annex can support those use cases, at least in indirect mode. + +It does seem like, in direct mode, it should just work. git-annex will commit various symlinks to git, but these symlinks will never be followed to get at the content of a file, since direct mode arranges for the content to be directly present in the working tree. +"""]] diff --git a/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_2_1fbbd02e61ef524597dafd69460b00b4._comment b/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_2_1fbbd02e61ef524597dafd69460b00b4._comment new file mode 100644 index 0000000000..b7aa61f176 --- /dev/null +++ b/doc/bugs/Git_annexed_files_symlink_are_wrong_when_submodule_is_not_in_the_same_path/comment_2_1fbbd02e61ef524597dafd69460b00b4._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="konubinix" + ip="82.243.233.186" + subject="Thanks" + date="2013-08-26T06:25:19Z" + content=""" +Thanks for the reply. + +Also thanks for this great tool (Though I am not sure I truelly realize the true power of git annex yet). +"""]] diff --git a/doc/bugs/Hangs_on_creating_repository_when_using_--listen/comment_2_dc128eeddeaaf3f84e71aca0fb7d341f._comment b/doc/bugs/Hangs_on_creating_repository_when_using_--listen/comment_2_dc128eeddeaaf3f84e71aca0fb7d341f._comment new file mode 100644 index 0000000000..55d7efa1ce --- /dev/null +++ b/doc/bugs/Hangs_on_creating_repository_when_using_--listen/comment_2_dc128eeddeaaf3f84e71aca0fb7d341f._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-24T18:52:11Z" + content=""" +This also affects creating a second repository in the webapp, not just the repository creation at first startup. +"""]] diff --git a/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex.mdwn b/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex.mdwn new file mode 100644 index 0000000000..8c13a88ac0 --- /dev/null +++ b/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex.mdwn @@ -0,0 +1,52 @@ +### Please describe the problem. + +(small) identical files fail to unannex, leaving broken symlinks, except for the first copy. + +### What steps will reproduce the problem? + +* Have multiple identical files. For example, run this, which creates four 6-byte files: + +> echo Hello>file1.txt && cp file1.txt file2.txt && cp file1.txt file3.txt && cp file1.txt file4.txt + +* Run this (git init needs credentials to have been specified though) + +> git init && git-annex init && git-annex add + +Now there are 4 symlinks, pointing to the same object: + +> lrwxrwxrwx 1 186 Aug 16 15:54 file1.txt -> .git/annex/objects/31/XV/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt + +* Optionally run "git commit -a". It doesn't affect the outcome. + +* Run git-annex unannex + +> $ git annex unannex +> unannex file1.txt ok +> (Recording state in git...) +> $ + +Now file1.txt is a normal 6-byte file again, but 2, 3, and 4 are broken symlinks: + + -rw-r----- 1 6 Aug 16 15:54 file1.txt + lrwxrwxrwx 1 186 Aug 16 15:54 file2.txt -> .git/annex/objects/31/XV/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt + lrwxrwxrwx 1 186 Aug 16 15:54 file3.txt -> .git/annex/objects/31/XV/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt + lrwxrwxrwx 1 186 Aug 16 15:54 file4.txt -> .git/annex/objects/31/XV/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt/SHA256E-s6--66a045b452102c59d840ec097d59d9467e13a3f34f6494e539ffd32c1bb35f18.txt + + $ git-annex fsck + fsck file2.txt + ** No known copies exist of file2.txt + failed + fsck file3.txt + ** No known copies exist of file3.txt + failed + fsck file4.txt + ** No known copies exist of file4.txt + failed + git-annex: fsck: 3 failed + + +### What version of git-annex are you using? On what operating system? + +git-annex 4.20130802 package + +on Debian GNU/Linux jessie/sid (testing), amd64. diff --git a/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex/comment_2_f7149b684a97070cff051b780c73be48._comment b/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex/comment_2_f7149b684a97070cff051b780c73be48._comment new file mode 100644 index 0000000000..ca3ad12290 --- /dev/null +++ b/doc/bugs/Of_identical_files__44___all_but_the_first_copy_are_lost_on_unannex/comment_2_f7149b684a97070cff051b780c73be48._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://openid.yandex.ru/deletesoftware/" + nickname="deletesoftware" + subject="duplicate" + date="2013-08-16T14:52:23Z" + content=""" +It's the same as these: + +* [Large unannex operations result in stale symlinks and data loss](http://git-annex.branchable.com/bugs/Large_unannex_operations_result_in_stale_symlinks_and_data_loss/) +* [unannex removes object even if referred to by others](http://git-annex.branchable.com/bugs/unannex_removes_object_even_if_referred_to_by_others/) +* [annex unannex/uninit should handle copies](http://git-annex.branchable.com/bugs/annex_unannex__47__uninit_should_handle_copies/) + +and (as gernot mentioned) according to those, has a workaround of \"git annex unannex --fast\". Of course, it's not convenient to need to find a workaround, and to notice a potential dataloss issue… + +"""]] diff --git a/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple.mdwn b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple.mdwn index 96d73f0f48..46ae06f6de 100644 --- a/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple.mdwn +++ b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple.mdwn @@ -59,4 +59,6 @@ My .gitconfig is as follows: """]] > Closing this because all autobuilders have been upgraded -> to a more recent version of git. [[done]] --[[Joey]] +> to a more recent version of git. done --[[Joey]] +>> Reopened, because the Linux autobuilds have been downgraded to Debian +>> stable and have this problem again. --[[Joey]] diff --git a/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_3_eaed9b5532e30e401f50193a72b98310._comment b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_3_eaed9b5532e30e401f50193a72b98310._comment new file mode 100644 index 0000000000..bee277aa64 --- /dev/null +++ b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_3_eaed9b5532e30e401f50193a72b98310._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmTNrhkVQ26GBLaLD5-zNuEiR8syTj4mI8" + nickname="Juan" + subject="Still happening in the linux autobuild (08/22/2013)" + date="2013-08-23T02:04:42Z" + content=""" +I've seen that git-annex for linux is still coming with git 1.7, which causes problems with my installed git (1.8.1.2). +Wasn't that corrected in autobuilds? +Thanks in advance. +Keep up the good work. +Regards, + Juan +"""]] diff --git a/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_4_1fab407f3823ce8cec87f5df55e49f8c._comment b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_4_1fab407f3823ce8cec87f5df55e49f8c._comment new file mode 100644 index 0000000000..2c9c33c8e7 --- /dev/null +++ b/doc/bugs/Older_version_of_git_causes_Internal_Server_Error_when_push.default___61___simple/comment_4_1fab407f3823ce8cec87f5df55e49f8c._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 4" + date="2013-08-23T17:41:32Z" + content=""" +It was done for the autobuilds, but then I switched them to build using Debian stable, which still has git 1.7, and there is not currently a backport of a newer git to stable for me to use. +"""]] diff --git a/doc/bugs/Problem_when_dropping_unused_files.mdwn b/doc/bugs/Problem_when_dropping_unused_files.mdwn new file mode 100644 index 0000000000..853ab3c3c5 --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files.mdwn @@ -0,0 +1,17 @@ +### Please describe the problem. + +While dropping 19 unused files from an annex, I got this error: + + error: invalid object 100644 c873416e78db4dd94b6ab40470d6fe99b2ecb8bd for '002/0a6/SHA256E-s427690--03aeabcde841b66168b72de80098d74e047f3ffc832d4bbefa1f2f70ee6c92f8.jpg.log' + fatal: git-write-tree: error building trees + git-annex: failed to read sha from git write-tree + +I've actually seen this before, a few months ago. + +### What steps will reproduce the problem? + +I have no idea, but once it happens I can't interact with unused files anymore. Also, `git annex fsck` now reports this same problem as well. + +### What version of git-annex are you using? On what operating system? + +git-annex version: 4.20130815, OS X 10.8.4 diff --git a/doc/bugs/Problem_when_dropping_unused_files/comment_1_e1a99bd3eb8b3186653b52a52b1836de._comment b/doc/bugs/Problem_when_dropping_unused_files/comment_1_e1a99bd3eb8b3186653b52a52b1836de._comment new file mode 100644 index 0000000000..0e39a96fcc --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files/comment_1_e1a99bd3eb8b3186653b52a52b1836de._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89" + nickname="John" + subject="comment 1" + date="2013-08-24T05:01:37Z" + content=""" +The following command restored some sanity: + + find .git/annex/ -name '*.log' -delete +"""]] diff --git a/doc/bugs/Problem_when_dropping_unused_files/comment_2_dec3e5ffe5cfdc439f418ee00d7d9810._comment b/doc/bugs/Problem_when_dropping_unused_files/comment_2_dec3e5ffe5cfdc439f418ee00d7d9810._comment new file mode 100644 index 0000000000..e0c5a28822 --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files/comment_2_dec3e5ffe5cfdc439f418ee00d7d9810._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="arand" + ip="130.243.226.21" + subject="comment 2" + date="2013-08-24T11:40:54Z" + content=""" +If I recall, such files being stored in the annex object store is a result of using direct mode? +"""]] diff --git a/doc/bugs/Problem_when_dropping_unused_files/comment_3_d106a87101db52f957da84d90dafcdbb._comment b/doc/bugs/Problem_when_dropping_unused_files/comment_3_d106a87101db52f957da84d90dafcdbb._comment new file mode 100644 index 0000000000..8c739552da --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files/comment_3_d106a87101db52f957da84d90dafcdbb._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 3" + date="2013-08-24T16:04:21Z" + content=""" +Unfortunately, the git error message you pasted suggests very strongly that your git repository has gotten corrupted. You can probably verify that by running `git annex fsck`. Assuming it is corrupted, the best thing to do is to make a new clone and move .git/annex and .git/config over from the corrupted repository to it, and finally run `git annex fsck` + +You then seem to have some reason decided to go delete git-annex's .git/annex/journal/*.log files, which are just files that have not yet been committed to the git-annex branch. The only reason this \"restored some sanity\" is that git-annex was trying to commit that data to git, and failing because your git repository is corrupted. + +(This has nothing at all to do with direct mode.) +"""]] diff --git a/doc/bugs/Problem_when_dropping_unused_files/comment_4_f28ed0635612693e437e64d872af5c37._comment b/doc/bugs/Problem_when_dropping_unused_files/comment_4_f28ed0635612693e437e64d872af5c37._comment new file mode 100644 index 0000000000..ba2e693eeb --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files/comment_4_f28ed0635612693e437e64d872af5c37._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89" + nickname="John" + subject="comment 4" + date="2013-08-25T05:27:57Z" + content=""" +Do you have any thoughts on why it may have gotten corrupted, or why it seems to happen so commonly with large git-annex repositories? I've seen this exact same sort of error while processing log files maybe 5 or 6 times now. +"""]] diff --git a/doc/bugs/Problem_when_dropping_unused_files/comment_5_f0237075653768c84deb702442645f28._comment b/doc/bugs/Problem_when_dropping_unused_files/comment_5_f0237075653768c84deb702442645f28._comment new file mode 100644 index 0000000000..4ad874c082 --- /dev/null +++ b/doc/bugs/Problem_when_dropping_unused_files/comment_5_f0237075653768c84deb702442645f28._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89" + nickname="John" + subject="comment 5" + date="2013-08-25T05:50:35Z" + content=""" +I meant to say, in 5 or 6 different repositories. Further, when I see it happen the next time, how do you recommend I track down the real problem, instead of always just cloning and starting over? +"""]] diff --git a/doc/bugs/Resource_exhausted.mdwn b/doc/bugs/Resource_exhausted.mdwn index eae2ba8d3c..3f125b08aa 100644 --- a/doc/bugs/Resource_exhausted.mdwn +++ b/doc/bugs/Resource_exhausted.mdwn @@ -41,5 +41,5 @@ I'm interested in your thoughts. Best, Laszlo -[[!tag /design/assistant moreinfo]] +[[!tag /design/assistant]] [[!meta title="assistant can try to add too many files at once in batch add mode"]] diff --git a/doc/bugs/Resource_exhausted/comment_10_bccf9528ffe963154c92ce49762e7ea6._comment b/doc/bugs/Resource_exhausted/comment_10_bccf9528ffe963154c92ce49762e7ea6._comment new file mode 100644 index 0000000000..da2a15ba2a --- /dev/null +++ b/doc/bugs/Resource_exhausted/comment_10_bccf9528ffe963154c92ce49762e7ea6._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawln3ckqKx0x_xDZMYwa9Q1bn4I06oWjkog" + nickname="Michael" + subject="comment 10" + date="2013-08-26T18:33:40Z" + content=""" +@Joey: it was a \"pretty large\" transfer, several hundred gigabytes in perhaps ~100000 files. The copying was going to a GPG-encrypted directory remote. +The error only happened once or twice so far. Point taken about find in /proc; I'll do that if it happens next time. + +"""]] diff --git a/doc/bugs/Resource_exhausted/comment_9_419e24e0b91f569294ece28c42daa246._comment b/doc/bugs/Resource_exhausted/comment_9_419e24e0b91f569294ece28c42daa246._comment new file mode 100644 index 0000000000..0e06f5af92 --- /dev/null +++ b/doc/bugs/Resource_exhausted/comment_9_419e24e0b91f569294ece28c42daa246._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 9" + date="2013-08-24T19:10:21Z" + content=""" +@Michael how large a copy are you doing? And what kind of remote are you copying the files to? +It would be helpful if you could be more specific about something I could do to reproduce the problem. Without a test case, I am unlikely to fix the bug. With a test case, I'd be surprised if it took long to fix it. + +If you have a process running that is experiencing the problem, you can also narrow it down a *lot* by looking at what these leaking pipe file descriptors are pipes to. For example, if you have: + +lr-x------ 1 michael michael 64 Aug 10 20:14 895 -> pipe:[2251602] + +You can run `find /proc/ -ls 2251602` and find the process at other end of the pipe, and look its pid up in ps to see what command it is. +"""]] diff --git a/doc/bugs/Unable_to_import_feed.mdwn b/doc/bugs/Unable_to_import_feed.mdwn new file mode 100644 index 0000000000..49dc21bfef --- /dev/null +++ b/doc/bugs/Unable_to_import_feed.mdwn @@ -0,0 +1,27 @@ +Using `git-annex version: 4.20130802` on Debian unstable, when trying to add the feed at , I get: + +[[!format sh """ +importfeed http://www.ndr.de/fernsehen/sendungen/extra_3/videos/zum_mitnehmen/extradrei196_version-hq.xml +--2013-08-16 09:14:13-- http://www.ndr.de/fernsehen/sendungen/extra_3/videos/zum_mitnehmen/extradrei196_version-hq.xml +Auflösen des Hostnamen »www.ndr.de (www.ndr.de)«... 212.201.100.171, 212.201.100.187 +Verbindungsaufbau zu www.ndr.de (www.ndr.de)|212.201.100.171|:80... verbunden. +HTTP-Anforderung gesendet, warte auf Antwort... 200 OK +Länge: 61809 (60K) [application/xml] +In »»/tmp/feed4404«« speichern. + +100%[============================================>] 61.809 --.-K/s in 0,03s + +2013-08-16 09:14:13 (2,20 MB/s) - »»/tmp/feed4404«« gespeichert [61809/61809] + +failed +git-annex: importfeed: 1 failed +"""]] + +(Oh, and using `format` with nono-ASCII seems to break down., at least in the preview.) + +> I'm going to close this since I've narrowed it down to a bug in the +> upstream feed library. [[done]]. Of course, if we get a lot of reports of +> the library not working, I may need to revisit using it, but for now this +> seems an isolated problem. Also, I tried validating the feed, and it is +> not 100% valid, and one of the validity problems is a missing enclosure +> length. --[[Joey]] diff --git a/doc/bugs/Unable_to_import_feed/comment_1_16230fbbb996e165b84787ed4d5f72ea._comment b/doc/bugs/Unable_to_import_feed/comment_1_16230fbbb996e165b84787ed4d5f72ea._comment new file mode 100644 index 0000000000..7c9c1e129b --- /dev/null +++ b/doc/bugs/Unable_to_import_feed/comment_1_16230fbbb996e165b84787ed4d5f72ea._comment @@ -0,0 +1,45 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-23T18:09:27Z" + content=""" +When I try this, without the German translation, I get: + +
+joey@gnu:~/tmp/newrepo>git annex importfeed 'http://www.ndr.de/fernsehen/sendungen/extra_3/videos/zum_mitnehmen/extradrei196_version-hq.xml'
+(checking known urls...)
+importfeed http://www.ndr.de/fernsehen/sendungen/extra_3/videos/zum_mitnehmen/extradrei196_version-hq.xml 
+--2013-08-23 13:58:19--  http://www.ndr.de/fernsehen/sendungen/extra_3/videos/zum_mitnehmen/extradrei196_version-hq.xml
+Resolving www.ndr.de (www.ndr.de)... 23.73.180.154, 23.73.180.115
+Connecting to www.ndr.de (www.ndr.de)|23.73.180.154|:80... connected.
+HTTP request sent, awaiting response... 200 OK
+Length: 61865 (60K) [application/xml]
+Saving to: ‘/home/joey/tmp/feed31120’
+
+100%[======================================>] 61,865       151KB/s   in 0.4s   
+
+2013-08-23 13:58:25 (151 KB/s) - ‘/home/joey/tmp/feed31120’ saved [61865/61865]
+
+
+  warning: bad feed content
+
+ +It seems you left out the last line of the error. + +The feed library seems to fail to find any of the enclosures in this feed, although it is able to parse it as far as finding the individual items in the feed: + +
+Prelude Text.Feed.Query Text.Feed.Import> f <- parseFeedFromFile \"extradrei196_version-hq.xml\" 
+Prelude Text.Feed.Query Text.Feed.Import> map getItemEnclosure $ feedItems f
+[Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing,Nothing]
+
+ +The feed *appears* to contain enclosures, for example: + +
+
+
+ +It may not be well-formed, or the feed library may have a bug. Assuming the latter, I have filed a bug report on the feed library: https://github.com/sof/feed/issues/3 +"""]] diff --git a/doc/bugs/Unable_to_use_remotes_with_space_in_the_path.mdwn b/doc/bugs/Unable_to_use_remotes_with_space_in_the_path.mdwn index 33aeccedb4..6bb6c0782e 100644 --- a/doc/bugs/Unable_to_use_remotes_with_space_in_the_path.mdwn +++ b/doc/bugs/Unable_to_use_remotes_with_space_in_the_path.mdwn @@ -30,3 +30,6 @@ I'm using debian testing (jessie) on a i386 machine. ### Please provide any additional information below. I don't use git annex assistant nor the webapp + +> Tested and only file:// and not other urls have this problem. +> guilhem provided a fix. [[done]] --[[Joey]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_4_78b3c52ba85edfa6ee6e273bec3bea5c._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_4_78b3c52ba85edfa6ee6e273bec3bea5c._comment new file mode 100644 index 0000000000..61b03c1096 --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_4_78b3c52ba85edfa6ee6e273bec3bea5c._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 4" + date="2013-08-16T07:14:12Z" + content=""" +The [[OpenPGP standard|https://tools.ietf.org/html/rfc4880]] specifies that revoked keys/subkeys \"are not to be used\". AFIK GnuPG, as any RFC-compliant implementation, will not let you encrypt to a revoked key no matter what. An extremely dirty workaround is to set up your system clock prior to the revocation date (but that might put your whole system at risk since other applications may rely synced clocks to work properly). + +That said, what you really wanted to do was to revoke access to K1 and add K2 instead. That seems to be a perfectly valid use-case, and it shouldn't be hard to add to git-annex; stay tunned ;-) + + +Tobias: Not sure what you meant by \"revoke access to my annex\", but if you were thinking of the key owner, note that with the current [[encryption design|http://git-annex.branchable.com/design/encryption]], since that person may simply grab from the git repo and then at any time decrypt the passphrase for the symmetric cipher, it makes little sense to revoke access for that person unless you change that passphrase, and reencrypt all annexed files on the remote, which of course needs to be done locally for the encryption to make sense at all. +"""]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_5_a85ccf2f09ebe87147f8761b81a02326._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_5_a85ccf2f09ebe87147f8761b81a02326._comment new file mode 100644 index 0000000000..ff441671f7 --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_5_a85ccf2f09ebe87147f8761b81a02326._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://www.rfc1149.net/" + nickname="Sam" + subject="comment 5" + date="2013-08-19T11:35:52Z" + content=""" +Indeed, removing the revoked key and putting the new one would be acceptable, there is no reason to keep the revoked one around. +"""]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_6_8b89eb5e6386acd0a922310c04f863ac._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_6_8b89eb5e6386acd0a922310c04f863ac._comment new file mode 100644 index 0000000000..eb9cd0f542 --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_6_8b89eb5e6386acd0a922310c04f863ac._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 6" + date="2013-08-19T13:22:59Z" + content=""" +All right, what would be a nice user interface, compatible with the current commands? I was thinking of something along the lines of `git annex enableremote +encryption=newKey -encryption=oldKey`, with an alias `+encryption=encryption` to be backward compatible. It's probably not optimal though, feel free to comment :-) + +Of course, `git-annex` should ensure that at any point in time the passphrase is always encrypted using an OpenPGP key. (Otherwise it might be stored clear in the git repository, which would void the encryption.) Also, anyone who can decrypt the passphrase can revoke all existing keys and reencrypt it using another key; this not really a big deal since the cipher is version-controlled anyway, so loosing access to the repo is unlikely. + +By the way, since we're about to amend the arguments for `enableremote`, it'd be nice to take advantage of the situation to allow pure asymmetric encryption. I propose `git annex initremote ... encryption=myKey crypto={none,hybrid,pubkey}` to use respectively no-encryption, an asymmetrically encrypted passphrase (the current design, default), and OpenPGP keys only. +"""]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_7_20dc5a7ce7cb6ca97ccdfb923c3b24bb._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_7_20dc5a7ce7cb6ca97ccdfb923c3b24bb._comment new file mode 100644 index 0000000000..02be72e368 --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_7_20dc5a7ce7cb6ca97ccdfb923c3b24bb._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 7" + date="2013-08-19T16:08:49Z" + content=""" +On second thought, I think it makes more sense to have something like `git annex initremote ... encryption={none,shared,hybrid,pubkey} keyid=whatever` and `git annex enableremote ... [+keyid=newkey] [-keyid=oldkey]`, where `keyid` can only be used when `encryption` is either `hybrid` (default) or `pubkey`. + +This would break compatibility with the current interpretation of `encryption`, but I believe it's not so invasive: People are not creating new remotes every day, and an error message could clarify the new behavior. It's also clearer, since key IDs can be added and deleted at will, whereas the encryption scheme cannot. +"""]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_8_9dc921dc6077f828454a4444088b9a43._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_8_9dc921dc6077f828454a4444088b9a43._comment new file mode 100644 index 0000000000..a63ce1262c --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_8_9dc921dc6077f828454a4444088b9a43._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 8" + date="2013-08-22T17:05:49Z" + content=""" +Note that the assistant generates initremote parameters so code there also needs to be changed if the syntax changes. + +I think I am ok with changing the syntax. However, it seems that `encryption=-oldkey encryption=newkey` could be used to remove the old revoked key and add a new one. Using `-keyid` as a parameter to initremote is a bit tricky since git-annex's regular option parser would see it, before the parameter could get to initremote. (Unless -keyid was defined as a regular option specific to initremote.) OR, git-annex could just try to detect when a key is revoked and automatically remove it when a new encryption key is specified. + +Hmm, it would be possible to have it just notice, when adding a new key, if one of the existing keys is revoked, and +remove the revoked key automatically. + +The above doesn't deal with the case of wanting to add pure asymmetric encryption. It seems to me that from a user's point of view, what they really need to know about asymmetric encryption is that they can't easily give additional keyids access after the fact (without reencrypting and reuploading everything). So I think it would be good if the syntax made that obvious. Perhaps `encryptiononly=key` +"""]] diff --git a/doc/bugs/Using_a_revoked_GPG_key/comment_9_f50c802d78041fd1522f0e7599ce6a45._comment b/doc/bugs/Using_a_revoked_GPG_key/comment_9_f50c802d78041fd1522f0e7599ce6a45._comment new file mode 100644 index 0000000000..d86de4e1bf --- /dev/null +++ b/doc/bugs/Using_a_revoked_GPG_key/comment_9_f50c802d78041fd1522f0e7599ce6a45._comment @@ -0,0 +1,42 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 9" + date="2013-08-22T18:42:28Z" + content=""" +Hehe, I ran into the option parser issue when implementing that change +;-) So I moved to `git annex enableremote ... [keyid+=newkey] +[keyid-=oldkey]` (where `+` is optional, for consistency) which doesn't +prevent users from specifying a key by something starting with a sign. + +While it's certainly possible to tell git-annex to manage the authorized +keys itself, users may have other reasons to remove a key so I'm not +sure it's a good idea. Also, what if someone forgets to add his/her new +key after revocation (it's still possible to decrypt after all)? If +another person updates the keyring afterwards, the first user will be +denied further access, and will have to retrieve and reencrypt the +\"cipher\" manually, which is not so trivial. + + +I understand that asymmetric encryption needs special care, but Sam's +use case could be reproduced with that scheme I believe. For instance a +user may superseed and revoke his/her old key; then new files would be +uploaded with the new one, but as long as the old key is not +compromised, I don't see why s/he should reupload everything instead of +using the old key when pulling from the remote. Of course one may argue +that the key shouldn't be revoked at the first place, but if it's used +for other purposes (e.g., it's publicly available on a key server) it's +good practice to revoke it IMHO. + +As for the removal of keys with pure asymmetric encryption, it is just +required I think: Otherwise revoking a key would prevent any further +content to be encrypted. There I can't see any problem with git-annex +managing the keyring itself (beside the extra code to write :-P). + +All in all if we are to allow deletion/addition of keyIDs (and I think +we should!), I think it should be done for both `hybrid` and `pubkey` +schemes. Do you really want another syntax? I'd say clarify the manage +(plus maybe a warning when running the CLI) is enough, but true it's +easy to shoot oneself in the foot there... + +"""]] diff --git a/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_2_9e3c1f1ba05d8996b5a95829ce32c07e._comment b/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_2_9e3c1f1ba05d8996b5a95829ce32c07e._comment new file mode 100644 index 0000000000..d98e7976e3 --- /dev/null +++ b/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_2_9e3c1f1ba05d8996b5a95829ce32c07e._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="bad bug report title 101" + date="2013-08-24T19:17:29Z" + content=""" +I don't understand why you think the problem has something to do with Windows drive letters. There are no Windows drive letters in the symlinks you show. The only place I see any Windows drive letter is in the descripton of the remote that `git annex get` displays when it fails to get the file. That description is purely informative, it's not a path that git-annex is trying to use. + +I'd suggest that you run `git annex get --debug` to see if it is doing anything obviously wrong. The mostly likely culprit is your SMB setup, which I am not going to be able to replicate. +"""]] diff --git a/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_3_3a0787912f4a3a8797b7786f5ce38590._comment b/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_3_3a0787912f4a3a8797b7786f5ce38590._comment new file mode 100644 index 0000000000..16f240cf29 --- /dev/null +++ b/doc/bugs/Windows_to_Linux_clone_-_Windows_drive_letters_cause_git_annex_get_to_fail/comment_3_3a0787912f4a3a8797b7786f5ce38590._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawlzWwnBfgJrkhPQakBo6DbPXutJIVDHkj0" + nickname="Adam" + subject="comment 3" + date="2013-08-26T06:56:33Z" + content=""" +You're correct. I can see in .git/config that the remote references z:\ which of course will break on the Linux side. Maybe this is a case of the error messages not quite telling me the right thing? +"""]] diff --git a/doc/bugs/added_branches_makes___39__git_annex_unused__39___slow.mdwn b/doc/bugs/added_branches_makes___39__git_annex_unused__39___slow.mdwn index 46024e5007..95751527b3 100644 --- a/doc/bugs/added_branches_makes___39__git_annex_unused__39___slow.mdwn +++ b/doc/bugs/added_branches_makes___39__git_annex_unused__39___slow.mdwn @@ -79,3 +79,9 @@ What version of git-annex are you using? On what operating system? git-annex version: 3.20130216 On current Debian sid/experimental + +> [[Done]], thanks to guilhem. We ended up using a different algorythm +> which is faster yet, basically it now does a diff-index between the +> index and each branch for its second stage bloom filter. +> Speedup is 30x with 0 (or 1?) branch, and then massive for each +> additional branch. --[[Joey]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit.mdwn b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit.mdwn new file mode 100644 index 0000000000..e739b96911 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit.mdwn @@ -0,0 +1,28 @@ +### Please describe the problem. + +I installed git-annex on my android device (Nook HD+, with Cyanogenmod 10.1 installed) for the first time today and was excited to get it working. However, I noticed the device warming alarmingly, and, after installing a CPU usage monitor, it became clear that git annex was the problem, as it was hovering around 30-40% even when idle. + +I tried quitting git-annex using the webapp's "Shutdown Daemon" menu option, and it seemed to shut down successfully, but the CPU monitor still showed that process present and taking up high amounts of CPU (sometimes well over 50%). I used the android app switcher and noticed that the terminal emulator for git annex was still running; I tried to quit this by using the X button and it seemed to close, but the CPU monitor still showed the git-annex process consuming large amounts of CPU. Finally I had to quit the process forcefully from the monitor. + +### What steps will reproduce the problem? + +Install & run; observe CPU. I used a dedicated CPU monitor to stop it the first time; another time, I tried stopping it by going to Preferences, Apps, Running Applications, where it told me it had one process and one service running. I stopped the service without issue; it said the process could not be safely stopped but I stopped it anyway and that successfully stopped the app. + + +### What version of git-annex are you using? On what operating system? + +the current (4.20130826-g46f422) version on Android. + +### Please provide any additional information below. + +[[!format sh """ +# If you can, paste a complete transcript of the problem occurring here. +# If the problem is with the git-annex assistant, paste in .git/annex/daemon.log + +(I'm not sure how to get a log out of the web app to paste here unfortunately. + +# End of transcript or log. +"""]] + +> [[done]]; I fixed the bug which turned out to be a stupid +> minunderstanding of how a java library worked. --[[Joey]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_1d841ff0b0ffd814efed2449dc1f35f3._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_1d841ff0b0ffd814efed2449dc1f35f3._comment new file mode 100644 index 0000000000..892894ad42 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_1d841ff0b0ffd814efed2449dc1f35f3._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 10" + date="2013-08-27T01:46:36Z" + content=""" +This seems to be a reversion instroduced in commit a48d340abdaf3296a2ddacd73c18adc9a13a02ef. With that backed out, I get 0% cpu usage for the terminal app. Even if I run top in the terminal, its CPU sits under 1%. + +Clearly the infinite loop in that patch is running faster than expected! +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_cd101e0af45d8f463011fb0d04b3b822._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_cd101e0af45d8f463011fb0d04b3b822._comment new file mode 100644 index 0000000000..d8ca9fb05c --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_10_cd101e0af45d8f463011fb0d04b3b822._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="http://edheil.wordpress.com/" + ip="173.162.44.162" + subject="comment 10" + date="2013-08-26T20:19:06Z" + content=""" +Yeah, that would definitely explain both what I'm seeing and why you haven't been seeing it. + +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_1_8e7bc6965ea967a8d43240791a30c5bc._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_1_8e7bc6965ea967a8d43240791a30c5bc._comment new file mode 100644 index 0000000000..756b9d5c6c --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_1_8e7bc6965ea967a8d43240791a30c5bc._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="http://edheil.wordpress.com/" + ip="173.162.44.162" + subject="comment 1" + date="2013-08-26T18:34:44Z" + content=""" +Just noticed I was using the autobuild instead of the last release version; I'll try the release version and see if that makes any difference. + +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_2_891c1073f908b204651899d41599f944._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_2_891c1073f908b204651899d41599f944._comment new file mode 100644 index 0000000000..c26c512eae --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_2_891c1073f908b204651899d41599f944._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-26T18:42:02Z" + content=""" +If you shut down the daemon, it seems to me that the process that was still running would probably be `git annex transferkey` which runs in its own process to upload/download file contents. I normally see 0% to 1% cpu use from git-annex when it is running on my android tablet. It's possible that the 1% use is due to it waking up every second, which got fixed in 9dc2373977d583b4c4aa6cf0555dc97309f89991. +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_3_de02b8f1b5928fa1a7078c4aa2124bea._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_3_de02b8f1b5928fa1a7078c4aa2124bea._comment new file mode 100644 index 0000000000..71ad88d740 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_3_de02b8f1b5928fa1a7078c4aa2124bea._comment @@ -0,0 +1,11 @@ +[[!comment format=mdwn + username="http://edheil.wordpress.com/" + ip="173.162.44.162" + subject="comment 3" + date="2013-08-26T19:03:45Z" + content=""" +OK, so I might have a rogue transferkey process going on, but one which starts over again when I restart the app? + +I've set this all up purely as a \"can I do this\" experiment right now; there is literally zero important data there to lose, either on the tablet or on the laptop, so maybe I could just write this off as a bad result of my first few shaky attempts to get the device paired with my laptop, wipe out both annexes, and start completely from scratch. + +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_6_506acc4275a81ed9e9b08e8a40fcf96a._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_6_506acc4275a81ed9e9b08e8a40fcf96a._comment new file mode 100644 index 0000000000..553a135a00 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_6_506acc4275a81ed9e9b08e8a40fcf96a._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="http://edheil.wordpress.com/" + ip="173.162.44.162" + subject="comment 6" + date="2013-08-26T19:38:12Z" + content=""" +a final note -- according to the process monitor, the process eating CPU is \"ga.androidterm\". There are also a small swarm of about 6 git processes none of which are consuming much CPU time at all. + +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_7_d38d6f40db4c9437764c7b2ddf36b5a9._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_7_d38d6f40db4c9437764c7b2ddf36b5a9._comment new file mode 100644 index 0000000000..66a5601914 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_7_d38d6f40db4c9437764c7b2ddf36b5a9._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 7" + date="2013-08-26T20:00:39Z" + content=""" +It's certianly possible that the terminal app eats cpu for some reason even when sitting idle. It's hard for me to tell since I've been measuring cpu use by running top inside that terminal, which necessarily seems to use a lot of the CPU just to draw the screen. + +If it's the terminal at fault, it would continue after you shutdown the git-annex daemon, since that doesn't close the terminal. +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_8_9bb23e9cbc77ecca4b1209b0f66bc2b0._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_8_9bb23e9cbc77ecca4b1209b0f66bc2b0._comment new file mode 100644 index 0000000000..3fce2f21f7 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_8_9bb23e9cbc77ecca4b1209b0f66bc2b0._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="oh yeah, i can run top in adb.." + date="2013-08-26T20:14:13Z" + content=""" +So, I can tell that on my tablet, the terminal app is using 82% cpu while idle. +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_d1ce7fc251db076da61eed5bb9d71b9a._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_d1ce7fc251db076da61eed5bb9d71b9a._comment new file mode 100644 index 0000000000..ffd0a44bea --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_d1ce7fc251db076da61eed5bb9d71b9a._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="http://edheil.wordpress.com/" + ip="173.162.44.162" + subject="comment 9" + date="2013-08-26T20:49:34Z" + content=""" +(removed my earlier comments with debug info, since it wasn't relevant and I'd just as soon not display my gmail id and home machine's address on the web if I don't need to) + +"""]] diff --git a/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_feb71c1022ff65d82e66a3958a41dfb2._comment b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_feb71c1022ff65d82e66a3958a41dfb2._comment new file mode 100644 index 0000000000..8f32df0351 --- /dev/null +++ b/doc/bugs/android:_high_CPU_usage__44___unclear_how_to_quit/comment_9_feb71c1022ff65d82e66a3958a41dfb2._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 9" + date="2013-08-26T20:16:05Z" + content=""" +Strace doesn't show it doing anything. I suppose I should try building the terminal without the several patches I added to it to support git-annex to see if I somehow made it use all this cpu.. +"""]] diff --git a/doc/bugs/authentication_to_rsync.net_fails.mdwn b/doc/bugs/authentication_to_rsync.net_fails.mdwn index aacfe4e206..707f93d495 100644 --- a/doc/bugs/authentication_to_rsync.net_fails.mdwn +++ b/doc/bugs/authentication_to_rsync.net_fails.mdwn @@ -25,3 +25,6 @@ git-annex version: 4.20130521 on debian linux 7.1. That log is empty. # End of transcript or log. """]] + +> I added ssh-askpass as a recommends, so I suppose +> I can close this. [[done]] --[[Joey]] diff --git a/doc/bugs/authentication_to_rsync.net_fails/comment_1_9db65f89415c8d825f268afb75244998._comment b/doc/bugs/authentication_to_rsync.net_fails/comment_1_9db65f89415c8d825f268afb75244998._comment new file mode 100644 index 0000000000..731d5148fd --- /dev/null +++ b/doc/bugs/authentication_to_rsync.net_fails/comment_1_9db65f89415c8d825f268afb75244998._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawliqfHEW134uawIUPwyKiyOdoF-oI5TxnQ" + nickname="Ethan" + subject="Doh. /usr/bin/ssh-askpass needs to be on *local* machine." + date="2013-08-15T20:13:31Z" + content=""" +My mistake; the problem was the I was missing /usr/bin/ssh-askpass on my local machine, not the rsync.net host. + +I still think this is a bug. I'm on a debian machine and installed git-annex from its debian package, so seems like the ssh-askpass package should be listed as a dependency. But that's a debian packaging problem, not a git-annex bug per se, so I'll go file it elsewhere. +"""]] diff --git a/doc/bugs/cannot_determine_uuid_for_origin.mdwn b/doc/bugs/cannot_determine_uuid_for_origin.mdwn new file mode 100644 index 0000000000..ce46e5733a --- /dev/null +++ b/doc/bugs/cannot_determine_uuid_for_origin.mdwn @@ -0,0 +1,135 @@ +[[!toc]] + +### Please describe the problem. + +I get this error when trying to copy annexed files from my laptop to the bare repository on my server: + + anarcat@angela:ohm2013$ git annex copy -t origin . + git-annex: cannot determine uuid for origin + +### What steps will reproduce the problem? + +Here's my setup: + + * `angela`: regular git repository on my laptop (`angela`) where i ran `git annex init` and `git annex add`ed 4 big files (in `~anarcat/presentations/ohm2013`) + * `marcos-bare`: a bare git repository where i ran `git annex init` on a different server (`marcos`) (in `~anarcat/repos/presentations/ohm2013.git`) + * `marcos-checkout`: a checkout of the above repository on marcos (in `~anarcat/presentations/ohm2013`) + +I ran `git pull/push` everwhere in there, and still get the error. + +Remotes on all repos: + + * `angela`: `origin anarcat.ath.cx:repos/presentations/ohm2013.git` + * `marcos-bare`: no remote + * `marcos-checkout`: `origin /home/anarcat/repos/presentations/ohm2013.git` + +Note that file added with `git annex addurl` on `marcos-checkout` properly gets propagated on `angela` once i do `git annex get` there. + +### What version of git-annex are you using? On what operating system? + +`angela` runs: + +[[!format txt """ +git-annex version: 4.20130730-ge59a8c6 +build flags: Assistant Webapp Pairing Testsuite S3 WebDAV Inotify DBus XMPP DNS +local repository version: 3 +default repository version: 3 +supported repository versions: 3 4 +upgrade supported from repository versions: 0 1 2 +"""]] + +I was able to reproduce with the backport version too. + +I compiled it by hand from git. + +`marcos` runs: + +[[!format txt """ +git-annex version: 3.20120629 +local repository version: unknown +default repository version: 3 +supported repository versions: 3 +upgrade supported from repository versions: 0 1 2 +"""]] + +### Please provide any additional information below. + +In addition, there's this error on `marcos-bare`: + +[[!format sh """ +anarcat@marcos:ohm2013.git$ git annex status -d +supported backends: SHA256 SHA1 SHA512 SHA224 SHA384 SHA256E SHA1E SHA512E SHA224E SHA384E WORM URL +supported remote types: git S3 bup directory rsync web hook +trusted repositories: git ["--git-dir=/home/anarcat/repos/presentations/ohm2013.git","show-ref","git-annex"] +git ["--git-dir=/home/anarcat/repos/presentations/ohm2013.git","show-ref","--hash","refs/heads/git-annex"] +git ["--git-dir=/home/anarcat/repos/presentations/ohm2013.git","log","refs/heads/git-annex..6063e958c02259a39b87d0f1dc44c9272c52df3f","--oneline","-n1"] +git ["--git-dir=/home/anarcat/repos/presentations/ohm2013.git","cat-file","--batch"] +0 +semitrusted repositories: 4 + 00000000-0000-0000-0000-000000000001 -- web + 5868f840-02e7-11e3-94e9-9b3701bd28bb -- marcos-checkout + aafdd242-02e7-11e3-bb6a-6f16a5c6103e -- here (marcos-bare) + befc3057-d23d-4312-843a-0645e93107d8 -- angela +untrusted repositories: 0 +dead repositories: 0 +available local disk space: 14 gigabytes (+1 megabyte reserved) +local annex keys: 0 +local annex size: 0 bytes +known annex keys: git ["--git-dir=/home/anarcat/repos/presentations/ohm2013.git","ls-files","--cached","-z","--","/home/anarcat/repos/presentations/ohm2013.git"] +fatal: '/home/anarcat/repos/presentations/ohm2013.git' is outside repository +0 +known annex size: 0 bytes +bloom filter size: 16 mebibytes (0% full) +backend usage: +"""]] + +### Workaround! + +I found that I could succesfully push to the non-bare repo, like this: + +[[!format txt """ +anarcat@angela:ohm2013$ git remote add marcos-checkout ssh://anarcat.ath.cx/~/presentations/ohm2013 +anarcat@angela:ohm2013$ git fetch marcos-checkout +From ssh://anarcat.ath.cx/~/presentations/ohm2013 + * [new branch] git-annex -> marcos-checkout/git-annex + * [new branch] master -> marcos-checkout/master +anarcat@angela:ohm2013$ git annex copy AlerteRouge.webm --to marcos-checkout +copy AlerteRouge.webm (checking marcos-checkout...) (to marcos-checkout...) +SHA256E-s138903105--a69db8d4c3835b03bdb08cb1cccfde5c76f586f934d63283694e7101b25352a8.webm +[...] +"""]] + +It seems that git-annex doesn't like bare repos at all... + +### Fix + +It seems that my problem was specifically related to [[bare repositories]], which are not well supported historically. There has been other reports of problems in the past, which I missed in my search because symptoms were different: + + * [[bugs/bare git repos]] + * [[forum/get and copy with bare repositories]] + +Yet while I was able to do `git annex get --all` *from* the `marcos-bare` repository, I still get the original error message while trying to `git annex copy -t marcos-bare`, which is pretty annoying considering the original files are on my laptop, which is not publicly accessible. So I basically need to add the `marcos-checkout` as a remote, copy there, then get from the bare repo to make this work, which is a rather convoluted way of doing things. :) + +It seems to me a proper fix would be to be able to `git annex copy --to marcos-bare`. Thanks! + +Update: it seems te problem was that I had the following in my `.git/config`: + + [remote "marcos-bare"] + url = ssh://anarcat.ath.cx/~/repos/presentations/ohm2013.git + annex-ignore = true + fetch = +refs/heads/*:refs/remotes/marcos-bare/* + +I have *no* idea how that `annex-ignore` got there, but that was the root of my problem. Removing it it allowed my to do `git annex copy`. I really don't know how this happened, but I guess this is [[done]], although I believe this error message is really confusing and could be improved. + +> `annex-ignore` is set automatically by git-annex if it fails to query +> the uuid of a remote the first time it tries to use it. It will say +> when it does that. The assumption +> is that a remote whose uuid cannot be looked up is a git remote +> on a server w/o git-annex support (like github) and it would be annoying +> to constantly be trying and failing to get that uuid. +> +> So, I've improved the error message. Now when annex-ignore is set +> for a remote, the error you got will mention that. +> +> (Also, there is not currently anything lacking in git-annex's support +> for bare repositories.) --[[Joey]] diff --git a/doc/bugs/cannot_link_executable_on_android.mdwn b/doc/bugs/cannot_link_executable_on_android.mdwn new file mode 100644 index 0000000000..cb660dd9cf --- /dev/null +++ b/doc/bugs/cannot_link_executable_on_android.mdwn @@ -0,0 +1,28 @@ +### Please describe the problem. +Then starting git-annex on my Galaxy Nexus Android device, in the terminal window I get: + +[[!format sh """ +Falling back to hardcoded app location: cannot find expected files in /data/app-lib +git annex webapp +u0_a123@maguro:/sdcad/git-annex.home $ git annex webapp +CANNOT LINK EXECUTABLE: git-annex invalid R_ARM_COPY relocation against DT_SYMBOLIC shared library libc.so (built with -Bsymbolic?) +u0_a123@maguro:/sdcad/git-annex.home $ +"""]] + +### What steps will reproduce the problem? +Start git-annex. + +### What version of git-annex are you using? On what operating system? +Nightly build and release from a few days ago - 1.0.52 + +### Please provide any additional information below. + +[[!format sh """ +# If you can, paste a complete transcript of the problem occurring here. +# If the problem is with the git-annex assistant, paste in .git/annex/daemon.log + + +# End of transcript or log. +"""]] + +> [[dup|done]] of [[git-annex_broken_on_Android_4.3]].--[[Joey]] diff --git a/doc/bugs/git-annex_opens_too_many_files/comment_4_c03bde64be8fdd962826bc7afa07d2a9._comment b/doc/bugs/git-annex_opens_too_many_files/comment_4_c03bde64be8fdd962826bc7afa07d2a9._comment new file mode 100644 index 0000000000..b4c4587063 --- /dev/null +++ b/doc/bugs/git-annex_opens_too_many_files/comment_4_c03bde64be8fdd962826bc7afa07d2a9._comment @@ -0,0 +1,137 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawlmRpGORNKWimtzqItvwm4I6cn16vx8OvU" + nickname="hayden" + subject="Many network sockets with associated fds hanging around" + date="2013-08-15T18:00:42Z" + content=""" +I see something similar in logs and after roughly 10 mins the web-apps dies. +So I think I hit the same as the above user. +Sometimes I get thread deaths and restart requests but the root cause appears to match the scenario mentioned over. +Often the webapp just hangs. But always when it hits the fd ulimit... 1024 on this system. + +git-annex version is 4.20130802-g1452ac3 and I used the static-linked linux tar.gz linux-binary download. + +Test setup is a from scratch assistant startup on Ubuntu 12.04. +Not exactly a clean ubuntu though, so maybe difficult to duplicate troubles at your end. + +I fired up the web-app with a cleaned out config. No signs of leaks until an annex is created. +On creation of an empty annex I get fd leaks a about 1 per second after a repository is created. +Strace'ing the main process only shows 8-bytes writes (see below) at the same rate as the leak. +Sometimes the fd-leak stops before the resource limit, sometimes not. +Creating a new annex on top of an existing directory tree with many files is pretty reliable trigger though. +Startup scan finishes and fds leak away until the ulimit is hit. + + hayden@orca:~/gamma$ ls /proc/26319/fd + 0 10 12 14 16 18 2 21 23 25 27 29 30 32 34 36 38 4 41 43 45 6 8 + 1 11 13 15 17 19 20 22 24 26 28 3 31 33 35 37 39 40 42 44 5 7 9 + hayden@orca:~/gamma$ ls /proc/26319/fd + 0 10 12 14 16 18 2 21 23 25 27 29 30 32 34 36 38 4 41 43 45 6 8 + 1 11 13 15 17 19 20 22 24 26 28 3 31 33 35 37 39 40 42 44 5 7 9 + hayden@orca:~/gamma$ ls /proc/26319/fd + 0 10 12 14 16 18 2 21 23 25 27 29 30 32 34 36 38 4 41 43 45 5 7 9 + 1 11 13 15 17 19 20 22 24 26 28 3 31 33 35 37 39 40 42 44 46 6 8 + + hayden@orca:~/gamma$ ls /proc/26319/fd/43 + /proc/26319/fd/43 + + hayden@orca:~/gamma$ ls -l /proc/26319/fd/43 + ls -l /proc/26319/fd/43 + lrwx------ 1 hayden hayden 64 Aug 14 21:10 /proc/26319/fd/43 -> socket:[568994] + + hayden@orca:~/gamma$ lsof | grep 568994 + git-annex 26319 hayden 43u IPv4 568994 0t0 UDP 224.0.0.251:55556 + + hayden@orca:~/gamma$ uname -a + Linux orca 3.2.0-25-generic #40-Ubuntu SMP Wed May 23 20:30:51 UTC 2012 x86_64 x86_64 x86_64 GNU/Linux + + hayden@orca:~/gamma$ cat /etc/issue + Ubuntu 12.04 LTS \n \l + + hayden@orca:~/gamma$ fuser 55556/udp -a + 55556/udp: 4415 26319 27080 27083 + + hayden@orca:~/gamma$ ps aux | grep 4415 + hayden 4415 0.0 0.0 66716 3036 ? S Aug12 0:03 curl -s --head -L http://127.0.0.1:38464/?auth=da9c4aba4cc2db9cf78574753f6e94d8031c6a7bdf8bfe100bde868f57b81fd751965cc9d68a9afac79f826d257a256a04ce62615a7f23cd7c925969dda1c7b8 -w %{http_code} + hayden 27458 0.0 0.0 10612 924 pts/0 S+ 21:50 0:00 grep --color=auto 4415 + + hayden@orca:~/gamma$ ps aux | grep 26319 + hayden 26319 0.1 0.7 497188 28560 pts/5 Sl 21:09 0:04 git-annex webapp + hayden 26338 3.4 3.4 1035572 137864 pts/5 Sl 21:09 1:25 /usr/lib/firefox/firefox /tmp/webapp26319.html + hayden 27460 0.0 0.0 10612 920 pts/0 S+ 21:50 0:00 grep --color=auto 26319 + + hayden@orca:~/gamma$ ps aux | grep 27080 + hayden 27080 0.0 0.0 16476 1288 pts/5 S 21:33 0:00 git --git-dir=/home/hayden/boo/.git --work-tree=/home/hayden/boo cat-file --batch + hayden 27462 0.0 0.0 10612 924 pts/0 S+ 21:50 0:00 grep --color=auto 27080 + + hayden@orca:~/gamma$ ps aux | grep 27083 + hayden 27083 0.0 0.0 16476 1060 pts/5 S 21:33 0:00 git --git-dir=/home/hayden/boo/.git --work-tree=/home/hayden/boo check-attr -z --stdin annex.backend annex.numcopies -- + hayden 27464 0.0 0.0 10612 920 pts/0 S+ 21:51 0:00 grep --color=auto 27083 + +----> has 579 open fds at this point but this number holds stable over 10 min +(copy in new tree to provoke) +(no change) +----> restart daemon in gui to provoke +(new process has open fds slowly climbing after startup scan) + +straces look like this repeating every second. (clipped down) + + futex(0x34f001c, FUTEX_WAIT_PRIVATE, 51, NULL) = ? ERESTARTSYS (To be restarted) + --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- + rt_sigreturn(0x1a) = 202 + futex(0x34f001c, FUTEX_WAIT_PRIVATE, 51, NULL) = ? ERESTARTSYS (To be restarted) + --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- + rt_sigreturn(0x1a) = 202 + futex(0x34f001c, FUTEX_WAIT_PRIVATE, 51, NULL) = ? ERESTARTSYS (To be restarted) + --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- + rt_sigreturn(0x1a) = 202 + futex(0x34f001c, FUTEX_WAIT_PRIVATE, 51, NULL) = ? ERESTARTSYS (To be restarted) + --- SIGVTALRM (Virtual timer expired) @ 0 (0) --- + write(6, \"\377\0\0\0\0\0\0\0\", 8) = 8 + rt_sigreturn(0x2) = 202 + futex(0x34f001c, FUTEX_WAIT_PRIVATE, 51, NULL^C + Process 29803 detached + +Until after roughly 10 mins... + + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1017 + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1023 + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1024 + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1024 + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1024 + hayden@orca:~/boo$ ls /proc/29803/fd | wc -l + 1024 + + hayden@orca:~/boo$ ulimit -a + core file size (blocks, -c) 0 + data seg size (kbytes, -d) unlimited + scheduling priority (-e) 0 + file size (blocks, -f) unlimited + pending signals (-i) 31164 + max locked memory (kbytes, -l) 64 + max memory size (kbytes, -m) unlimited + open files (-n) 1024 + pipe size (512 bytes, -p) 8 + POSIX message queues (bytes, -q) 819200 + real-time priority (-r) 0 + stack size (kbytes, -s) 8192 + cpu time (seconds, -t) unlimited + max user processes (-u) 31164 + virtual memory (kbytes, -v) unlimited + file locks (-x) unlimited + hayden@orca:~/boo$ + +At this point the webapp hangs but a number of interesting crashes may occur. I've also seen the particular error in the previous users log (on a big tree). + + [2013-08-14 21:56:12 CEST] main: starting assistant version 4.20130802-g1452ac3 + (scanning...) [2013-08-14 21:56:12 CEST] Watcher: Performing startup scan + (started...) DaemonStatus crashed: /home/hayden/boo/.git/annex/: openTempFile: resource exhausted (Too many open files) + [2013-08-14 22:06:12 CEST] DaemonStatus: warning DaemonStatus crashed: /home/hayden/boo/.git/annex/: openTempFile: resource exhausted (Too many open files) + +Is any of the above helpful? Anything else useful to kick for testing that you'd like done? +I'd guess this is something weird with my ubuntu setup that provokes this as more users would see it otherwise. +"""]] diff --git a/doc/bugs/git-annex_opens_too_many_files/comment_5_33a2e783e5355e981497b9861997570b._comment b/doc/bugs/git-annex_opens_too_many_files/comment_5_33a2e783e5355e981497b9861997570b._comment new file mode 100644 index 0000000000..786672eb20 --- /dev/null +++ b/doc/bugs/git-annex_opens_too_many_files/comment_5_33a2e783e5355e981497b9861997570b._comment @@ -0,0 +1,18 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 5" + date="2013-08-24T17:09:43Z" + content=""" +Thanks for an excellent amount of debug information. + +I can see what's leaking is UDP connections to 224.0.0.251. That address is used for the \"local pairing\" option in the webapp. + +I was able to reproduce the problem by disabling all network interfaces except `lo`. The PairListener then failed to open a multicast listening socket. When it fails that way, it retried every second, as you noticed. And there is a socket leak in that failure mode. + +I wonder if you're seeing this even when on the network? If so, perhaps your Ubuntu system has something going on that prevents opening a multicast listening socket on even `eth0` or `wlan0` or whatever. + +Unfortunately, the actual socket leak bug is in the [network-multicast](http://hackage.haskell.org/package/network-multicast) library, and not in git-annex. I have filed an upstream bug report: + +Hopefully that will be dealt with soon. There is a workaround I could do in git-annex: If it fails (leaking one socket), it could wait until the NetworkListener indicated a new network interface was opened, before trying again (possibly leaking one socket again). This would change it from a 1 per second leak to a 1 per change of network leak at worst, which is probably much less likely to cause problems. +"""]] diff --git a/doc/bugs/git-annex_opens_too_many_files/comment_6_b3a5a4e4ca29c5cd2840bfeb4c63ea68._comment b/doc/bugs/git-annex_opens_too_many_files/comment_6_b3a5a4e4ca29c5cd2840bfeb4c63ea68._comment new file mode 100644 index 0000000000..60c268fc03 --- /dev/null +++ b/doc/bugs/git-annex_opens_too_many_files/comment_6_b3a5a4e4ca29c5cd2840bfeb4c63ea68._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 6" + date="2013-08-24T18:38:56Z" + content=""" +My NetListener workaround turned out to not be portable enough. + +However, I have sent a patch to fix the FD leak: +Hopefully it gets applied soon. + +I have also made the PairListener only retry every 60 seconds. Which makes the leak 1/60th as bad, for whatever that's worth. + +Once a fix for this gets into Debian, I need to remember to backport it to stable, and update the autobuilders to use it. Also need to remember to update the Android autobuilder. Leaving this bug report open until that happens. +"""]] diff --git a/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__.mdwn b/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__.mdwn new file mode 100644 index 0000000000..88ea558eb8 --- /dev/null +++ b/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__.mdwn @@ -0,0 +1,354 @@ +### Please describe the problem. + +I installed the git-annex app for MacOSX (10.8.4) + +### What steps will reproduce the problem? + +- Created a repository +- In the configuration, entered my google username/password + +### What version of git-annex are you using? On what operating system? + +bundle version: 0.0.1 + +### Please provide any additional information below. + +[[!format sh """ +# If you can, paste a complete transcript of the problem occurring here. +# If the problem is with the git-annex assistant, paste in .git/annex/daemon.log + +Process: git-annex [12934] +Path: /Applications/git-annex.app/Contents/MacOS/bundle/git-annex +Identifier: git-annex +Version: 0 +Code Type: X86-64 (Native) +Parent Process: ??? [1] +User ID: 502 + +Date/Time: 2013-08-17 12:27:12.495 -0700 +OS Version: Mac OS X 10.8.4 (12E55) +Report Version: 10 +Sleep/Wake UUID: 6DB42174-0147-4C8B-B83E-F305823297CA + +Interval Since Last Report: 294009 sec +Crashes Since Last Report: 4 +Per-App Crashes Since Last Report: 4 +Anonymous UUID: 0D492F72-DAE5-360C-A6D6-ECB38FD53115 + +Crashed Thread: 3 + +Exception Type: EXC_BAD_ACCESS (SIGSEGV) +Exception Codes: KERN_INVALID_ADDRESS at 0x0000000000000000 + +VM Regions Near 0: +--> + __TEXT 000000010b5e6000-000000010e08d000 [ 42.7M] r-x/rwx SM=COW /Applications/git-annex.app/Contents/MacOS/bundle/git-annex + +Thread 0:: Dispatch queue: com.apple.main-thread +0 libsystem_kernel.dylib 0x00007fff931400fa __psynch_cvwait + 10 +1 libsystem_c.dylib 0x00007fff86adffe9 _pthread_cond_wait + 869 +2 git-annex 0x000000010df20179 0x10b5e6000 + 43229561 +3 git-annex 0x000000010defc8eb 0x10b5e6000 + 43084011 +4 git-annex 0x000000010df0bc86 0x10b5e6000 + 43146374 +5 git-annex 0x000000010df0c6fb 0x10b5e6000 + 43149051 +6 git-annex 0x000000010df07b46 0x10b5e6000 + 43129670 +7 git-annex 0x000000010df07c69 0x10b5e6000 + 43129961 +8 git-annex 0x000000010bcff518 0x10b5e6000 + 7443736 +9 libdyld.dylib 0x00007fff8c3e47e1 start + 1 + +Thread 1: +0 libsystem_kernel.dylib 0x00007fff931400fa __psynch_cvwait + 10 +1 libsystem_c.dylib 0x00007fff86adffe9 _pthread_cond_wait + 869 +2 git-annex 0x000000010df20179 0x10b5e6000 + 43229561 +3 git-annex 0x000000010defc8eb 0x10b5e6000 + 43084011 +4 git-annex 0x000000010df0bc86 0x10b5e6000 + 43146374 +5 git-annex 0x000000010df0c5e0 0x10b5e6000 + 43148768 +6 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +7 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 2: +0 libsystem_kernel.dylib 0x00007fff931400fa __psynch_cvwait + 10 +1 libsystem_c.dylib 0x00007fff86adffe9 _pthread_cond_wait + 869 +2 git-annex 0x000000010df20179 0x10b5e6000 + 43229561 +3 git-annex 0x000000010defc8eb 0x10b5e6000 + 43084011 +4 git-annex 0x000000010df0bc86 0x10b5e6000 + 43146374 +5 git-annex 0x000000010df0c5e0 0x10b5e6000 + 43148768 +6 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +7 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 3 Crashed: +0 libsystem_c.dylib 0x00007fff86ae0bf9 pthread_mutex_lock + 20 +1 H 0x000000010e9fd29f gnutls_system_mutex_lock + 12 +2 H 0x000000010ea7fa29 wrap_nettle_rnd_refresh + 20 +3 H 0x000000010e9fee89 gnutls_deinit + 42 +4 git-annex 0x000000010caf0a3a 0x10b5e6000 + 22063674 + +Thread 4: +0 libsystem_kernel.dylib 0x00007fff93140d2a kevent64 + 10 +1 git-annex 0x000000010deab5fa 0x10b5e6000 + 42751482 + +Thread 5: +0 libsystem_kernel.dylib 0x00007fff931400fa __psynch_cvwait + 10 +1 libsystem_c.dylib 0x00007fff86adffe9 _pthread_cond_wait + 869 +2 git-annex 0x000000010df20179 0x10b5e6000 + 43229561 +3 git-annex 0x000000010defc8eb 0x10b5e6000 + 43084011 +4 git-annex 0x000000010df0bc86 0x10b5e6000 + 43146374 +5 git-annex 0x000000010df0c5e0 0x10b5e6000 + 43148768 +6 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +7 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 6:: Dispatch queue: com.apple.libdispatch-manager +0 libsystem_kernel.dylib 0x00007fff93140d16 kevent + 10 +1 libdispatch.dylib 0x00007fff8e6fedea _dispatch_mgr_invoke + 883 +2 libdispatch.dylib 0x00007fff8e6fe9ee _dispatch_mgr_thread + 54 + +Thread 7: +0 libsystem_kernel.dylib 0x00007fff9313e686 mach_msg_trap + 10 +1 libsystem_kernel.dylib 0x00007fff9313dc42 mach_msg + 70 +2 com.apple.CoreFoundation 0x00007fff8c1e2233 __CFRunLoopServiceMachPort + 195 +3 com.apple.CoreFoundation 0x00007fff8c1e7916 __CFRunLoopRun + 1078 +4 com.apple.CoreFoundation 0x00007fff8c1e70e2 CFRunLoopRunSpecific + 290 +5 com.apple.CoreFoundation 0x00007fff8c1f5dd1 CFRunLoopRun + 97 +6 git-annex 0x000000010c72b3ec 0x10b5e6000 + 18109420 +7 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +8 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 8: +0 libsystem_kernel.dylib 0x00007fff9313e686 mach_msg_trap + 10 +1 libsystem_kernel.dylib 0x00007fff9313dc42 mach_msg + 70 +2 com.apple.CoreFoundation 0x00007fff8c1e2233 __CFRunLoopServiceMachPort + 195 +3 com.apple.CoreFoundation 0x00007fff8c1e7916 __CFRunLoopRun + 1078 +4 com.apple.CoreFoundation 0x00007fff8c1e70e2 CFRunLoopRunSpecific + 290 +5 com.apple.CoreFoundation 0x00007fff8c1f5dd1 CFRunLoopRun + 97 +6 git-annex 0x000000010c72b3ec 0x10b5e6000 + 18109420 +7 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +8 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 9: +0 libsystem_kernel.dylib 0x00007fff9313e686 mach_msg_trap + 10 +1 libsystem_kernel.dylib 0x00007fff9313dc42 mach_msg + 70 +2 com.apple.CoreFoundation 0x00007fff8c1e2233 __CFRunLoopServiceMachPort + 195 +3 com.apple.CoreFoundation 0x00007fff8c1e7916 __CFRunLoopRun + 1078 +4 com.apple.CoreFoundation 0x00007fff8c1e70e2 CFRunLoopRunSpecific + 290 +5 com.apple.CoreFoundation 0x00007fff8c1f5dd1 CFRunLoopRun + 97 +6 git-annex 0x000000010c72b3ec 0x10b5e6000 + 18109420 +7 libsystem_c.dylib 0x00007fff86adb7a2 _pthread_start + 327 +8 libsystem_c.dylib 0x00007fff86ac81e1 thread_start + 13 + +Thread 3 crashed with X86 Thread State (64-bit): + rax: 0x000000010eaaca28 rbx: 0x00007f9dc38000c0 rcx: 0x000000010f87ce00 rdx: 0x000000010e3c28f0 + rdi: 0x0000000000000000 rsi: 0x001c4500001c4500 rbp: 0x000000010f87ce10 rsp: 0x000000010f87cdd0 + r8: 0x0000000000002060 r9: 0x000000010f87ce00 r10: 0x000000010eabf328 r11: 0x000000010e9fee5f + r12: 0x000000010f5585d8 r13: 0x000000010e3c2798 r14: 0x0000000000000000 r15: 0x000000010f548140 + rip: 0x00007fff86ae0bf9 rfl: 0x0000000000010202 cr2: 0x0000000000000000 +Logical CPU: 0 + +Binary Images: + 0x10b5e6000 - 0x10e08cff7 +git-annex (0) <2C4C13B3-4830-322A-A144-9E51B386EB1E> /Applications/git-annex.app/Contents/MacOS/bundle/git-annex + 0x10e85a000 - 0x10e957ff7 +E (22.3) <47B09CB2-C636-3024-8B55-6040F7829B4C> /Applications/git-annex.app/Contents/MacOS/bundle/E + 0x10e990000 - 0x10e9a4fff +F (0) /Applications/git-annex.app/Contents/MacOS/bundle/F + 0x10e9ab000 - 0x10e9d8ff7 +G (0) /Applications/git-annex.app/Contents/MacOS/bundle/G + 0x10e9de000 - 0x10eaabfdf +H (0) <29C3AFF5-8EFB-3A16-81F6-0DA6CF2675A6> /Applications/git-annex.app/Contents/MacOS/bundle/H + 0x10eadd000 - 0x10eaefff7 +B (43) <2A1551E8-A272-3DE5-B692-955974FE1416> /Applications/git-annex.app/Contents/MacOS/bundle/B + 0x10eaf7000 - 0x10ebecfff +D (34) /Applications/git-annex.app/Contents/MacOS/bundle/D + 0x10ec01000 - 0x10ed1992f +I (532.2) <90D31928-F48D-3E37-874F-220A51FD9E37> /Applications/git-annex.app/Contents/MacOS/bundle/I + 0x10ed3d000 - 0x10ef3dfff +S (491.11.3) <5783D305-04E8-3D17-94F7-1CEAFA975240> /Applications/git-annex.app/Contents/MacOS/bundle/S + 0x10f048000 - 0x10f06dff7 +Z (26) /Applications/git-annex.app/Contents/MacOS/bundle/Z + 0x10f0a1000 - 0x10f109ff7 +0A (65.1) <20E31B90-19B9-3C2A-A9EB-474E08F9FE05> /Applications/git-annex.app/Contents/MacOS/bundle/0A + 0x10f163000 - 0x10f1ccfff +0B (56) /Applications/git-annex.app/Contents/MacOS/bundle/0B + 0x10f235000 - 0x10f248fff +T (0) /Applications/git-annex.app/Contents/MacOS/bundle/T + 0x10f257000 - 0x10f264ff7 +U (0) /Applications/git-annex.app/Contents/MacOS/bundle/U + 0x10f26f000 - 0x10f291ff7 +V (0) <51B317C7-94CC-3C58-B515-924BB3AF0BCC> /Applications/git-annex.app/Contents/MacOS/bundle/V + 0x10f29b000 - 0x10f2a8ff7 +W (0) <91CF16BE-027F-3FE6-B1EE-6B8BFD51FC1B> /Applications/git-annex.app/Contents/MacOS/bundle/W + 0x10f2b4000 - 0x10f310fd7 +X (0) <84D934AF-A321-36C0-BBCF-CD3FDAEB0B95> /Applications/git-annex.app/Contents/MacOS/bundle/X + 0x7fff6b1e6000 - 0x7fff6b21a93f dyld (210.2.3) <36CAA36E-72BC-3E48-96D9-B96A2DF77730> /usr/lib/dyld + 0x7fff8652a000 - 0x7fff865d0ff7 com.apple.CoreServices.OSServices (557.6 - 557.6) /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/OSServices.framework/Versions/A/OSServices + 0x7fff865d1000 - 0x7fff865e8fff libGL.dylib (8.9.2) /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGL.dylib + 0x7fff865e9000 - 0x7fff86610fff com.apple.framework.familycontrols (4.1 - 410) <50F5A52C-8FB6-300A-977D-5CFDE4D5796B> /System/Library/PrivateFrameworks/FamilyControls.framework/Versions/A/FamilyControls + 0x7fff86611000 - 0x7fff8663cfff libxslt.1.dylib (11.3) <441776B8-9130-3893-956F-39C85FFA644F> /usr/lib/libxslt.1.dylib + 0x7fff86649000 - 0x7fff86698ff7 libcorecrypto.dylib (106.2) /usr/lib/system/libcorecrypto.dylib + 0x7fff8669d000 - 0x7fff866a3fff com.apple.DiskArbitration (2.5.2 - 2.5.2) /System/Library/Frameworks/DiskArbitration.framework/Versions/A/DiskArbitration + 0x7fff866a4000 - 0x7fff86ac1fff FaceCoreLight (2.4.1) /System/Library/PrivateFrameworks/FaceCoreLight.framework/Versions/A/FaceCoreLight + 0x7fff86ac7000 - 0x7fff86b93ff7 libsystem_c.dylib (825.26) <4C9EB006-FE1F-3F8F-8074-DFD94CF2CE7B> /usr/lib/system/libsystem_c.dylib + 0x7fff86d50000 - 0x7fff86da1ff7 com.apple.SystemConfiguration (1.12.2 - 1.12.2) <581BF463-C15A-363B-999A-E830222FA925> /System/Library/Frameworks/SystemConfiguration.framework/Versions/A/SystemConfiguration + 0x7fff86dee000 - 0x7fff86deefff com.apple.Accelerate.vecLib (3.8 - vecLib 3.8) /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/vecLib + 0x7fff86def000 - 0x7fff86df4fff com.apple.OpenDirectory (10.8 - 151.10) /System/Library/Frameworks/OpenDirectory.framework/Versions/A/OpenDirectory + 0x7fff86df5000 - 0x7fff86df6fff libDiagnosticMessagesClient.dylib (8) <8548E0DC-0D2F-30B6-B045-FE8A038E76D8> /usr/lib/libDiagnosticMessagesClient.dylib + 0x7fff86e0a000 - 0x7fff87201fff libLAPACK.dylib (1073.4) /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libLAPACK.dylib + 0x7fff87622000 - 0x7fff87650ff7 libsystem_m.dylib (3022.6) /usr/lib/system/libsystem_m.dylib + 0x7fff8766c000 - 0x7fff8769dff7 com.apple.DictionaryServices (1.2 - 184.4) /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/DictionaryServices.framework/Versions/A/DictionaryServices + 0x7fff8769e000 - 0x7fff8769efff libkeymgr.dylib (25) /usr/lib/system/libkeymgr.dylib + 0x7fff87732000 - 0x7fff87754ff7 libxpc.dylib (140.43) <70BC645B-6952-3264-930C-C835010CCEF9> /usr/lib/system/libxpc.dylib + 0x7fff87755000 - 0x7fff877d7ff7 com.apple.Heimdal (3.0 - 2.0) /System/Library/PrivateFrameworks/Heimdal.framework/Versions/A/Heimdal + 0x7fff877d8000 - 0x7fff87859fff com.apple.Metadata (10.7.0 - 707.11) <2DD25313-420D-351A-90F1-300E95C970CA> /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/Metadata.framework/Versions/A/Metadata + 0x7fff87cbf000 - 0x7fff87d19fff com.apple.print.framework.PrintCore (8.3 - 387.2) <5BA0CBED-4D80-386A-9646-F835C9805B71> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/PrintCore.framework/Versions/A/PrintCore + 0x7fff87e27000 - 0x7fff87e34ff7 com.apple.NetAuth (4.0 - 4.0) /System/Library/PrivateFrameworks/NetAuth.framework/Versions/A/NetAuth + 0x7fff87f54000 - 0x7fff87f68fff com.apple.speech.synthesis.framework (4.1.12 - 4.1.12) <94EDF2AB-809C-3D15-BED5-7AD45B2A7C16> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/SpeechSynthesis.framework/Versions/A/SpeechSynthesis + 0x7fff87f77000 - 0x7fff87f7dff7 libunwind.dylib (35.1) <21703D36-2DAB-3D8B-8442-EAAB23C060D3> /usr/lib/system/libunwind.dylib + 0x7fff87fab000 - 0x7fff87fabfff com.apple.Accelerate (1.8 - Accelerate 1.8) <6AD48543-0864-3D40-80CE-01F184F24B45> /System/Library/Frameworks/Accelerate.framework/Versions/A/Accelerate + 0x7fff88161000 - 0x7fff88162ff7 libSystem.B.dylib (169.3) <9089D72D-E714-31E1-80C8-698A8E8B05AD> /usr/lib/libSystem.B.dylib + 0x7fff88167000 - 0x7fff88205ff7 com.apple.ink.framework (10.8.2 - 150) <3D8D16A2-7E01-3EA1-B637-83A36D353308> /System/Library/Frameworks/Carbon.framework/Versions/A/Frameworks/Ink.framework/Versions/A/Ink + 0x7fff88222000 - 0x7fff88223ff7 libsystem_sandbox.dylib (220.3) /usr/lib/system/libsystem_sandbox.dylib + 0x7fff88224000 - 0x7fff88228ff7 com.apple.TCC (1.0 - 1) /System/Library/PrivateFrameworks/TCC.framework/Versions/A/TCC + 0x7fff88229000 - 0x7fff88230fff libcopyfile.dylib (89) <876573D0-E907-3566-A108-577EAD1B6182> /usr/lib/system/libcopyfile.dylib + 0x7fff88a6e000 - 0x7fff88a8dff7 libresolv.9.dylib (51) <0882DC2D-A892-31FF-AD8C-0BB518C48B23> /usr/lib/libresolv.9.dylib + 0x7fff88a8e000 - 0x7fff88aa1ff7 libbsm.0.dylib (32) /usr/lib/libbsm.0.dylib + 0x7fff88bbd000 - 0x7fff88bbdfff com.apple.ApplicationServices (45 - 45) /System/Library/Frameworks/ApplicationServices.framework/Versions/A/ApplicationServices + 0x7fff88bce000 - 0x7fff88bf6fff libJPEG.dylib (850) /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libJPEG.dylib + 0x7fff88bf7000 - 0x7fff88bf9fff libquarantine.dylib (52.1) <143B726E-DF47-37A8-90AA-F059CFD1A2E4> /usr/lib/system/libquarantine.dylib + 0x7fff88fe0000 - 0x7fff8933ffff com.apple.Foundation (6.8 - 945.18) <1D7E58E6-FA3A-3CE8-AC85-B9D06B8C0AA0> /System/Library/Frameworks/Foundation.framework/Versions/C/Foundation + 0x7fff89340000 - 0x7fff89575ff7 com.apple.CoreData (106.1 - 407.7) /System/Library/Frameworks/CoreData.framework/Versions/A/CoreData + 0x7fff89576000 - 0x7fff8957dfff libGFXShared.dylib (8.9.2) <398F8D57-EC82-3E13-AC8E-470BE19237D7> /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGFXShared.dylib + 0x7fff895d4000 - 0x7fff8a201fff com.apple.AppKit (6.8 - 1187.39) <199962F0-B06B-3666-8FD5-5C90374BA16A> /System/Library/Frameworks/AppKit.framework/Versions/C/AppKit + 0x7fff8a202000 - 0x7fff8a519ff7 com.apple.CoreServices.CarbonCore (1037.6 - 1037.6) <1E567A52-677F-3168-979F-5FBB0818D52B> /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/CarbonCore.framework/Versions/A/CarbonCore + 0x7fff8a5e0000 - 0x7fff8a5e7fff com.apple.NetFS (5.0 - 4.0) <82E24B9A-7742-3DA3-9E99-ED267D98C05E> /System/Library/Frameworks/NetFS.framework/Versions/A/NetFS + 0x7fff8a5e8000 - 0x7fff8a63fff7 com.apple.ScalableUserInterface (1.0 - 1) /System/Library/Frameworks/QuartzCore.framework/Versions/A/Frameworks/ScalableUserInterface.framework/Versions/A/ScalableUserInterface + 0x7fff8a71b000 - 0x7fff8a767ff7 libauto.dylib (185.4) /usr/lib/libauto.dylib + 0x7fff8a768000 - 0x7fff8a768fff libOpenScriptingUtil.dylib (148.3) /usr/lib/libOpenScriptingUtil.dylib + 0x7fff8a7e7000 - 0x7fff8a808ff7 libCRFSuite.dylib (33) <736ABE58-8DED-3289-A042-C25AF7AE5B23> /usr/lib/libCRFSuite.dylib + 0x7fff8a809000 - 0x7fff8a815fff com.apple.CrashReporterSupport (10.8.3 - 418) /System/Library/PrivateFrameworks/CrashReporterSupport.framework/Versions/A/CrashReporterSupport + 0x7fff8a816000 - 0x7fff8b1a64af com.apple.CoreGraphics (1.600.0 - 332) <5AB32E51-9154-3733-B83B-A9A748652847> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/CoreGraphics.framework/Versions/A/CoreGraphics + 0x7fff8b1a7000 - 0x7fff8b1befff com.apple.CFOpenDirectory (10.8 - 151.10) <10F41DA4-AD54-3F52-B898-588D9A117171> /System/Library/Frameworks/OpenDirectory.framework/Versions/A/Frameworks/CFOpenDirectory.framework/Versions/A/CFOpenDirectory + 0x7fff8b242000 - 0x7fff8b285ff7 com.apple.bom (12.0 - 192) <0BF1F2D2-3648-36B7-BE4B-551A0173209B> /System/Library/PrivateFrameworks/Bom.framework/Versions/A/Bom + 0x7fff8b286000 - 0x7fff8b2c3fef libGLImage.dylib (8.9.2) /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGLImage.dylib + 0x7fff8b2c4000 - 0x7fff8b303ff7 com.apple.QD (3.42.1 - 285.1) <77A20C25-EBB5-341C-A05C-5D458B97AD5C> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/QD.framework/Versions/A/QD + 0x7fff8b304000 - 0x7fff8b39efff libvMisc.dylib (380.6) <714336EA-1C0E-3735-B31C-19DFDAAF6221> /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libvMisc.dylib + 0x7fff8b3b8000 - 0x7fff8b566fff com.apple.QuartzCore (1.8 - 304.3) /System/Library/Frameworks/QuartzCore.framework/Versions/A/QuartzCore + 0x7fff8ba39000 - 0x7fff8ba4cff7 com.apple.LangAnalysis (1.7.0 - 1.7.0) <2F2694E9-A7BC-33C7-B4CF-8EC907DF0FEB> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/LangAnalysis.framework/Versions/A/LangAnalysis + 0x7fff8bd12000 - 0x7fff8bd1cfff com.apple.speech.recognition.framework (4.1.5 - 4.1.5) /System/Library/Frameworks/Carbon.framework/Versions/A/Frameworks/SpeechRecognition.framework/Versions/A/SpeechRecognition + 0x7fff8c0d6000 - 0x7fff8c0d7ff7 libdnsinfo.dylib (453.19) <14202FFB-C3CA-3FCC-94B0-14611BF8692D> /usr/lib/system/libdnsinfo.dylib + 0x7fff8c179000 - 0x7fff8c17efff libcompiler_rt.dylib (30) <08F8731D-5961-39F1-AD00-4590321D24A9> /usr/lib/system/libcompiler_rt.dylib + 0x7fff8c1b2000 - 0x7fff8c39cff7 com.apple.CoreFoundation (6.8 - 744.19) <0F7403CA-2CB8-3D0A-992B-679701DF27CA> /System/Library/Frameworks/CoreFoundation.framework/Versions/A/CoreFoundation + 0x7fff8c39d000 - 0x7fff8c3c4ff7 com.apple.PerformanceAnalysis (1.16 - 16) /System/Library/PrivateFrameworks/PerformanceAnalysis.framework/Versions/A/PerformanceAnalysis + 0x7fff8c3e2000 - 0x7fff8c3e5ff7 libdyld.dylib (210.2.3) /usr/lib/system/libdyld.dylib + 0x7fff8c3e6000 - 0x7fff8c3e8fff libCVMSPluginSupport.dylib (8.9.2) /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libCVMSPluginSupport.dylib + 0x7fff8c3e9000 - 0x7fff8c484fff com.apple.CoreSymbolication (3.0 - 117) <50716F74-41C2-3BB9-AC16-12C4D4C2DD1E> /System/Library/PrivateFrameworks/CoreSymbolication.framework/Versions/A/CoreSymbolication + 0x7fff8c75b000 - 0x7fff8c75bfff com.apple.CoreServices (57 - 57) <9DD44CB0-C644-35C3-8F57-0B41B3EC147D> /System/Library/Frameworks/CoreServices.framework/Versions/A/CoreServices + 0x7fff8cf1f000 - 0x7fff8d094ff7 com.apple.CFNetwork (596.4.3 - 596.4.3) /System/Library/Frameworks/CFNetwork.framework/Versions/A/CFNetwork + 0x7fff8d0ae000 - 0x7fff8d0e4fff libsystem_info.dylib (406.17) <4FFCA242-7F04-365F-87A6-D4EFB89503C1> /usr/lib/system/libsystem_info.dylib + 0x7fff8d0e5000 - 0x7fff8d148ff7 com.apple.audio.CoreAudio (4.1.1 - 4.1.1) <9ACD3AED-6C04-3BBB-AB2A-FC253B16D093> /System/Library/Frameworks/CoreAudio.framework/Versions/A/CoreAudio + 0x7fff8d156000 - 0x7fff8d16cfff com.apple.MultitouchSupport.framework (235.29 - 235.29) <617EC8F1-BCE7-3553-86DD-F857866E1257> /System/Library/PrivateFrameworks/MultitouchSupport.framework/Versions/A/MultitouchSupport + 0x7fff8d16d000 - 0x7fff8d171fff libGIF.dylib (850) /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libGIF.dylib + 0x7fff8d264000 - 0x7fff8d2aeff7 libGLU.dylib (8.9.2) <1B5511FF-1064-3004-A245-972CE5687D37> /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libGLU.dylib + 0x7fff8d2b2000 - 0x7fff8d2dcff7 com.apple.CoreVideo (1.8 - 99.4) /System/Library/Frameworks/CoreVideo.framework/Versions/A/CoreVideo + 0x7fff8d58d000 - 0x7fff8d591fff com.apple.IOSurface (86.0.4 - 86.0.4) <26F01CD4-B76B-37A3-989D-66E8140542B3> /System/Library/Frameworks/IOSurface.framework/Versions/A/IOSurface + 0x7fff8d6de000 - 0x7fff8d78ffff com.apple.LaunchServices (539.9 - 539.9) <07FC6766-778E-3479-8F28-D2C9917E1DD1> /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/LaunchServices.framework/Versions/A/LaunchServices + 0x7fff8d7bf000 - 0x7fff8d80eff7 libFontRegistry.dylib (100) <2E03D7DA-9B8F-31BB-8FB5-3D3B6272127F> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATS.framework/Versions/A/Resources/libFontRegistry.dylib + 0x7fff8d80f000 - 0x7fff8d88fff7 com.apple.ApplicationServices.ATS (332 - 341.1) <39B53565-FA31-3F61-B090-C787C983142E> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATS.framework/Versions/A/ATS + 0x7fff8d94e000 - 0x7fff8d95bfff com.apple.AppleFSCompression (49 - 1.0) <5508344A-2A7E-3122-9562-6F363910A80E> /System/Library/PrivateFrameworks/AppleFSCompression.framework/Versions/A/AppleFSCompression + 0x7fff8d95c000 - 0x7fff8d99fff7 com.apple.RemoteViewServices (2.0 - 80.6) <5CFA361D-4853-3ACC-9EFC-A2AC1F43BA4B> /System/Library/PrivateFrameworks/RemoteViewServices.framework/Versions/A/RemoteViewServices + 0x7fff8dac2000 - 0x7fff8dac8fff libmacho.dylib (829) /usr/lib/system/libmacho.dylib + 0x7fff8dac9000 - 0x7fff8db03ff7 com.apple.GSS (3.0 - 2.0) <970CAE00-1437-3F4E-B677-0FDB3714C08C> /System/Library/Frameworks/GSS.framework/Versions/A/GSS + 0x7fff8db09000 - 0x7fff8db12ff7 com.apple.CommerceCore (1.0 - 26.1) <40A129A8-4E5D-3C7A-B299-8CB203C4C65D> /System/Library/PrivateFrameworks/CommerceKit.framework/Versions/A/Frameworks/CommerceCore.framework/Versions/A/CommerceCore + 0x7fff8db13000 - 0x7fff8db15fff com.apple.TrustEvaluationAgent (2.0 - 23) /System/Library/PrivateFrameworks/TrustEvaluationAgent.framework/Versions/A/TrustEvaluationAgent + 0x7fff8de6c000 - 0x7fff8de6eff7 libunc.dylib (25) <92805328-CD36-34FF-9436-571AB0485072> /usr/lib/system/libunc.dylib + 0x7fff8de6f000 - 0x7fff8de8eff7 com.apple.ChunkingLibrary (2.0 - 133.3) <8BEC9AFB-DCAA-37E8-A5AB-24422B234ECF> /System/Library/PrivateFrameworks/ChunkingLibrary.framework/Versions/A/ChunkingLibrary + 0x7fff8de8f000 - 0x7fff8deeefff com.apple.AE (645.6 - 645.6) <44F403C1-660A-3543-AB9C-3902E02F936F> /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/AE.framework/Versions/A/AE + 0x7fff8deef000 - 0x7fff8dfecfff libsqlite3.dylib (138.1) /usr/lib/libsqlite3.dylib + 0x7fff8e06b000 - 0x7fff8e076ff7 com.apple.bsd.ServiceManagement (2.0 - 2.0) /System/Library/Frameworks/ServiceManagement.framework/Versions/A/ServiceManagement + 0x7fff8e077000 - 0x7fff8e086fff com.apple.opengl (1.8.9 - 1.8.9) <6FD163A7-16CC-3D1F-B4B5-B0FDC4ADBF79> /System/Library/Frameworks/OpenGL.framework/Versions/A/OpenGL + 0x7fff8e087000 - 0x7fff8e092fff com.apple.CommonAuth (3.0 - 2.0) <7A953C1F-8B18-3E46-9BEA-26D9B5B7745D> /System/Library/PrivateFrameworks/CommonAuth.framework/Versions/A/CommonAuth + 0x7fff8e093000 - 0x7fff8e093fff com.apple.Cocoa (6.7 - 19) <1F77945C-F37A-3171-B22E-F7AB0FCBB4D4> /System/Library/Frameworks/Cocoa.framework/Versions/A/Cocoa + 0x7fff8e1f3000 - 0x7fff8e1f4fff libsystem_blocks.dylib (59) /usr/lib/system/libsystem_blocks.dylib + 0x7fff8e23c000 - 0x7fff8e23cffd com.apple.audio.units.AudioUnit (1.9 - 1.9) /System/Library/Frameworks/AudioUnit.framework/Versions/A/AudioUnit + 0x7fff8e23d000 - 0x7fff8e30fff7 com.apple.CoreText (260.0 - 275.16) <5BFC1D67-6A6F-38BC-9D90-9C712684EDAC> /System/Library/Frameworks/CoreText.framework/Versions/A/CoreText + 0x7fff8e310000 - 0x7fff8e31eff7 libkxld.dylib (2050.24.15) /usr/lib/system/libkxld.dylib + 0x7fff8e31f000 - 0x7fff8e38dff7 com.apple.framework.IOKit (2.0.1 - 755.24.1) <04BFB138-8AF4-310A-8E8C-045D8A239654> /System/Library/Frameworks/IOKit.framework/Versions/A/IOKit + 0x7fff8e39f000 - 0x7fff8e525fff libBLAS.dylib (1073.4) /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libBLAS.dylib + 0x7fff8e553000 - 0x7fff8e597fff libcups.2.dylib (327.6) <9C01D012-6F4C-3B69-B614-1B408B0ED4E3> /usr/lib/libcups.2.dylib + 0x7fff8e598000 - 0x7fff8e5a6fff libcommonCrypto.dylib (60027) /usr/lib/system/libcommonCrypto.dylib + 0x7fff8e6fa000 - 0x7fff8e70fff7 libdispatch.dylib (228.23) /usr/lib/system/libdispatch.dylib + 0x7fff8e710000 - 0x7fff8e71eff7 libsystem_network.dylib (77.10) <0D99F24E-56FE-380F-B81B-4A4C630EE587> /usr/lib/system/libsystem_network.dylib + 0x7fff8e71f000 - 0x7fff8e741ff7 com.apple.Kerberos (2.0 - 1) /System/Library/Frameworks/Kerberos.framework/Versions/A/Kerberos + 0x7fff8e788000 - 0x7fff8e797ff7 libxar.1.dylib (105) <370ED355-E516-311E-BAFD-D80633A84BE1> /usr/lib/libxar.1.dylib + 0x7fff8f144000 - 0x7fff8f1d1ff7 com.apple.SearchKit (1.4.0 - 1.4.0) /System/Library/Frameworks/CoreServices.framework/Versions/A/Frameworks/SearchKit.framework/Versions/A/SearchKit + 0x7fff8f24c000 - 0x7fff8f24ffff libRadiance.dylib (850) <62E3F7FB-03E3-3937-A857-AF57A75EAF09> /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libRadiance.dylib + 0x7fff8f533000 - 0x7fff8f7d7ff7 com.apple.CoreImage (8.4.0 - 1.0.1) /System/Library/Frameworks/QuartzCore.framework/Versions/A/Frameworks/CoreImage.framework/Versions/A/CoreImage + 0x7fff8f7d8000 - 0x7fff8f840fff libvDSP.dylib (380.6) /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vecLib.framework/Versions/A/libvDSP.dylib + 0x7fff8f8ab000 - 0x7fff8f8affff libpam.2.dylib (20) /usr/lib/libpam.2.dylib + 0x7fff8fabb000 - 0x7fff8fb28ff7 com.apple.datadetectorscore (4.1 - 269.3) <5775F0DB-87D6-310D-8B03-E2AD729EFB28> /System/Library/PrivateFrameworks/DataDetectorsCore.framework/Versions/A/DataDetectorsCore + 0x7fff8fc60000 - 0x7fff8fcbcff7 com.apple.Symbolication (1.3 - 93) <97F3B1D2-D81D-3F37-87B3-B9A686124CF5> /System/Library/PrivateFrameworks/Symbolication.framework/Versions/A/Symbolication + 0x7fff8fd91000 - 0x7fff8fe6bfff com.apple.backup.framework (1.4.3 - 1.4.3) <6B65C44C-7777-3331-AD9D-438D10AAC777> /System/Library/PrivateFrameworks/Backup.framework/Versions/A/Backup + 0x7fff8fe6c000 - 0x7fff8fe79fff libbz2.1.0.dylib (29) /usr/lib/libbz2.1.0.dylib + 0x7fff8fe89000 - 0x7fff8ffdbfff com.apple.audio.toolbox.AudioToolbox (1.9 - 1.9) <62770C0F-5600-3EF9-A893-8A234663FFF5> /System/Library/Frameworks/AudioToolbox.framework/Versions/A/AudioToolbox + 0x7fff90071000 - 0x7fff90173fff libJP2.dylib (850) <2E43216C-3A5A-3693-820C-38B360698FA0> /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libJP2.dylib + 0x7fff90ab4000 - 0x7fff90b79ff7 com.apple.coreui (2.0 - 181.1) <83D2C92D-6842-3C9D-9289-39D5B4554C3A> /System/Library/PrivateFrameworks/CoreUI.framework/Versions/A/CoreUI + 0x7fff90e1a000 - 0x7fff90e1bfff liblangid.dylib (116) <864C409D-D56B-383E-9B44-A435A47F2346> /usr/lib/liblangid.dylib + 0x7fff90f20000 - 0x7fff90fddff7 com.apple.ColorSync (4.8.0 - 4.8.0) <6CE333AE-EDDB-3768-9598-9DB38041DC55> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ColorSync.framework/Versions/A/ColorSync + 0x7fff90fde000 - 0x7fff9105dff7 com.apple.securityfoundation (6.0 - 55115.4) <8676E0DF-295F-3690-BDAA-6C9C1D210B88> /System/Library/Frameworks/SecurityFoundation.framework/Versions/A/SecurityFoundation + 0x7fff9105e000 - 0x7fff910b4fff com.apple.HIServices (1.20 - 417) /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/HIServices.framework/Versions/A/HIServices + 0x7fff910b5000 - 0x7fff910d6fff com.apple.Ubiquity (1.2 - 243.15) /System/Library/PrivateFrameworks/Ubiquity.framework/Versions/A/Ubiquity + 0x7fff910de000 - 0x7fff91133ff7 libTIFF.dylib (850) /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libTIFF.dylib + 0x7fff9125c000 - 0x7fff9127cfff libPng.dylib (850) <203C43BF-FAD3-3CCB-81D5-F2770E36338B> /System/Library/Frameworks/ImageIO.framework/Versions/A/Resources/libPng.dylib + 0x7fff9127f000 - 0x7fff91398fff com.apple.ImageIO.framework (3.2.1 - 850) /System/Library/Frameworks/ImageIO.framework/Versions/A/ImageIO + 0x7fff9139f000 - 0x7fff913b6fff com.apple.GenerationalStorage (1.1 - 132.3) /System/Library/PrivateFrameworks/GenerationalStorage.framework/Versions/A/GenerationalStorage + 0x7fff91582000 - 0x7fff91586fff libCoreVMClient.dylib (32.3) /System/Library/Frameworks/OpenGL.framework/Versions/A/Libraries/libCoreVMClient.dylib + 0x7fff91587000 - 0x7fff915bdfff com.apple.DebugSymbols (98 - 98) <14E788B1-4EB2-3FD7-934B-849534DFC198> /System/Library/PrivateFrameworks/DebugSymbols.framework/Versions/A/DebugSymbols + 0x7fff915cd000 - 0x7fff915d5fff liblaunch.dylib (442.26.2) <2F71CAF8-6524-329E-AC56-C506658B4C0C> /usr/lib/system/liblaunch.dylib + 0x7fff915d6000 - 0x7fff915e1fff libsystem_notify.dylib (98.5) /usr/lib/system/libsystem_notify.dylib + 0x7fff91650000 - 0x7fff917ebfef com.apple.vImage (6.0 - 6.0) /System/Library/Frameworks/Accelerate.framework/Versions/A/Frameworks/vImage.framework/Versions/A/vImage + 0x7fff917ec000 - 0x7fff917f4ff7 libsystem_dnssd.dylib (379.38.1) /usr/lib/system/libsystem_dnssd.dylib + 0x7fff9182d000 - 0x7fff91938fff libFontParser.dylib (84.6) <96C42E49-79A6-3475-B5E4-6A782599A6DA> /System/Library/Frameworks/ApplicationServices.framework/Versions/A/Frameworks/ATS.framework/Versions/A/Resources/libFontParser.dylib + 0x7fff919d8000 - 0x7fff919ddfff libcache.dylib (57) <65187C6E-3FBF-3EB8-A1AA-389445E2984D> /usr/lib/system/libcache.dylib + 0x7fff919de000 - 0x7fff919defff com.apple.vecLib (3.8 - vecLib 3.8) <794317C7-4E38-338A-A874-5E18001C8503> /System/Library/Frameworks/vecLib.framework/Versions/A/vecLib + 0x7fff919df000 - 0x7fff91cb0ff7 com.apple.security (7.0 - 55179.13) /System/Library/Frameworks/Security.framework/Versions/A/Security + 0x7fff91d3f000 - 0x7fff9206ffff com.apple.HIToolbox (2.0 - 626.1) <656D08C2-9068-3532-ABDD-32EC5057CCB2> /System/Library/Frameworks/Carbon.framework/Versions/A/Frameworks/HIToolbox.framework/Versions/A/HIToolbox + 0x7fff92084000 - 0x7fff920deff7 com.apple.opencl (2.2.19 - 2.2.19) <3C7DFB2C-B3F9-3447-A1FC-EAAA42181A6E> /System/Library/Frameworks/OpenCL.framework/Versions/A/OpenCL + 0x7fff9216c000 - 0x7fff9216dff7 libremovefile.dylib (23.2) <6763BC8E-18B8-3AD9-8FFA-B43713A7264F> /usr/lib/system/libremovefile.dylib + 0x7fff9312e000 - 0x7fff93149ff7 libsystem_kernel.dylib (2050.24.15) /usr/lib/system/libsystem_kernel.dylib + 0x7fff9314d000 - 0x7fff9326dfff com.apple.desktopservices (1.7.4 - 1.7.4) /System/Library/PrivateFrameworks/DesktopServicesPriv.framework/Versions/A/DesktopServicesPriv + +External Modification Summary: + Calls made by other processes targeting this process: + task_for_pid: 1 + thread_create: 0 + thread_set_state: 0 + Calls made by this process: + task_for_pid: 0 + thread_create: 0 + thread_set_state: 0 + Calls made by all processes on this machine: + task_for_pid: 168404 + thread_create: 1 + thread_set_state: 0 + +VM Region Summary: +ReadOnly portion of Libraries: Total=109.3M resident=31.8M(29%) swapped_out_or_unallocated=77.5M(71%) +Writable regions: Total=90.9M written=16.1M(18%) resident=17.5M(19%) swapped_out=0K(0%) unallocated=73.4M(81%) + +REGION TYPE VIRTUAL +=========== ======= +MALLOC 62.5M +MALLOC guard page 48K +STACK GUARD 56.0M +Stack 12.6M +VM_ALLOCATE 12.0M +__DATA 13.8M +__IMAGE 528K +__LINKEDIT 58.6M +__TEXT 134.3M +__UNICODE 544K +shared memory 308K +=========== ======= +TOTAL 351.2M + +Model: MacBookPro10,1, BootROM MBP101.00EE.B03, 4 processors, Intel Core i7, 2.8 GHz, 16 GB, SMC 2.3f35 +Graphics: Intel HD Graphics 4000, Intel HD Graphics 4000, Built-In, 512 MB +Graphics: NVIDIA GeForce GT 650M, NVIDIA GeForce GT 650M, PCIe, 1024 MB +Memory Module: BANK 0/DIMM0, 8 GB, DDR3, 1600 MHz, 0x80AD, 0x484D5434314753364D465238432D50422020 +Memory Module: BANK 1/DIMM0, 8 GB, DDR3, 1600 MHz, 0x80AD, 0x484D5434314753364D465238432D50422020 +AirPort: spairport_wireless_card_type_airport_extreme (0x14E4, 0xEF), Broadcom BCM43xx 1.0 (5.106.98.100.17) +Bluetooth: Version 4.1.4f2 12041, 2 service, 18 devices, 1 incoming serial ports +Network Service: Wi-Fi, AirPort, en0 +Serial ATA Device: APPLE SSD SM768E, 751.28 GB +USB Device: hub_device, 0x8087 (Intel Corporation), 0x0024, 0x1a100000 / 2 +USB Device: FaceTime HD Camera (Built-in), apple_vendor_id, 0x8510, 0x1a110000 / 3 +USB Device: USB Receiver, 0x046d (Logitech Inc.), 0xc52b, 0x14200000 / 1 +USB Device: hub_device, 0x8087 (Intel Corporation), 0x0024, 0x1d100000 / 2 +USB Device: hub_device, 0x0424 (SMSC), 0x2512, 0x1d180000 / 3 +USB Device: Apple Internal Keyboard / Trackpad, apple_vendor_id, 0x0262, 0x1d182000 / 5 +USB Device: BRCM20702 Hub, 0x0a5c (Broadcom Corp.), 0x4500, 0x1d181000 / 4 +USB Device: Bluetooth USB Host Controller, apple_vendor_id, 0x8286, 0x1d181300 / 6 + +# End of transcript or log. +"""]] diff --git a/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__/comment_1_97abb8442329d19c9687002f43afac74._comment b/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__/comment_1_97abb8442329d19c9687002f43afac74._comment new file mode 100644 index 0000000000..4dcc5412c7 --- /dev/null +++ b/doc/bugs/git-annex_quit_unexpectedly___40__macosx__41__/comment_1_97abb8442329d19c9687002f43afac74._comment @@ -0,0 +1,23 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-26T19:51:48Z" + content=""" +So this is a crash in the gnutls library used for XMPP. Someone else using OSX reported a similar crash to me by email, reproducible reliably by setting up xmpp with google. This is great debugging info: + +
+Thread 3 Crashed:
+0   libsystem_c.dylib               0x00007fff86ae0bf9 pthread_mutex_lock + 20
+1   H                               0x000000010e9fd29f gnutls_system_mutex_lock + 12
+2   H                               0x000000010ea7fa29 wrap_nettle_rnd_refresh + 20
+3   H                               0x000000010e9fee89 gnutls_deinit + 42
+4   git-annex                       0x000000010caf0a3a 0x10b5e6000 + 22063674
+
+ +Looks like `gnutls_deinit` was called and it crashed there, inside pthread code. So I think git-annex has already managed to connect to the XMPP server (to test it) and the cleanup is where it's crashing. + +This is the second time I have seen a gnutls-related crash using XMPP. The other one was tracked down by John Millikin to a resource allocation bug in haskell-gnutls and fixed. + +I have written a test case that reproduces the problem -- just forking a dozen threads that each try to connect to the google xmpp server and then close the connection. After a dozen or so succeed, one will reliably cause a segfault. Forwarded this test case to John. +"""]] diff --git a/doc/bugs/git-annex_sync_may_fail_when_the_directory_I__39__m_in_disepeared.mdwn b/doc/bugs/git-annex_sync_may_fail_when_the_directory_I__39__m_in_disepeared.mdwn new file mode 100644 index 0000000000..fe50125ee6 --- /dev/null +++ b/doc/bugs/git-annex_sync_may_fail_when_the_directory_I__39__m_in_disepeared.mdwn @@ -0,0 +1,14 @@ +### Please describe the problem. +While running git annex sync, it may failed if one did run it on some deep directory, and the sync remove this direcory. + +### What version of git-annex are you using? On what operating system? + +git-annex version: 4.20130815 +build flags: Assistant Webapp Pairing Testsuite S3 WebDAV Inotify DBus XMPP +local repository version: 3 +default repository version: 3 +supported repository versions: 3 4 +upgrade supported from repository versions: 0 1 2 + +on Debian Gnu Linux sid + diff --git a/doc/bugs/git_annex_add_error_with_Andrew_File_System/comment_2_faefcf69bd61c47566131cb31b78cc19._comment b/doc/bugs/git_annex_add_error_with_Andrew_File_System/comment_2_faefcf69bd61c47566131cb31b78cc19._comment new file mode 100644 index 0000000000..a2301499cb --- /dev/null +++ b/doc/bugs/git_annex_add_error_with_Andrew_File_System/comment_2_faefcf69bd61c47566131cb31b78cc19._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-24T19:48:46Z" + content=""" +I'm confused by this bug report, because it seems to me I already fixed this same problem in commit a64106dcef5c5aad825662ef115cb2a1cc6985a8. There the problem was that encfs in paranoia mode doesn't support hard links. So I made it detect when createLink fails, and fall back to a code path that doesn't need hard links. + +Can you re-check the version you have, and perhaps try with a current daily build? +"""]] diff --git a/doc/bugs/http_git_annex_404_retry.mdwn b/doc/bugs/http_git_annex_404_retry.mdwn new file mode 100644 index 0000000000..38ab860bbd --- /dev/null +++ b/doc/bugs/http_git_annex_404_retry.mdwn @@ -0,0 +1,16 @@ +A repository like http://annex.debconf.org/debconf-share/ has a git repo +published via http. When getting files from such a repo, git-annex tries +two urls. One url would be used by a bare repo, and the other by a non-bare +repo. (This is due to the directory hashing change.) Result is every file +download from a non-bare http repo starts with a 404 and then it retries +with the right url. + +Since git-annex already downloads the .git/config to find the uuid of the +http repo, it could also look at it to see if the repo is bare. If not, +set a flag, and try the two urls in reverse order, which would almost +always avoid this 404 problem. + +(The real solution is probably to flag day and get rid of the old-style +directory hashing, but that's been discussed elsewhere.) + +--[[Joey]] diff --git a/doc/bugs/immediately_drops_files/comment_1_9ef6e694ef8a8eee7a42f88554475db7._comment b/doc/bugs/immediately_drops_files/comment_1_9ef6e694ef8a8eee7a42f88554475db7._comment new file mode 100644 index 0000000000..9d630e385e --- /dev/null +++ b/doc/bugs/immediately_drops_files/comment_1_9ef6e694ef8a8eee7a42f88554475db7._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T16:41:04Z" + content=""" +You are running the git annex assistant, which takes care of getting and dropping files as it's configured to do, and you are then going in and manually running `git annex get`. If the assistant sees a file's content has appeared, and that file is in a directory that it has been configured to not want the content of file in (the `archive` directory by default), it will immediately try to drop it. + +The only thing I don't understand is why the number of `..` in the symlink would change. +"""]] diff --git a/doc/bugs/immediately_drops_files/comment_2_76e4f8b73ab60b2540dd2a3e5379791d._comment b/doc/bugs/immediately_drops_files/comment_2_76e4f8b73ab60b2540dd2a3e5379791d._comment new file mode 100644 index 0000000000..274090c63e --- /dev/null +++ b/doc/bugs/immediately_drops_files/comment_2_76e4f8b73ab60b2540dd2a3e5379791d._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-24T16:41:47Z" + content=""" +BTW if you don't want the assistant to automatically get and drop files in your repository, you can edit the repository in the webapp and select \"manual mode\". +"""]] diff --git a/doc/bugs/immediately_drops_files/comment_3_788db083f5ba2e5589c3b952203ec954._comment b/doc/bugs/immediately_drops_files/comment_3_788db083f5ba2e5589c3b952203ec954._comment new file mode 100644 index 0000000000..9253caa1aa --- /dev/null +++ b/doc/bugs/immediately_drops_files/comment_3_788db083f5ba2e5589c3b952203ec954._comment @@ -0,0 +1,21 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnSenxKyE_2Z6Wb-EBMO8FciyRywjx1ZiQ" + nickname="Walter" + subject="comment 3" + date="2013-08-24T21:59:12Z" + content=""" +I have all of my repositories set to either manual (all the computers), or full backup (the usb drive and s3). +So, this is happening in a manual repository. + + +Also, I still don't understand why it would be confused over the annex.numcopies setting (why does it claim it needs 2 copies, when numcopies is 1?) + +I just tested between desktop and laptop. File is also present in s3. + +File on desktop. Copy to laptop --> desktop drops (why? both are set to manual, and both have the other set as manual as well) + +Get on desktop. Works, it gets it from laptop. But then, desktop makes laptop drop it (why? again, both are manual repositories) + + + +"""]] diff --git a/doc/bugs/inconsistent_use_of_SI_prefixes.mdwn b/doc/bugs/inconsistent_use_of_SI_prefixes.mdwn new file mode 100644 index 0000000000..3168fd36c6 --- /dev/null +++ b/doc/bugs/inconsistent_use_of_SI_prefixes.mdwn @@ -0,0 +1,55 @@ +### Please describe the problem. + +`git annex status` inconsistently uses mebi (SI) and giga (informal) prefixes. + +### What steps will reproduce the problem? + +Example: + +[[!format txt """ +anarcat@marcos:mp3$ git annex status +supported backends: SHA256E SHA1E SHA512E SHA224E SHA384E SHA256 SHA1 SHA512 SHA224 SHA384 WORM URL +supported remote types: git S3 bup directory rsync web glacier hook +repository mode: direct +trusted repositories: 0 +semitrusted repositories: 2 + 00000000-0000-0000-0000-000000000001 -- web + b7802161-c984-4c9f-8d05-787a29c41cfe -- here (anarcat@marcos:/srv/mp3) +untrusted repositories: 0 +transfers in progress: none +available local disk space: 31.93 gigabytes (+1 megabyte reserved) +local annex keys: 19913 +local annex size: 111.08 gigabytes +known annex keys: 20085 +known annex size: 111.38 gigabytes +bloom filter size: 16 mebibytes (3.1% full) +backend usage: + SHA256E: 39998 +"""]] + +Notice `mebibytes` and `gigabytes`. It is unclear whether those are gigabytes (1000^3) or gibibytes (1024^3). + +### What version of git-annex are you using? On what operating system? + +4.20130802~bpo70+2, Debian wheezy. + +### Please provide any additional information below. + +nil. + +> git-annex consistently uses the powers of ten units +> for disk storage sizes. Its "gigabyte" is the SI gigabyte. +> +> It uses the absurdly named units for powers of 2 for memory sizes, +> in the few places it deals with memory (probably only the above bloom +> filter size number). +> +> AFAIK I am complying with all relevant standards and best practices. +> Even though I consider them rather dumb, as is clear if you +> [read the opionated source code I wrote to handle this](). +> +> If git-annex used "gibibyte", the numbers it reports for disk size +> would not match the numbers disk vendors and most tools use. +> +> [[bug_is_in_world_not_in_git-annex|done]] --[[Joey]] + diff --git a/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange.mdwn b/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange.mdwn index 7811ef6bf0..1dca843466 100644 --- a/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange.mdwn +++ b/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange.mdwn @@ -36,3 +36,5 @@ Ubuntu 12.04 LTS # End of transcript or log. """]] + +> [[fixed|done]] --[[Joey]] diff --git a/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange/comment_8_c53ce2274388711ffbde1595b64f932b._comment b/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange/comment_8_c53ce2274388711ffbde1595b64f932b._comment new file mode 100644 index 0000000000..b4ef6b5c7e --- /dev/null +++ b/doc/bugs/non-annexed_file_changed_to_annexed_on_typechange/comment_8_c53ce2274388711ffbde1595b64f932b._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 8" + date="2013-08-22T17:25:48Z" + content=""" +Yay for the git-annex community for another fine bug testcase! + +The problem is simply that it assumes any typechanged link was an annexed file, and doesn't doublecheck. Fixing that now.. +"""]] diff --git a/doc/bugs/test_suite_failure_on_samba_mount/comment_1_e074b20801b921ee2661025a050a8af2._comment b/doc/bugs/test_suite_failure_on_samba_mount/comment_1_e074b20801b921ee2661025a050a8af2._comment new file mode 100644 index 0000000000..623028c80c --- /dev/null +++ b/doc/bugs/test_suite_failure_on_samba_mount/comment_1_e074b20801b921ee2661025a050a8af2._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="seems like a general git problem" + date="2013-08-24T19:55:56Z" + content=""" +\"unable to create temporary sha1 filename\" is a git error message. I don't actually see any git-annex failure here, just a git failure that seems to lead to a cascade of other failures. + +I'm not sure if the \"/media/freebox/.t/tmprepo3/.git: No such file or directory\" is because git clone has failed due to the other errors, or if git clone somehow failed to set up the .git directory. + +It would probably be helpful to have a play around with git on this filesystem and see what breaks. Alternatively, you can use git-annex with `--debug` to see the git commands it's running that fail, and try them yourself and perhaps strace or gdb them or something to see where they go wrong. +"""]] diff --git a/doc/copies/comment_1_af9bee33777fb8a187b714fc8c5fb11d._comment b/doc/copies/comment_1_af9bee33777fb8a187b714fc8c5fb11d._comment new file mode 100644 index 0000000000..45e5722604 --- /dev/null +++ b/doc/copies/comment_1_af9bee33777fb8a187b714fc8c5fb11d._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="See also section on backups in walthroug" + date="2013-08-25T05:37:04Z" + content=""" +See also [walthrough/backups](/walkthrough/backups/) for some details about copies. +"""]] diff --git a/doc/design/assistant/blog/day_311__Windows_porting/comment_1_8e738f54a72557bee1e19970472b925c._comment b/doc/design/assistant/blog/day_311__Windows_porting/comment_1_8e738f54a72557bee1e19970472b925c._comment new file mode 100644 index 0000000000..9f4bf2284a --- /dev/null +++ b/doc/design/assistant/blog/day_311__Windows_porting/comment_1_8e738f54a72557bee1e19970472b925c._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawlpSOjMH7Iaz56v6Pr9KCFSpbvMXvg-y9o" + nickname="Dominik" + subject="That's amazing..." + date="2013-08-17T11:18:05Z" + content=""" +...so pretty soon my bi-directional Mac <-> Win Git-Annex-Assitant sync via rsync.net will work without a VM on Windows :-) +"""]] diff --git a/doc/design/assistant/blog/day_312__DebConf_midpoint.mdwn b/doc/design/assistant/blog/day_312__DebConf_midpoint.mdwn new file mode 100644 index 0000000000..8e07584326 --- /dev/null +++ b/doc/design/assistant/blog/day_312__DebConf_midpoint.mdwn @@ -0,0 +1,30 @@ +Wow, 11 days off! I was busy with first dentistry and then DebConf. + +Yesterday I [visited CERN](http://joeyh.name/blog/entry/words_fail_me/) and +got to talk with some of their IT guys about how they manage their tens of +petabytes of data. Interested to hear they also have the equivilant of a +per-subdirectory annex.numcopies setting. OTOH, they have half a billion +more files than git's index file is likely to be able to scale to support. ;) + +Pushed a release out today despite not having many queued changes. +Also, I got git-annex migrated to Debian testing, and so was also +able to update the wheezy backport to a just 2 week old version. + +Today is also the last day of the [campaign](https://campaign.joeyh.name/)! + +---- + +There has been a ton of discussion about git-annex here at DebConf, +including 3 BoF sessions that mostly focused on it, amoung other git stuff. +Also, RichiH will be presenting his +"[Gitify Your Life](http://penta.debconf.org/dc13_schedule/events/1025.en.html)" +talk on Friday; you can catch it on the [live stream](http://blog.debconf.org/blog/2013/08/14#hl_dc13_recordings). + +I've also had a continual stream of in-person bug and feature requests. +(Mostly features.) +These have been added to the wiki and I look forward to working on that +backlog when I get home. + +As for coding, I am doing little here, but I do have a branch cooking that +adds some options to `git annex import` to control handling of duplicate +files. diff --git a/doc/design/assistant/blog/day_313__back.mdwn b/doc/design/assistant/blog/day_313__back.mdwn new file mode 100644 index 0000000000..28c7f971d4 --- /dev/null +++ b/doc/design/assistant/blog/day_313__back.mdwn @@ -0,0 +1,34 @@ +Back home. I have some 170 messages of backlog to attend to. Rather than +digging into that on my first day back, I spent some time implementing some +new features. + +`git annex import` has grown three options that help managing importing of +duplicate files in different ways. I started work on that last week, but +didn't have time to find a way to avoid the `--deduplicate` option +checksumming each imported file twice. Unfortunately, I have still not +found a way I'm happy with, so it works but is not as efficient as it could +be. + +`git annex mirror` is a new command suggested to me by someone at DebConf +(they don't seem to have filed the requested todo). It arranges for two +repositories to contain the same set of files, as much as possible (when +numcopies allows). So for example, `git annex mirror --to otherdrive` +will make the otherdrive remote have the same files present and not present +as the local repository. + +I am thinking about expanding `git annex sync` with an option to also sync +data. I know some find it confusing that it only syncs the git metadata +and not the file contents. That still seems to me to be the best and most +flexible behavior, and not one I want to change in any case since +it would be most unexpected if `git annex sync` downloaded a lot of stuff +you don't want. But I can see making `git annex sync --data` download +all the file contents it can, as well as uploading all available file +contents to each remote it syncs with. And `git annex sync --data --auto` +limit that to only the preferred content. Although perhaps +these command lines are too long to be usable? + +---- + +With the campaign more or less over, I only have a little over a week +before it's time to dive into the first big item on the roadmap. Hope +to be through the backlog by then. diff --git a/doc/design/assistant/blog/day_313__back/comment_1_fbf3fdf9688c18156753d446facd942d._comment b/doc/design/assistant/blog/day_313__back/comment_1_fbf3fdf9688c18156753d446facd942d._comment new file mode 100644 index 0000000000..7230a15682 --- /dev/null +++ b/doc/design/assistant/blog/day_313__back/comment_1_fbf3fdf9688c18156753d446facd942d._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="GLITTAH" + ip="77.247.181.162" + subject="comment 1" + date="2013-08-20T22:42:46Z" + content=""" +I wouldn't worry about the commands being too long. If they're used often enough, they'll get aliased. + +alias GASDA='git annex sync --data --auto' +"""]] diff --git a/doc/design/assistant/blog/day_314__quvi.mdwn b/doc/design/assistant/blog/day_314__quvi.mdwn new file mode 100644 index 0000000000..3c38e427d8 --- /dev/null +++ b/doc/design/assistant/blog/day_314__quvi.mdwn @@ -0,0 +1,27 @@ +Made some good progress on the backlog today. Fixed some bugs, applied some +patches. Noticing that without me around, things still get followed up +on, to a point, for example incomplete test cases for bugs get corrected so +they work. This is a very good thing. Community! + +I had to stop going through the backlog when I got to one message from +Anarcat mentioning [quvi](http://quvi.sourceforge.net/). That turns +out to be just what is needed to implement the often-requested feature +of `git-annex addurl` supporting YouTube and other similar sites. So I +spent the rest of the day making that work. For example: + +
+% git annex addurl --fast 'http://www.youtube.com/watch?v=1mxPFHBCfuU&list=PL4F80C7D2DC8D9B6C&index=1'
+addurl Star_Wars_X_Wing__Seth_Green__Clare_Grant__and_Mike_Lamond_Join_Wil_on_TableTop_SE2E09.webm ok
+
+ +Yes, that got the video title and used it as the filename, and yes, +I can commit this file and run `git annex get` later, and it will be +able to go download the video! I can even use `git annex fsck --fast` +to make sure YouTube still has my videos. Awesome. + +The great thing about quvi is it takes the url to a video webpage, and +returns an url that can be used to download the actual video file. So it +simplifies ugly flash videos as far out of existence as is possible. +However, since the direct url to the video file may not keep working for long. +addurl actually records the page's url, with an added indication that quvi +should be used to get it. diff --git a/doc/design/assistant/blog/day_315__backlog.mdwn b/doc/design/assistant/blog/day_315__backlog.mdwn new file mode 100644 index 0000000000..ec0ee33be3 --- /dev/null +++ b/doc/design/assistant/blog/day_315__backlog.mdwn @@ -0,0 +1,12 @@ +After a couple days plowing through it, my backlog is down to 30 messages +from 150. And most of what's left is legitimate bugs and todo items. + +Spent a while today on an ugly file descriptor leak in the assistant's +local pairing listener. This was an upstream bug in the network-multicast +library, so while I've written a patch to fix it, the fix isn't quite +deployed yet. The file descriptor leak happens when the assistant is +running and there is no network interface that supports multicast. +I was able to reproduce it by just disconnecting from wifi. + +Meanwhile, guilhem has been working on patches that promise to massively +speed up `git annex unused`! I will be reviewing them tonight. diff --git a/doc/design/assistant/blog/day_316__day_off.mdwn b/doc/design/assistant/blog/day_316__day_off.mdwn new file mode 100644 index 0000000000..b26118b17b --- /dev/null +++ b/doc/design/assistant/blog/day_316__day_off.mdwn @@ -0,0 +1,6 @@ +Today was a day off, really. However, I have a job running to try to +build get a version of ghc-android that works on newer Android releases. + +Also, guilhem's `git annex unused` speedup patch landed. The results are +extrordinary -- speedups on the order of 50 to 100 times faster should +not be uncommon. Best of all (for me), it still runs in constant memory! diff --git a/doc/design/assistant/blog/day_317__misc.mdwn b/doc/design/assistant/blog/day_317__misc.mdwn new file mode 100644 index 0000000000..e2acf21684 --- /dev/null +++ b/doc/design/assistant/blog/day_317__misc.mdwn @@ -0,0 +1,17 @@ +Spent a while tracking down a bug that causes a crash on OSX when setting +up an XMPP account. I managed to find a small test case that reliably +crashes, and sent it off to the author of the haskell-gnutls bindings, +which had one similar segfault bug fixed before with a similar test case. +Fingers crossed.. + +Just finished tracking down a bug in the Android app that caused its +terminal to spin and consume most CPU (and presumably a lot of battery). +I introduced this bug when adding the code to open urls written to a fifo, +due to misunderstanding how java objects are created, basically. This bug +is bad enough to do a semi-immediate release for; luckily it's just about +time for a release anyway with other improvements, so in the next few +days.. + +Have not managed to get a recent ghc-android to build so far. + +Guilhem fixed some bugs in `git annex unused`. diff --git a/doc/design/assistant/polls/prioritizing_special_remotes.mdwn b/doc/design/assistant/polls/prioritizing_special_remotes.mdwn index beebeaad84..640f6c4dfa 100644 --- a/doc/design/assistant/polls/prioritizing_special_remotes.mdwn +++ b/doc/design/assistant/polls/prioritizing_special_remotes.mdwn @@ -6,7 +6,7 @@ locally paired systems, and remote servers with rsync. Help me prioritize my work: What special remote would you most like to use with the git-annex assistant? -[[!poll open=yes 16 "Amazon S3 (done)" 12 "Amazon Glacier (done)" 9 "Box.com (done)" 71 "My phone (or MP3 player)" 20 "Tahoe-LAFS" 9 "OpenStack SWIFT" 31 "Google Drive"]] +[[!poll open=yes 16 "Amazon S3 (done)" 12 "Amazon Glacier (done)" 9 "Box.com (done)" 71 "My phone (or MP3 player)" 21 "Tahoe-LAFS" 10 "OpenStack SWIFT" 31 "Google Drive"]] This poll is ordered with the options I consider easiest to build listed first. Mostly because git-annex already supports them and they diff --git a/doc/direct_mode.mdwn b/doc/direct_mode.mdwn index b0e9a0adb5..a6a2003a79 100644 --- a/doc/direct_mode.mdwn +++ b/doc/direct_mode.mdwn @@ -56,7 +56,15 @@ A very few commands don't work in direct mode, and will refuse to do anything. Direct mode also works well with the git-annex assistant. -You can use `git commit --staged`, or plain `git commit`. +The most important command to use in a direct mode repository is `git annex +sync`. This will commit any files you have run `git annex add` on, as well +as files that were added earlier and have been modified. It will push +the changes to other repositories for `git annex sync` there to pick up, +and will pull and merge any changes made on other repositories into the +local repository. + +While you generally will just use `git annex sync`, if you want to, +you can use `git commit --staged`, or plain `git commit`. But not `git commit -a`, or `git commit ` .. that'd commit whole large files into git! diff --git a/doc/direct_mode/comment_10_94284a476604e9c812b7ee475ca22959._comment b/doc/direct_mode/comment_10_94284a476604e9c812b7ee475ca22959._comment new file mode 100644 index 0000000000..e14f56485f --- /dev/null +++ b/doc/direct_mode/comment_10_94284a476604e9c812b7ee475ca22959._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="How to sync changes made in another remote when in direct mode" + date="2013-08-17T21:53:57Z" + content=""" +Re-reading @joey's reponse above, I see that merge/pull don't seem to be safe and will create dangling symlinks. That corresponds to those files I can see on cifs, I guess. + +But then, how can a direct repo sync with changes made in other remotes, if there no pull/fetch available. + +Can it then be only the source of changes which will propagate to indirect remotes ? +"""]] diff --git a/doc/direct_mode/comment_11_1c79c93f4b17cfc354ab920e3775cc60._comment b/doc/direct_mode/comment_11_1c79c93f4b17cfc354ab920e3775cc60._comment new file mode 100644 index 0000000000..ad1b66bc07 --- /dev/null +++ b/doc/direct_mode/comment_11_1c79c93f4b17cfc354ab920e3775cc60._comment @@ -0,0 +1,26 @@ +[[!comment format=mdwn + username="http://www.gl-como.it/author/valhalla/" + nickname="valhalla" + subject="Direct mode clone of an indirect repo" + date="2013-08-18T08:47:35Z" + content=""" +I too have issues with mixing direct and indirect mode repositories. + + I have a regular, existing repository with ebooks, shared between various clones on proper :) filesystems; now I would need a copy of some of them on an ereader which only offers a FAT filesystem, so it has to be direct mode. + + mount $READER + cd $reader + git clone $REPO + +I get a directory full of small files, the way git manages links on FAT. + + git annex init \"ebook reader\" + +This detects the fact that it is working on a crippled filesystem, enables direct mode and disables ssh connection caching; up to now everything seems to be fine, but then + + git annex get $SOME_BOOK + +seems to work, downloads the file somewhere, but when I try to open $SOME_BOOK it is still the fake link, and the file has been downloaded in its destination, as if the repo wasn't in direct mode. + +I use version 4.20130723 on debian jessie +"""]] diff --git a/doc/direct_mode/comment_12_1b5218fdb6ee362d6df68ff1229590d4._comment b/doc/direct_mode/comment_12_1b5218fdb6ee362d6df68ff1229590d4._comment new file mode 100644 index 0000000000..1743d5df99 --- /dev/null +++ b/doc/direct_mode/comment_12_1b5218fdb6ee362d6df68ff1229590d4._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 12" + date="2013-08-23T17:48:54Z" + content=""" +There should be no obstacles to using direct mode on one clone of a git repository, and indirect mode on another clone. The data stored in git for either mode is identical, and I do this myself for some repositories. + +@valhalla, you probably need to run `git annex fsck`, and if that does not solve your problem, you need to file a bug report. +"""]] diff --git a/doc/direct_mode/comment_13_55108ac736ea450df89332ba5de4a208._comment b/doc/direct_mode/comment_13_55108ac736ea450df89332ba5de4a208._comment new file mode 100644 index 0000000000..b8d80cd7ea --- /dev/null +++ b/doc/direct_mode/comment_13_55108ac736ea450df89332ba5de4a208._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 13" + date="2013-08-23T17:50:15Z" + content=""" +@obergix asked: + +> But then, how can a direct repo sync with changes made in other remotes, if there no pull/fetch available. + +The answer is simple: By running `git annex sync`, which handles all that. +"""]] diff --git a/doc/direct_mode/comment_14_ff4ffc2aabc5fd174d7386ef13860f78._comment b/doc/direct_mode/comment_14_ff4ffc2aabc5fd174d7386ef13860f78._comment new file mode 100644 index 0000000000..3a538e00b3 --- /dev/null +++ b/doc/direct_mode/comment_14_ff4ffc2aabc5fd174d7386ef13860f78._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Git annex copy needed before git annex sync" + date="2013-08-23T19:59:35Z" + content=""" +Thanks for these details @joeyh. But AFAIU, one needs to proceed to the git annex copy before doing the git annex sync, otherwise, symlinks (or files containing the symlink path on SMB) will be created, instead of the plain \"direct\" files that are expected. + +I'm still not sure whether the git annex sync needs to be issued on either of the indirect or direct remotes first, or both, then in which sequence. I think a \"walkthrough\" script would help. +"""]] diff --git a/doc/direct_mode/comment_15_1cd32456630b25d5aaa6d2763e6eb384._comment b/doc/direct_mode/comment_15_1cd32456630b25d5aaa6d2763e6eb384._comment new file mode 100644 index 0000000000..d265118a04 --- /dev/null +++ b/doc/direct_mode/comment_15_1cd32456630b25d5aaa6d2763e6eb384._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 15" + date="2013-08-24T15:56:47Z" + content=""" +No, you can sync before you copy, get, or whatever. git-annex will replace the symlinks with the actual files when they arrive at the repository. +"""]] diff --git a/doc/direct_mode/comment_9_cff56dbcdfec60375c30d5b1b1c60614._comment b/doc/direct_mode/comment_9_cff56dbcdfec60375c30d5b1b1c60614._comment new file mode 100644 index 0000000000..d2c752a543 --- /dev/null +++ b/doc/direct_mode/comment_9_cff56dbcdfec60375c30d5b1b1c60614._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Mixing indirect mode and direct mode on different remotes" + date="2013-08-17T20:35:40Z" + content=""" +I'd like to have an indirect mode repo on my laptop cloned on a cifs mount point (mounted off an SMB NAS) thus in direct mode. But all I can see on the clone after merge/pull is text files of length 207 chars containg the symlink in plain text. + +I guess this is what git manages internally for the symlinks... so I'm afraid git annex doesn't work in such case. + +Can you confirm that indirect and direct modes can coexist on clones of the same repo ? +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with.mdwn b/doc/forum/Adding_existing_S3_bucket_to_sync_with.mdwn new file mode 100644 index 0000000000..af138c1015 --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with.mdwn @@ -0,0 +1,16 @@ +Hello, + +I am just starting to learn git-annex so forgive me if this is a naive question. + +I have the following repositories: + +1. Home (laptop) +2. Work (mac mini) +3. S3 bucket +4. USB drive, full backup, attached to Home laptop. + +I want to sync files between Home and Work via the S3 bucket. It is not clear to me how to accomplish this through the git-annex assistant. Is this possible? Are there instructions online? + +Thanks in advance! + +Scott diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_1_30b9a70d367dd5b8781e9a86e42d4c3e._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_1_30b9a70d367dd5b8781e9a86e42d4c3e._comment new file mode 100644 index 0000000000..d68af19f95 --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_1_30b9a70d367dd5b8781e9a86e42d4c3e._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://marco.paga.myopenid.com/" + ip="2001:4dd0:ff00:917b:d575:780:2c27:d982" + subject="Yes, it is possible" + date="2013-08-19T17:59:56Z" + content=""" +You can sync both repos. The simplest way is to have both clients signed on to jabber. This way the clients exchange information when the two are online. + +Additionally you need to have a cloud special remote available on both ends. The cloud repository is needed to push and retrieve data for the clients. You need to configure the cloud as a transfer reposity. The clients as - what else - client. The USB Drive can be used as a backup repository on one or both ends and perhaps even for syncing very large files around. +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_2_a8525c1a7e5f89c30c9503fe8bfed02e._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_2_a8525c1a7e5f89c30c9503fe8bfed02e._comment new file mode 100644 index 0000000000..9e1d27af4e --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_2_a8525c1a7e5f89c30c9503fe8bfed02e._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://marco.paga.myopenid.com/" + ip="2001:4dd0:ff00:917b:d575:780:2c27:d982" + subject="I forgot to mention" + date="2013-08-19T18:01:47Z" + content=""" +You might want to have a look at this: https://git-annex.branchable.com/assistant/remote_sharing_walkthrough/ +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_3_c3878989f74e740c0ed42f440750f3a4._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_3_c3878989f74e740c0ed42f440750f3a4._comment new file mode 100644 index 0000000000..9925f8274d --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_3_c3878989f74e740c0ed42f440750f3a4._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawkjQhXk8KAh9yD0p1R6QzT-Sw7FtHE3d54" + nickname="Scott" + subject="comment 3" + date="2013-08-19T18:03:41Z" + content=""" +Great thanks! I'll try it out tonight and report back. +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_4_c06cc86496f9d4c0c42a8c89aa5a7b35._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_4_c06cc86496f9d4c0c42a8c89aa5a7b35._comment new file mode 100644 index 0000000000..5e1a397135 --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_4_c06cc86496f9d4c0c42a8c89aa5a7b35._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawkjQhXk8KAh9yD0p1R6QzT-Sw7FtHE3d54" + nickname="Scott" + subject="comment 4" + date="2013-08-20T16:18:24Z" + content=""" +When I try to setup my Jabber client, using my gmail address, the assistant crashes. I thought this might be due to having two-factor authentication enabled so I generated an application specific password and tried that. The assistant still crashes. The log is huge, I am not sure what would be relevant to show here. +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_5_0a1c2dd0929511ff824be8de2c8d85eb._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_5_0a1c2dd0929511ff824be8de2c8d85eb._comment new file mode 100644 index 0000000000..2c4927b195 --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_5_0a1c2dd0929511ff824be8de2c8d85eb._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="http://marco.paga.myopenid.com/" + ip="2001:4dd0:ff00:917b:f87b:5579:3820:5db" + subject="Please post the log" + date="2013-08-21T15:49:00Z" + content=""" +I don't know what is going wrong. It is not a bad idea to post the log information. + +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_6_1444c2f89885f028f20a4d3ce225a403._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_6_1444c2f89885f028f20a4d3ce225a403._comment new file mode 100644 index 0000000000..21c3d80e35 --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_6_1444c2f89885f028f20a4d3ce225a403._comment @@ -0,0 +1,23 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawkjQhXk8KAh9yD0p1R6QzT-Sw7FtHE3d54" + nickname="Scott" + subject="comment 6" + date="2013-08-21T20:05:31Z" + content=""" +I tried a different approach and attempted to setup s3 at the command line. This is what I did: + +zombie:annex scott$ export AWS_ACCESS_KEY_ID=\"my key\" +zombie:annex scott$ export AWS_SECRET_ACCESS_KEY=\"my secret key\" +zombie:annex scott$ git annex initremote S3 type=S3 encryption=shared +[2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"show-ref\",\"git-annex\"] +[2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"] +[2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"log\",\"refs/heads/git-annex..da801570f9ed8d28e5a0cea6cc51f1a2003317d6\",\"--oneline\",\"-n1\"] +[2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"log\",\"refs/heads/git-annex..8015f3fed32792b558d16008d20816fab0fc50c2\",\"--oneline\",\"-n1\"] +[2013-08-21 13:03:42 PDT] chat: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"cat-file\",\"--batch\"] +[2013-08-21 13:03:42 PDT] read: git [\"config\",\"--null\",\"--list\"] +initremote S3 (encryption setup) [2013-08-21 13:03:42 PDT] read: gpg [\"--quiet\",\"--trust-model\",\"always\",\"--gen-random\",\"--armor\",\"2\",\"512\"] +(shared cipher) (checking bucket...) +git-annex: connect: does not exist (Connection refused) +failed +git-annex: initremote: 1 failed +"""]] diff --git a/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_7_1c30944010d541096baff18198a5560d._comment b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_7_1c30944010d541096baff18198a5560d._comment new file mode 100644 index 0000000000..7e05bf59af --- /dev/null +++ b/doc/forum/Adding_existing_S3_bucket_to_sync_with/comment_7_1c30944010d541096baff18198a5560d._comment @@ -0,0 +1,23 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawkjQhXk8KAh9yD0p1R6QzT-Sw7FtHE3d54" + nickname="Scott" + subject="comment 7" + date="2013-08-21T20:07:58Z" + content=""" +Sorry that didnt format properly + + zombie:annex scott$ export AWS_ACCESS_KEY_ID=\"key\" + zombie:annex scott$ export AWS_SECRET_ACCESS_KEY=\"secret\" + zombie:annex scott$ git annex initremote S3 type=S3 encryption=shared + [2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"show-ref\",\"git-annex\"] + [2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"] + [2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"log\",\"refs/heads/git-annex..da801570f9ed8d28e5a0cea6cc51f1a2003317d6\",\"--oneline\",\"-n1\"] + [2013-08-21 13:03:42 PDT] read: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"log\",\"refs/heads/git-annex..8015f3fed32792b558d16008d20816fab0fc50c2\",\"--oneline\",\"-n1\" ] + [2013-08-21 13:03:42 PDT] chat: git [\"--git-dir=/Network/Servers/filer004/vol/office_homes/scott/annex/.git\",\"--work-tree=/Network/Servers/filer004/vol/office_homes/scott/annex\",\"cat-file\",\"--batch\"] + [2013-08-21 13:03:42 PDT] read: git [\"config\",\"--null\",\"--list\"] + initremote S3 (encryption setup) [2013-08-21 13:03:42 PDT] read: gpg [\"--quiet\",\"--trust-model\",\"always\",\"--gen-random\",\"--armor\",\"2\",\"512\"] + (shared cipher) (checking bucket...) + git-annex: connect: does not exist (Connection refused) + failed + git-annex: initremote: 1 failed +"""]] diff --git a/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__.mdwn b/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__.mdwn new file mode 100644 index 0000000000..0392dbb38f --- /dev/null +++ b/doc/forum/Android:_is_constant_high_cpu_usage_to_be_expected__63__.mdwn @@ -0,0 +1,3 @@ +While running the Git Annex App on Android, the app causes a constant cpu usage of about 50% when idling. I've seen this behavior on two devices (phone and tablet) with a CM 10.1 nightly build. The app causes this high cpu usage even when it is in the background, not performing any synchronization and managing only one repository containing just one file. Unfortunately I couldn't figure out what causes the cpu usage. The daemon.log file remains unchanged and I couldn't find any other log files. + +Is this expected behavior or unusual high cpu usage? diff --git a/doc/forum/Annex_contents_just_disappeared__63__.mdwn b/doc/forum/Annex_contents_just_disappeared__63__.mdwn new file mode 100644 index 0000000000..d18e2bf91c --- /dev/null +++ b/doc/forum/Annex_contents_just_disappeared__63__.mdwn @@ -0,0 +1,12 @@ +Joey, + +I have git-annex now to manage many of the repositories on my system. I have them both on my local machine, and on a very large file server, and a backup system on the Internet. + +Today I went to look at a file in one of my annexes and it wasn't there. This really surprised me. But what surprised me most is that around 90% of the files in *all* of my annexes on both my local system and my file server are completely missing. Only the Internet backup system has them. + +How could something like this happen, when I haven't been interacting with these annexes at all during this time? Can you think of any scenario that might lead to this? This is pretty much the absolute worst case scenario for an archival data system. + +I am running on Mac OS X 10.8, using GHC 7.6.3 to build git-annex, and I keep my git-annex binary updated often. + +Thanks, + John diff --git a/doc/forum/Annex_contents_just_disappeared__63__/comment_1_4ab5ca00f912c0c95fabc10f2d9600d3._comment b/doc/forum/Annex_contents_just_disappeared__63__/comment_1_4ab5ca00f912c0c95fabc10f2d9600d3._comment new file mode 100644 index 0000000000..fe4edbc27c --- /dev/null +++ b/doc/forum/Annex_contents_just_disappeared__63__/comment_1_4ab5ca00f912c0c95fabc10f2d9600d3._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89" + nickname="John" + subject="comment 1" + date="2013-08-23T03:06:00Z" + content=""" +Wait, I think this comes from a backend switch. I changed my .gitattributes file at one point to read: + +* annex.backend=SHA512E annex.numcopies=2 + +I thought this would just affect new files, not existing annexed content. Could this do it? +"""]] diff --git a/doc/forum/Annex_contents_just_disappeared__63__/comment_2_657f737c5d64d440aa133ddb41408fbc._comment b/doc/forum/Annex_contents_just_disappeared__63__/comment_2_657f737c5d64d440aa133ddb41408fbc._comment new file mode 100644 index 0000000000..e30ff02ca1 --- /dev/null +++ b/doc/forum/Annex_contents_just_disappeared__63__/comment_2_657f737c5d64d440aa133ddb41408fbc._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/2grhJvAC049fJnvALDXek.6MRZMTlg--#eec89" + nickname="John" + subject="comment 2" + date="2013-08-23T03:14:15Z" + content=""" +Yes, that was the problem, sorry to bother you. None of my data is gone, it's just sitting there under unknown names. I can roll back to when it knew the names, and migrate them forward. +"""]] diff --git a/doc/forum/Annex_contents_just_disappeared__63__/comment_3_9b4c35feb14b37d43d053d7430da9abf._comment b/doc/forum/Annex_contents_just_disappeared__63__/comment_3_9b4c35feb14b37d43d053d7430da9abf._comment new file mode 100644 index 0000000000..6c40a1cac9 --- /dev/null +++ b/doc/forum/Annex_contents_just_disappeared__63__/comment_3_9b4c35feb14b37d43d053d7430da9abf._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 3" + date="2013-08-23T04:28:45Z" + content=""" +If you change the backend, and then in one repository you run `git annex migrate`, other repositories that have the old keys will not know about the new names. For this reason, then multiple repositories have the files, it's best to run it redundantly in each repository. + +TBH, migration is a bit of a PITA because of this. Best to aovid it in most cases. + +Git-annex will never perform a migration begind your back. You must have run `git annex migrate` at some point. You can check the git history for details. +"""]] diff --git a/doc/forum/Assistant:_configure_auto-sync.mdwn b/doc/forum/Assistant:_configure_auto-sync.mdwn new file mode 100644 index 0000000000..48c4dc4552 --- /dev/null +++ b/doc/forum/Assistant:_configure_auto-sync.mdwn @@ -0,0 +1,11 @@ +I have large central repositories of data. Therefore, on each client I want to save part data(to save space of disk). In command line I do + + [...] + git-annex webapp + git-annex drop [DeleteContentDirectory] + [...] + +After this command Assistant performs automatic synchronization getting content of files from this directory(DeleteContentDirectory), but I don't want. I want it's was only symlink of file in this directory. + +How can I configure Assistant which files have to get content on the client? It's possible? + diff --git a/doc/forum/Assistant:_configure_auto-sync/comment_1_c8cabd38114582bbdbad49f2d81959d7._comment b/doc/forum/Assistant:_configure_auto-sync/comment_1_c8cabd38114582bbdbad49f2d81959d7._comment new file mode 100644 index 0000000000..34fffb8463 --- /dev/null +++ b/doc/forum/Assistant:_configure_auto-sync/comment_1_c8cabd38114582bbdbad49f2d81959d7._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmWg4VvDTer9f49Y3z-R0AH16P4d1ygotA" + nickname="Tobias" + subject="comment 1" + date="2013-08-26T07:44:22Z" + content=""" +You should set your repository to \"manual\" mode instead of \"client\" mode. + +But then no data will be synced at all by the assistant, only metadata. You would have to do \"get/drop\" manually for commandline for all files. + +Alternatively you could use the special \"archive\" folders that are supported by the assistant. + +"""]] diff --git a/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_2_af2a2634d8d128868022d033d6adb549._comment b/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_2_af2a2634d8d128868022d033d6adb549._comment new file mode 100644 index 0000000000..0623ed1dbb --- /dev/null +++ b/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_2_af2a2634d8d128868022d033d6adb549._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-23T18:35:01Z" + content=""" +Having just set up which uses a git hook to run `git annex merge`, I can say that the main problems you are likely to run into are: + +1. The hook might be run with the cwd not set to the top of the git repository. cd to the git repository in the hook to fix. +2. The hook might be run with `GIT_DIR` set to a strange value (in my case, it was set to \".\"), which is not the actual .git directory location. Unsetting it fixes that. + +I don't know about how to get git hooks to work on FAT filesystems though. Hooks have to be executable, and most systems probably don't mount such filesystems with executability allowed. +"""]] diff --git a/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_3_31ec762a0684d2ce87d229ed2924db93._comment b/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_3_31ec762a0684d2ce87d229ed2924db93._comment new file mode 100644 index 0000000000..2a56b57e92 --- /dev/null +++ b/doc/forum/Can__39__t_get_git-annex_merge_to_work_from_git_hook/comment_3_31ec762a0684d2ce87d229ed2924db93._comment @@ -0,0 +1,16 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawlq495p0WtZDUpxzYN9YnToZGODfCGnqOw" + nickname="Stanis" + subject="comment 3" + date="2013-08-24T13:30:52Z" + content=""" +Thanks joey, that's exactly what was happening. + +Just to repeat it here, if anyone else runs into the same problem, your post-receive hook has to look like this: + + #!/bin/sh + unset GIT_DIR + cd .. + git annex merge + +"""]] diff --git a/doc/forum/How_do_I_cleanly_remove_an_Android_git-annex_installation__63__/comment_1_e14757c2c106770c2d7069ace4987b3b._comment b/doc/forum/How_do_I_cleanly_remove_an_Android_git-annex_installation__63__/comment_1_e14757c2c106770c2d7069ace4987b3b._comment new file mode 100644 index 0000000000..b051aa704a --- /dev/null +++ b/doc/forum/How_do_I_cleanly_remove_an_Android_git-annex_installation__63__/comment_1_e14757c2c106770c2d7069ace4987b3b._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T18:43:08Z" + content=""" +It should be sufficient to delete `/sdcard/git-annex.home` and delete the .git directory inside whatever directory you set up as the repository. +"""]] diff --git a/doc/forum/Manual_Setup_of_a_Central_Repo/comment_1_3a163fd5629dc40423f1290a78ae1c07._comment b/doc/forum/Manual_Setup_of_a_Central_Repo/comment_1_3a163fd5629dc40423f1290a78ae1c07._comment new file mode 100644 index 0000000000..7fe30c6ddd --- /dev/null +++ b/doc/forum/Manual_Setup_of_a_Central_Repo/comment_1_3a163fd5629dc40423f1290a78ae1c07._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-26T18:46:06Z" + content=""" +You could certianly do that. I don't think it's the easiest way. + +Note that this is essentially a git question. It really has nothing to do with git-annex, unless you want to use the git-annex assistant, which can sync a repository over XMPP without needing a central git repository at all. + +If I had this problem with git in general, I would make a new empty repository on the server, and push the local repository I have on the one machine to it. Then on the other machine, I would clone from the server. Problem solved, I think? +"""]] diff --git a/doc/forum/Manual_mode_option_in_assistant_auto-syncs.mdwn b/doc/forum/Manual_mode_option_in_assistant_auto-syncs.mdwn new file mode 100644 index 0000000000..49b58e529e --- /dev/null +++ b/doc/forum/Manual_mode_option_in_assistant_auto-syncs.mdwn @@ -0,0 +1,11 @@ +Hi, + +I've recently set-up a server which uses Southpaw's Tactic DAM system and I've initialised a git-annex directory using the assistant which will manage any files which Tactic puts into the git-annex. I plan to make some remote repositories to Amazon S3, friends and some local machines on my home network. The server is running Ubuntu 64-bit and so I've written an upstart job which runs 'git-annex assistant --autostart' as the user 'git-annex' as this user doesn't log-in and run the xdg autostart .desktop at all. + +I saw that you can set the purpose of each repository which it will sync to and noticed 'Manual Mode.' From the description, it seems it will only work if I do explicit git-annex commands to it which would be perfect for me as I'd like to write tools which run git-annex add/get/drop/etc. manually on some remotes like ones to friends as I don't want them to sync to everything or any files that they produce, only files which they request with a special tool that I'll write and have Tactic marshal the file changes/names/etc. + +I've set those remotes to manual-mode via the assistant and tried copying a file to the remote's directory, but it auto-synced the file anyway. Maybe I'm getting confused at how manual mode works but I'd like to only explicitly set which files to add to the repo by a command and not just 'any' file which gets placed into that directory. If this is more of a wishlist request I guess just move this post into there and I'll reword it as a wish request. + +I don't need to use the assistant if that makes more sense, but I would like to be able to still monitor things as the webapp makes for a great GUI to check for that stuff. I can't wait for the https version of webapp too, I currently run git-annex webapp --listen=: and then run the link it outputs on my desktop machine to manage it from the server. + +Thanks, and this is such a great bit of software, especially as my Internet connection is really bad for 2013 standards, and having the option for friends/remote servers to sync up via an encrypted S3 or box.com account is great! diff --git a/doc/forum/Manual_mode_option_in_assistant_auto-syncs/comment_1_4a0468b6ca2ffff8ef8f19800597567d._comment b/doc/forum/Manual_mode_option_in_assistant_auto-syncs/comment_1_4a0468b6ca2ffff8ef8f19800597567d._comment new file mode 100644 index 0000000000..56e68f779b --- /dev/null +++ b/doc/forum/Manual_mode_option_in_assistant_auto-syncs/comment_1_4a0468b6ca2ffff8ef8f19800597567d._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T16:20:29Z" + content=""" +In the assistant, putting a repository in manual mode prevents the assistant from automatically downloading every file that is added to other clones of the repository. As you've noticed, it does not prevent the assistant from automatically adding new files that are put into the local repository, or from uploading those files to other clients that want them (ie, clients not themselves set to use manual mode). + +You can prevent the assistant from noticing when you add new files to a repository by clicking on \"syncing enabled\" in the first repository in the list. (The repository labeled as \"here\".) You can then `git annex add` the files you want to add by hand, and manually `copy annex copy` them to other repositories, and manually `git annex sync`. +"""]] diff --git a/doc/forum/Poor_man__39__s_IMAP/comment_6_1e81bd4bb62652bc674cdcd7ed57ac5c._comment b/doc/forum/Poor_man__39__s_IMAP/comment_6_1e81bd4bb62652bc674cdcd7ed57ac5c._comment new file mode 100644 index 0000000000..7e07204561 --- /dev/null +++ b/doc/forum/Poor_man__39__s_IMAP/comment_6_1e81bd4bb62652bc674cdcd7ed57ac5c._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8" + nickname="Hamza" + subject="comment 6" + date="2013-08-16T09:14:52Z" + content=""" +You can either keep running 2 webapps paired using xmpp running all the time that gives you push like notifications or if you are ok with syncing every once in a while you can have a check mail script that adds files on the server commits them then calls git annex sync locally, + + ssh $1 \"cd /path/to/annex/;git add .;git commit 'Update'\";git annex sync + +should do the trick. The latter method you just need to annex repos no encrypted third repo. Just init your git annex repo on the server and clone on the laptop thats it. +"""]] diff --git a/doc/forum/Poor_man__39__s_IMAP/comment_7_b3929281dff6078d77f1b9ae42e25bb6._comment b/doc/forum/Poor_man__39__s_IMAP/comment_7_b3929281dff6078d77f1b9ae42e25bb6._comment new file mode 100644 index 0000000000..aba4cd0de9 --- /dev/null +++ b/doc/forum/Poor_man__39__s_IMAP/comment_7_b3929281dff6078d77f1b9ae42e25bb6._comment @@ -0,0 +1,16 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 7" + date="2013-08-23T18:30:04Z" + content=""" +I don't feel that git-annex is the best thing to use for this. Maildir has some specific semantics for the filenames used in it that let imap clients resolve inconsistencies, such as a message that was read on machine A, and deleted on machine B. git-annex is unlikely to work as well. + +However, I have to say that the very beginning of this thread has a wrong statement in it. + +> I tried setting it up with the webUI to the assistant but it only offers encrypted storage[1] on the remote server. + +If you install git and git-annex on your remote server, the git-annex assistant will detect this, and offer the choice between a regular git repository, and encrypted storage. If you don't have them installed, it tells you you don't, offers to let you retry once you do install them, and offers encrypted storage as the only option that works given what's installed on the server. + +(Also, the bug you linked to in [1] has nothing at all to do with what you were talking about.) +"""]] diff --git a/doc/forum/Relocating_annex_directory/comment_1_13ff5438baa1db110beb6aab3a783def._comment b/doc/forum/Relocating_annex_directory/comment_1_13ff5438baa1db110beb6aab3a783def._comment new file mode 100644 index 0000000000..5136941c50 --- /dev/null +++ b/doc/forum/Relocating_annex_directory/comment_1_13ff5438baa1db110beb6aab3a783def._comment @@ -0,0 +1,11 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmBUR4O9mofxVbpb8JV9mEbVfIYv670uJo" + nickname="Justin" + subject="comment 1" + date="2013-08-16T03:42:00Z" + content=""" +moving the annex should work fine, provided: + +* You are moving it to a proper unix filesystem - NOT fat32 +* The assistant is shutdown. If it is running, bad things will happen. +"""]] diff --git a/doc/forum/Relocating_annex_directory/comment_2_6d88ff03fcf00ae872442e8a86c968ed._comment b/doc/forum/Relocating_annex_directory/comment_2_6d88ff03fcf00ae872442e8a86c968ed._comment new file mode 100644 index 0000000000..e7b361675f --- /dev/null +++ b/doc/forum/Relocating_annex_directory/comment_2_6d88ff03fcf00ae872442e8a86c968ed._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-24T18:56:11Z" + content=""" +`git annex whereis` does not show dead repositories. + +Anyway Justin is of course right: Provided the assistant is not running in a repository, the repository is just a collection of files in a directory, and can be moved around, tarred up, untarred, etc just like any other repository. If the assistant is running it may become unhappy if its repository vanishes out from underneath it. +"""]] diff --git a/doc/forum/Revert_file_linkage_to_original_files.mdwn b/doc/forum/Revert_file_linkage_to_original_files.mdwn new file mode 100644 index 0000000000..ba83cfd150 --- /dev/null +++ b/doc/forum/Revert_file_linkage_to_original_files.mdwn @@ -0,0 +1,9 @@ +I've recently found the following problem: + +I really really want to get back my original folder structure - which includes the real files, not the symlinks. I've searched for quite a while, but I simply could not find an acceptable solution... + +So I thought I would like to ask you guys here, if anybody experienced similar problems (or at least knows a solution for my problem)? + +Greetings + +Pethor diff --git a/doc/forum/Revert_file_linkage_to_original_files/comment_1_898ca2c9976e92d22470c7404aa9813f._comment b/doc/forum/Revert_file_linkage_to_original_files/comment_1_898ca2c9976e92d22470c7404aa9813f._comment new file mode 100644 index 0000000000..a72a2cfdd4 --- /dev/null +++ b/doc/forum/Revert_file_linkage_to_original_files/comment_1_898ca2c9976e92d22470c7404aa9813f._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="2001:4978:f:21a::2" + subject="comment 1" + date="2013-08-15T09:02:38Z" + content=""" +Sounds like you want to switch to [[direct mode]]. + +(Or possibly to run `git annex unannex`, if you don't want to use git-annex for these files.) +"""]] diff --git a/doc/forum/USB_drive_in_transfer_group_keeps_growing_-_assistant/comment_1_0a6f6054d70009979f4a036e24b7c500._comment b/doc/forum/USB_drive_in_transfer_group_keeps_growing_-_assistant/comment_1_0a6f6054d70009979f4a036e24b7c500._comment new file mode 100644 index 0000000000..f298b56cde --- /dev/null +++ b/doc/forum/USB_drive_in_transfer_group_keeps_growing_-_assistant/comment_1_0a6f6054d70009979f4a036e24b7c500._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T19:22:05Z" + content=""" +The assistant is supposed to remove files from transfer repositories once the file has been transferred to all known clients. This generally seems to work, with all the transfer repositories I've tested it with. Nothing is special about USB drives compared with other transfer repositories. + +Perhaps you have not configured the USB drive as a transfer repository? Or perhaps you have another client repository (even a client repository you had once but have now deleted). +"""]] diff --git a/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_1_85806316ed28d7a891f04fab4027141b._comment b/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_1_85806316ed28d7a891f04fab4027141b._comment new file mode 100644 index 0000000000..b175204e55 --- /dev/null +++ b/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_1_85806316ed28d7a891f04fab4027141b._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://thkoch2001.myopenid.com/" + nickname="thkoch" + subject="It would also be nice, if git-annex would use btrfs reflinks on unlock" + date="2013-08-24T12:46:40Z" + content=""" +I don't know whether git-annex already does use btrfs reflinks, but I suspect, that I double the size of my git-annex repo folder on disk when I unlink all files. +"""]] diff --git a/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_2_ecb411a2c4d67917b734a90bd460d44b._comment b/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_2_ecb411a2c4d67917b734a90bd460d44b._comment new file mode 100644 index 0000000000..a4ade57926 --- /dev/null +++ b/doc/forum/Use_reflinks_on_BTRFS_instead_of_symlinks___63__/comment_2_ecb411a2c4d67917b734a90bd460d44b._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-24T15:54:02Z" + content=""" +git-annex has always used cp --reflink=auto, including when it cp's the file in `git annex unlock`. + +You can verify this with --debug. +"""]] diff --git a/doc/forum/Using_git-annex_via_command_line_in_OS_X.mdwn b/doc/forum/Using_git-annex_via_command_line_in_OS_X.mdwn new file mode 100644 index 0000000000..5eba701bdd --- /dev/null +++ b/doc/forum/Using_git-annex_via_command_line_in_OS_X.mdwn @@ -0,0 +1,3 @@ +After installing the binary for Mac OS X and including some larger directories, my computer now seems quite busy (for the last days) with the import process. I see a process called git-annex causing the load, so it seems OK. As the git-annex assistant seems to hang quite a bit, I would like to see the progress using a command line interface. However, I cannot use the "git annex" command as I get the message "git: 'annex' is not a git command. See 'git --help'." + +I guess this is my normal git version, installed by homebrew (the OS X version for apt-get) that does not know anything about the installed binary. Can I still use the CLI with this version? Or better, is there or will there be a way to install git-annex from source, or even better using "brew install git-annex"? diff --git a/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_1_1c9e121f60fb6868c07f1a53b03c4ed0._comment b/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_1_1c9e121f60fb6868c07f1a53b03c4ed0._comment new file mode 100644 index 0000000000..1f51e6c971 --- /dev/null +++ b/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_1_1c9e121f60fb6868c07f1a53b03c4ed0._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnaZYaspvzx1lQiM56UQo-X82BnPiAaiEY" + nickname="Martin" + subject="comment 1" + date="2013-08-19T18:07:04Z" + content=""" +One more question. When running the git-annex binary the webapp opens. After closing the window I cannot access the webapp anymore. Using the IP + port number (http://127.0.0.1:53027/) does not work. Would be handy to have a bookmark for the webapp that works as long as the assistant is running. +"""]] diff --git a/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_2_52d8ffba82e29ac2722a8e43e469cc47._comment b/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_2_52d8ffba82e29ac2722a8e43e469cc47._comment new file mode 100644 index 0000000000..b30773cd22 --- /dev/null +++ b/doc/forum/Using_git-annex_via_command_line_in_OS_X/comment_2_52d8ffba82e29ac2722a8e43e469cc47._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawnaZYaspvzx1lQiM56UQo-X82BnPiAaiEY" + nickname="Martin" + subject="git-annex via comand line" + date="2013-08-19T21:53:11Z" + content=""" +Just found the page how to install the CLI on OS X: http://git-annex.branchable.com/install/OSX/ +That solved all my questions for now. +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs.mdwn b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs.mdwn new file mode 100644 index 0000000000..1e64430385 --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs.mdwn @@ -0,0 +1,5 @@ +I've got a Freebox Revolution set-top box / TV NAS at home, with some preconfigured layou for videos, photos and music. + +I'd like to use it as a git-annex remote, but am afraid there's no support for FTP (authenticated) or SMB shares exported by the NAS (I don't think it supports other protocols even though runs Linux internally, AFAIK). + +Is there any option to store much on that NAS and sync it with git-annex ? diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_1_bd73c8d10028e1b45da9ea8f657e5064._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_1_bd73c8d10028e1b45da9ea8f657e5064._comment new file mode 100644 index 0000000000..d5e8d54043 --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_1_bd73c8d10028e1b45da9ea8f657e5064._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://cstork.org/" + nickname="Chris Stork" + subject="Similar to "direct special remotes"" + date="2013-08-16T17:57:26Z" + content=""" +You have a very similar problem as I do. + +See my post where I called this [direct special remotes](http://git-annex.branchable.com/forum/Direct_special_remotes/). +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_2_16c3c994ee8fcb466e52ca0e812e5915._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_2_16c3c994ee8fcb466e52ca0e812e5915._comment new file mode 100644 index 0000000000..93eef73220 --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_2_16c3c994ee8fcb466e52ca0e812e5915._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Except I don't have rsync/sftp on the NAS AFAICT" + date="2013-08-17T08:56:37Z" + content=""" +There seemed to be some hope with rsync in your case, but not mine. Thanks anyway for the pointer. +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_3_ac60f6edb76bdd541711e472eec9591a._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_3_ac60f6edb76bdd541711e472eec9591a._comment new file mode 100644 index 0000000000..8729a8481e --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_3_ac60f6edb76bdd541711e472eec9591a._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Experimenting with a CIFS mount point of the NAS and direct mode" + date="2013-08-17T22:11:19Z" + content=""" +I've been experimenting with a direct mode repo on a CIFS mount of the SMB share of the NAS. + +Unfortunately, it seems I can't propagate changes made on the laptop to the mount point by issueing a git pull or merge, as it is part of the unsafe commands that don't support direct mode (see details in )... direct mode wouldn't be very useful then : I intend to mirror on the NAS the files I've been managing locally. For instance I will sort my photos in subdirs, on the laptop, and intend to mirror that on the NAS. +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_4_2194f0600d9a90f0d9c947ea9cc213a3._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_4_2194f0600d9a90f0d9c947ea9cc213a3._comment new file mode 100644 index 0000000000..4a59acdeb7 --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_4_2194f0600d9a90f0d9c947ea9cc213a3._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 4" + date="2013-08-23T17:55:39Z" + content=""" +Just run `git annex sync` to update the direct mode repository on your NAS. +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_5_eb7d13f6b6fa674a2536bde51bfc3fd1._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_5_eb7d13f6b6fa674a2536bde51bfc3fd1._comment new file mode 100644 index 0000000000..e014efb86c --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_5_eb7d13f6b6fa674a2536bde51bfc3fd1._comment @@ -0,0 +1,48 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="So it seems I have found a sequence that seems to be operating fine" + date="2013-08-23T20:28:45Z" + content=""" +Here's a script, which I think makes it work, using git clone, git annex copy and git annex sync : + # The \"master\" remote which is with default indirect mode, on a Linux FS + BASE1=~/tmp + REPO1=$BASE1/annex-test + + # The \"slave\" remote on the NAS (a Samba server), which has been mounted with cifs, and thus will be in direct mode + BASE2=/mnt/freebox-server/ + REPO2=$BASE2/annex-test + + cd $BASE1 + mkdir $REPO1 + cd $REPO1 + git init + git annex init \"my laptop\" + + cd $REPO1 + cp -Lr ~/some_large_files ./ + git annex add some_large_files + git commit -m \"added\" + + cd $BASE2 + git clone $REPO1 $REPO2 + cd $REPO2 + + git annex init \"freebox server\" + # This is not really needed, but if you want to replicate on a non cifs mount + git annex direct + + cd $REPO1 + git remote add freebox-server $REPO2 + + git annex copy --to freebox-server + git annex sync + + cd $REPO2 + git remote add laptop $REPO1 + #git annex sync + +After this, you should have your .git and plain \"direct\" files on the NAS, mirrored from what's on the laptop. + +Hope this helps. +"""]] diff --git a/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_6_ae323b16ddb9342e91be955408eca3b1._comment b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_6_ae323b16ddb9342e91be955408eca3b1._comment new file mode 100644 index 0000000000..44d3f5a85c --- /dev/null +++ b/doc/forum/Using_git_annex_with_a_SMB__47__FTP_TV_NAS_with_preconfigured_dirs/comment_6_ae323b16ddb9342e91be955408eca3b1._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 6" + date="2013-08-24T15:58:28Z" + content=""" +You can run any of these operations in any order and it will work. Ie, this is far more complicated and detailed than it needs to be. Just run git-annex commands in any order to do what you want to do. If they don't, file a (detailed) bug report. +"""]] diff --git a/doc/forum/correct_way_to_add_two_preexisting_datasets.mdwn b/doc/forum/correct_way_to_add_two_preexisting_datasets.mdwn new file mode 100644 index 0000000000..bfc1a62721 --- /dev/null +++ b/doc/forum/correct_way_to_add_two_preexisting_datasets.mdwn @@ -0,0 +1,25 @@ +I've been syncronizing my data since long time, mainly using rsync or unison. Thus I had two 3.5Gb datasets set1 (usb drive, hfs+ partition) and set2 (hdd, ext4 ubuntu 13.04 box) which differed only in 50Mb (new on set1 ). This was double checked using diff -r before doing anything. + +I created a git annex repo in direct mode for set2 from command line, and after that I let the assistant scan it. +After that created the repo for set1 and added it to the assistant. I think here comes my mistake (I think). + +Instead of keeping them apart, at told assistant to sync with set2. +Why I think this was a mistake? Because set2 was indexed and set1 no, and I'm seeing a lot of file moving a copying, which in my humble opinion should not happen. +What I expected it only the difference to be transferred from set1 to set2. +What it seems to be doing is moving away all content in set1, and copying it back from set2. I think it will end correctly, but with a lot of unnecessary and risky operations. + +I think I should have independently added both datasets, let them be scanned and then connect to each other. +So, now the questions: + +1. Is that the correct way to proceed? +2. What if I have to identical files with different modifying times, I hope they are not synced, right? +3. Is it posssible to achieve this behaviour of copying only the 50Mb? + +Thanks in advance and keep up the good work. +Best regards, + Juan + +EDIT: a couple of questions more: + +4. after finishing, set2 ended with a lot of symlinks but only in one subfolder. To prevent this should I put numcopies in 2? +5. This data is composed of input datasets and output simulations. Thus, I need to change them often, but not as often as code and in a very partial way (chunks of 50Mb). For me direct mode is the best (or plain git). However, I was wondering, it is possible to drop some files (even in direct mode) and use simlinks instead? diff --git a/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_1_c5c3ff25c9f5e34db222b5f4ae58b093._comment b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_1_c5c3ff25c9f5e34db222b5f4ae58b093._comment new file mode 100644 index 0000000000..13e2a58d2b --- /dev/null +++ b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_1_c5c3ff25c9f5e34db222b5f4ae58b093._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8" + nickname="Hamza" + subject="comment 1" + date="2013-08-23T16:17:58Z" + content=""" +I did something similar for my videos, I've created the repo on one machine add the video files then cloned it on the other machine then reinjected the files in to the cloned repo. + +http://joeyh.name/blog/entry/moving_my_email_archives_and_packages_to_git-annex/ +"""]] diff --git a/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_2_ee3ecc86990ac5a8d0c4fdfb482a7594._comment b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_2_ee3ecc86990ac5a8d0c4fdfb482a7594._comment new file mode 100644 index 0000000000..d1e259afd9 --- /dev/null +++ b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_2_ee3ecc86990ac5a8d0c4fdfb482a7594._comment @@ -0,0 +1,16 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 2" + date="2013-08-23T18:23:52Z" + content=""" +If you need to preserve mtimes, or differentiate between files with identical content but different mtimes, neither git nor git-annex is going to do what you want, since git doesn't care about preserving much file metadata. + +As far as importing two sets of files on two computers, the best thing to do is import each, and then let the two sync up. Otherwise, when you're running the assistant it will start downloading the first set you import to the second computer, before the second set is added there, and do extra work. Although once the duplicate files from the second set land in the second git repository, the assistant will avoid any additional redundant transfers. + +(The assistant never *moves* files, if both repositories are configured to be in the default client repository group. It only copies.) + +I don't understand question #1. \"set2 ended with a lot of symlinks but only in one subfolder\" doesn't make sense to me, or rather I could interpret it to mean any of dozen things (none of which seem likely) + +You can `git annex drop` files in direct mode. However, if you're running the assistant, it will try to get them back. You can configure your repository to be in manual mode to prevent the assistant doing that, or not use the assistant, or configure a [[preferred_content]] expression to make the assistant do something more custom like not try to get files located in a \"olddata\" directory. +"""]] diff --git a/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_3_e29bf8b848da04c761dc601ac979ac14._comment b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_3_e29bf8b848da04c761dc601ac979ac14._comment new file mode 100644 index 0000000000..d750e9581a --- /dev/null +++ b/doc/forum/correct_way_to_add_two_preexisting_datasets/comment_3_e29bf8b848da04c761dc601ac979ac14._comment @@ -0,0 +1,11 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmTNrhkVQ26GBLaLD5-zNuEiR8syTj4mI8" + nickname="Juan" + subject="comment 3" + date="2013-08-25T13:00:04Z" + content=""" +Thanks. It is very clear now. I think I got it running. I have 2 direct mode copies in my ubuntu box and in the USB drive and one indirect in my ultrabook (small SSD). +What I meant is that even in direct mode, after sync ended, the set I indexed first ended with the contents of a folder in the .git dir using symlinks. But it might have been a leftover of previous attempts. +I think I got confused by the great amount of flexibility it provides. +Thanks. +"""]] diff --git a/doc/forum/howto_update_feed.mdwn b/doc/forum/howto_update_feed.mdwn new file mode 100644 index 0000000000..5323e92eb3 --- /dev/null +++ b/doc/forum/howto_update_feed.mdwn @@ -0,0 +1,14 @@ +I am using the importfeed [1] functionality. + +How am I supposed to update the feed/feeds? + +I understand that running + + cd annex; git annex importfeed http://url/to/podcast + +a second time will 'do the right thing'. But that is cumbersome as I have to know the url again. Is there sth like git annex updatefeeds? + + + + +[1] http://joeyh.name/blog/entry/git-annex_as_a_podcatcher/ diff --git a/doc/forum/howto_update_feed/comment_1_bec356619f370a618f19a187d09d2e35._comment b/doc/forum/howto_update_feed/comment_1_bec356619f370a618f19a187d09d2e35._comment new file mode 100644 index 0000000000..fa87e3494d --- /dev/null +++ b/doc/forum/howto_update_feed/comment_1_bec356619f370a618f19a187d09d2e35._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-26T18:11:07Z" + content=""" +I have purposefully kept a list of feeds out of git-annex. I handle this by having a `feeds` file, which I check into git. Then a cron job runs: `xargs git-annex importfeed < feeds` +"""]] diff --git a/doc/forum/howto_update_feed/comment_2_84dfb80ba3db8d41164eb97022becae3._comment b/doc/forum/howto_update_feed/comment_2_84dfb80ba3db8d41164eb97022becae3._comment new file mode 100644 index 0000000000..4f28d8f4ef --- /dev/null +++ b/doc/forum/howto_update_feed/comment_2_84dfb80ba3db8d41164eb97022becae3._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="ringprince" + ip="134.76.140.110" + subject="comment 2" + date="2013-08-26T19:04:21Z" + content=""" +Thanks for that. I'll do the same ;-) +"""]] diff --git a/doc/forum/many_remotes.mdwn b/doc/forum/many_remotes.mdwn new file mode 100644 index 0000000000..4e463cb3c3 --- /dev/null +++ b/doc/forum/many_remotes.mdwn @@ -0,0 +1,24 @@ +Thanks Joey for the great work. + +I'm using git annex for my tv-shows and movies Folder. + +I have 3 USB HDD (ext.150Gb,ext.200Gb, ext.2Tb) and a USB Stick (ATV), which are traveling between 3 Devices + +2 Notebooks (Lappi,Kiste) and a Nas. + +First of all, I'm made a mistake and mixed the remote Locations from the tvshows folder with the movies folder and did a git annex sync, ( this happened about two weeks ago) +I think i can't undo this, only unannex will help. + +I've now watched the annex status output and noticed that there are many Remotes, some of them have a timestamp as name. + +see log file at http://pastebin.com/79bRVkK6 + +Running git annex on ubuntu 12.04 + + christian@Lappi:~/Serien$ git annex version + git-annex version: 4.20130417 + local repository version: 3 + default repository version: 3 + supported repository versions: 3 4 + upgrade supported from repository versions: 0 1 2 + build flags: Assistant Webapp Pairing Testsuite S3 WebDAV Inotify DBus XMPP DNS diff --git a/doc/forum/webapp___47___assistant_without_watch.mdwn b/doc/forum/webapp___47___assistant_without_watch.mdwn new file mode 100644 index 0000000000..9bb1fcf1ad --- /dev/null +++ b/doc/forum/webapp___47___assistant_without_watch.mdwn @@ -0,0 +1,9 @@ +I did not recieve feedback on my comment [1], so I try to post my question again but more clearly. + +Is it possible to run the assistent/the webapp without the functionality of 'git annex watch'? + +I'd like to use the assistant and to have the automatic syncing but I do not want the local repository to be watched. Instead I prefer to manually add/drop my files. + +I do not see the 'pause button' mentioned in my earlier question [1]. + +[1] http://git-annex.branchable.com/forum/webapp_and_manual_mode/ diff --git a/doc/forum/webapp___47___assistant_without_watch/comment_1_1bcd99aa81f937ded683e19a69d33dd9._comment b/doc/forum/webapp___47___assistant_without_watch/comment_1_1bcd99aa81f937ded683e19a69d33dd9._comment new file mode 100644 index 0000000000..c76128ae39 --- /dev/null +++ b/doc/forum/webapp___47___assistant_without_watch/comment_1_1bcd99aa81f937ded683e19a69d33dd9._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-26T18:14:17Z" + content=""" +The assistant is currently only able to transfer files that it has added itself. So if you disable syncing, you have to manually upload any files you add. + +I doubt that I will change this in the assistant, because supporting this use case would complicate it unnecessarily for a use case that is not what it's designed to do. It's more likely that `git annex sync` will get an option to also transfer file contents. +"""]] diff --git a/doc/forum/webapp___47___assistant_without_watch/comment_2_9f5b3f5bf7fedcd5baec519d97d3aa8c._comment b/doc/forum/webapp___47___assistant_without_watch/comment_2_9f5b3f5bf7fedcd5baec519d97d3aa8c._comment new file mode 100644 index 0000000000..a441558768 --- /dev/null +++ b/doc/forum/webapp___47___assistant_without_watch/comment_2_9f5b3f5bf7fedcd5baec519d97d3aa8c._comment @@ -0,0 +1,16 @@ +[[!comment format=mdwn + username="ringprince" + ip="134.76.140.110" + subject="comment 2" + date="2013-08-26T18:54:40Z" + content=""" +Thanks for the clarification. + +Although + +* not what I hoped for ;-) +* I don't see that it would get complicated +* I do not consider my use case special + +Anyway, thanks for this great piece of software. +"""]] diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn index 60736d579f..7cac9087d1 100644 --- a/doc/git-annex.mdwn +++ b/doc/git-annex.mdwn @@ -157,6 +157,24 @@ subdirectories). post-receive hook. Then any syncs to the repository will update its working copy automatically. +* mirror [path ...] + + This causes a destination repository to mirror a source repository. + + To use the local repository as the source repository, + specify mirror --to remote. + + To use a remote as the source repository, specify mirror --from remote. + + Each specified file in the source repository is mirrored to the destination + repository. If a file's content is present in the source repository, it is + copied to the destination repository. If a file's content is not present in + the source repository, it will be dropped from the destination repository + when possible. + + Note that mirror does not sync the git repository, but only the file + contents. + * addurl [url ...] Downloads each url to its own file, which is added to the annex. @@ -177,6 +195,9 @@ subdirectories). alternate locations from which the file can be downloaded. In this mode, addurl can be used both to add new files, or to add urls to existing files. + When quvi is installed, urls are automatically tested to see if they + are on a video hosting site, and the video is downloaded instead. + * rmurl file url Record that the file is no longer available at the url. @@ -190,6 +211,28 @@ subdirectories). git annex import /media/camera/DCIM/ + By default, importing two files with the same contents from two different + locations will result in both files being added to the repository. + (With all checksumming backends, including the default SHA256E, + only one copy of the data will be stored.) + + To not delete files from the import location, use the + --duplicate option. This could allow importing the same files repeatedly + to different locations in a repository. More likely, it could be used to + import the same files to a number of different branches or separate git + repositories. + + To only import files whose content has not been seen before by git-annex, + use the --deduplicate option. Duplicate files will be deleted from the + import location. + + The --clean-duplicates option does not import any new files, but any files + found in the import location that are duplicates of content in the annex + are deleted. + + (Note that using --deduplicate or --clean-duplicates with the WORM + backend does not look at file content, but filename and mtime.) + * importfeed [url ...] Imports the contents of podcast feeds. Only downloads files whose @@ -1072,6 +1115,11 @@ Here are all the supported configuration settings. (wget is always used in preference to curl if available.) For example, to force ipv4 only, set it to "-4" +* `annex.quvi-options` + + Options to pass to quvi when using it to find the url to download for a + video. + * `annex.http-headers` HTTP headers to send when downloading from the web. Multiple lines of diff --git a/doc/install/Android/comment_8_34f7c42050fa48769a6bfae60d72e477._comment b/doc/install/Android/comment_8_34f7c42050fa48769a6bfae60d72e477._comment new file mode 100644 index 0000000000..efba6aeeb3 --- /dev/null +++ b/doc/install/Android/comment_8_34f7c42050fa48769a6bfae60d72e477._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmrb8I1K5jjNr7ZrLSvgmkeQGjYauPeGJU" + nickname="Martin" + subject="comment 8" + date="2013-08-18T16:44:02Z" + content=""" +Any chance that older versions of Android will be supported in the future? +"""]] diff --git a/doc/install/Debian.mdwn b/doc/install/Debian.mdwn index 045531b345..2158794b18 100644 --- a/doc/install/Debian.mdwn +++ b/doc/install/Debian.mdwn @@ -7,7 +7,7 @@ sudo apt-get install git-annex Note: This version does not include support for the [[assistant]]. -The version of git-annex in unstable can be easily installed in wheezy. +A backport is available with the assistant and other new features. ## Debian 6.0 "squeeze" diff --git a/doc/install/Debian/comment_14_a34e23d9aa3027012ab1236aa4f7d5cb._comment b/doc/install/Debian/comment_14_a34e23d9aa3027012ab1236aa4f7d5cb._comment new file mode 100644 index 0000000000..86f1d60502 --- /dev/null +++ b/doc/install/Debian/comment_14_a34e23d9aa3027012ab1236aa4f7d5cb._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="Miles" + ip="88.175.62.104" + subject="installed git-annex on debian but cannot find it" + date="2013-08-19T23:29:24Z" + content=""" +I am an absolute beginner when it comes to linux in debian in particular. I installed git-annex via the root terminal, but now I do not know where to find it. I searched for in the file system but could not locate it. Any help is appreciated. +"""]] diff --git a/doc/install/Debian/comment_15_20d8271ba3f6cfe3c8849c3d41607630._comment b/doc/install/Debian/comment_15_20d8271ba3f6cfe3c8849c3d41607630._comment new file mode 100644 index 0000000000..6f32c2b0b8 --- /dev/null +++ b/doc/install/Debian/comment_15_20d8271ba3f6cfe3c8849c3d41607630._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawk_GWOEjK4Sn4hUB6ofFlE3CNeC7tO56J8" + nickname="John" + subject="Re: installed git-annex on debian but cannot find it " + date="2013-08-20T00:50:28Z" + content=""" +@Miles - The command is git annex webapp to bring up the web interface. +"""]] diff --git a/doc/install/cabal/comment_14_14b46470593f84f8c3768a91cb77bdab._comment b/doc/install/cabal/comment_14_14b46470593f84f8c3768a91cb77bdab._comment new file mode 100644 index 0000000000..93fca16531 --- /dev/null +++ b/doc/install/cabal/comment_14_14b46470593f84f8c3768a91cb77bdab._comment @@ -0,0 +1,9 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawlfIVXjkzrYE9qJAO2A0H7K6tKGMaSgc3U" + nickname="Daniel" + subject="Problems with cryptocipher" + date="2013-08-22T01:36:50Z" + content=""" +I had problems following these directions on recent releases of Fedora/Ubuntu. The install attempts failed on cryptocipher-0.3.1, which I think came as a dependency of Yesod. +I was able to work around this by installing yesod-platform with cabal first, then installing git-annex. +"""]] diff --git a/doc/install/cabal/comment_15_c3a5b0aad28a90e0bb8da31a430578eb._comment b/doc/install/cabal/comment_15_c3a5b0aad28a90e0bb8da31a430578eb._comment new file mode 100644 index 0000000000..fc64af2341 --- /dev/null +++ b/doc/install/cabal/comment_15_c3a5b0aad28a90e0bb8da31a430578eb._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="RaspberryPie" + ip="77.247.181.162" + subject="git-annex assistant on Arm" + date="2013-08-23T03:07:11Z" + content=""" +I'd like to use the assistant's power on a Raspberry Pi to build an always-on file/sync server. Is there a way to get the assistant running on Arm? I know there's a Debian package, but it's Version 3.20120629 and comes without the assistant. Has anyone ever successfully built a recent git-annex version on Arm? What would I need in order to do it myself? +"""]] diff --git a/doc/install/cabal/comment_16_4faf214f97f9516898d7c17d743ef825._comment b/doc/install/cabal/comment_16_4faf214f97f9516898d7c17d743ef825._comment new file mode 100644 index 0000000000..be14b39081 --- /dev/null +++ b/doc/install/cabal/comment_16_4faf214f97f9516898d7c17d743ef825._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 16" + date="2013-08-23T17:37:52Z" + content=""" +The git-annex assistant can easily be built on arm. But not the webapp. It's entirely possible to use the assistant without the webapp though; you just have to make the git repository and configure the remotes by hand, and then the assistant will sync them the same way the webapp does. + +It is possible but very involved to build the webapp for arm. I do not anticipate doing it in the Debian package until ghc gets proper template haskell support for arm. See [[forum/Webapp_on_ARM]] +"""]] diff --git a/doc/install/cabal/comment_17_2a9d6807a3a13815c824985521757167._comment b/doc/install/cabal/comment_17_2a9d6807a3a13815c824985521757167._comment new file mode 100644 index 0000000000..c0b570dfb6 --- /dev/null +++ b/doc/install/cabal/comment_17_2a9d6807a3a13815c824985521757167._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="RaspberryPie" + ip="77.247.181.162" + subject="comment 17" + date="2013-08-23T18:51:51Z" + content=""" +Thanks for the quick answer. I will try to build git-annex with just the assistant, as you suggest, and once it works set up the server by hand as you suggest. + +BTW: Awesome job you're doing with git-annex. I appreciate your enthusiasm. +"""]] diff --git a/doc/install/fromscratch.mdwn b/doc/install/fromscratch.mdwn index 63d4b1cbb8..17444a4fd8 100644 --- a/doc/install/fromscratch.mdwn +++ b/doc/install/fromscratch.mdwn @@ -11,6 +11,7 @@ quite a lot. * [monad-control](http://hackage.haskell.org/package/monad-control) * [QuickCheck 2](http://hackage.haskell.org/package/QuickCheck) * [json](http://hackage.haskell.org/package/json) + * [aeson](http://hackage.haskell.org/package/aeson) * [IfElse](http://hackage.haskell.org/package/IfElse) * [dlist](http://hackage.haskell.org/package/dlist) * [bloomfilter](http://hackage.haskell.org/package/bloomfilter) diff --git a/doc/news/version_4.20130815.mdwn b/doc/news/version_4.20130815.mdwn new file mode 100644 index 0000000000..3c83b40734 --- /dev/null +++ b/doc/news/version_4.20130815.mdwn @@ -0,0 +1,11 @@ +git-annex 4.20130815 released with [[!toggle text="these changes"]] +[[!toggleable text=""" + * assistant, watcher: .gitignore files and other git ignores are now + honored, when git 1.8.4 or newer is installed. + (Thanks, Adam Spiers, for getting the necessary support into git for this.) + * importfeed: Ignores transient problems with feeds. Only exits nonzero + when a feed has repeatedly had a problems for at least 1 day. + * importfeed: Fix handling of dots in extensions. + * Windows: Added support for encrypted special remotes. + * Windows: Fixed permissions problem that prevented removing files + from directory special remote. Directory special remotes now fully usable."""]] \ No newline at end of file diff --git a/doc/related_software.mdwn b/doc/related_software.mdwn index 4a8bc78ac6..024a155e3b 100644 --- a/doc/related_software.mdwn +++ b/doc/related_software.mdwn @@ -9,3 +9,4 @@ designed to interoperate with it. is git-annex aware. * [sizes](http://hackage.haskell.org/package/sizes) is another du-like utility, with a `-A` switch that enables git-annex support. +* Emacs Org mode can auto-commit attached files to git-annex. diff --git a/doc/special_remotes.mdwn b/doc/special_remotes.mdwn index 978989503b..a0102fcaaa 100644 --- a/doc/special_remotes.mdwn +++ b/doc/special_remotes.mdwn @@ -18,7 +18,15 @@ They cannot be used by other git commands though. * [[hook]] The above special remotes can be used to tie git-annex -into many cloud services. Here are specific instructions +into many cloud services. + +There are many use cases for a special remote. You could use it as a backup. You could use it to archive files offline in a drive with encryption enabled so if the drive is stolen your data is not. You could git annex move --to specialremote large files when your local drive is getting full, and then git annex move the files back when free space is again available. You could have one repository copy files to a special remote, and then git annex get them on another repository, to transfer the files between computers that do not communicate directly. + +The git-annex assistant makes it easy to set up rsync remotes using this last scenario, which is referred to as a transfer repository, and arranges to drop files from the transfer repository once they have been transferred to all known clients. + +None of these use cases are particular to particular special remote types. Most special remotes can all be used in these and other ways. It largely doesn't matter for your use what underlying transport the special remote uses. + +Here are specific instructions for various cloud things: * [[Amazon_S3|tips/using_Amazon_S3]] diff --git a/doc/special_remotes/S3/comment_15_ceb9048c743135f6beca57a23505f0a3._comment b/doc/special_remotes/S3/comment_15_ceb9048c743135f6beca57a23505f0a3._comment new file mode 100644 index 0000000000..a8b5573e77 --- /dev/null +++ b/doc/special_remotes/S3/comment_15_ceb9048c743135f6beca57a23505f0a3._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawne_amN4fko4p5cRY_9EYwaYuJKNn7LRio" + nickname="Tobias" + subject="different s3 storage URLs" + date="2013-08-23T08:59:32Z" + content=""" +Is it possible to change the S3 endpoint hosts? I'm running a radosgw with S3 support which I'd like to define as S3 remote for git-annex +"""]] diff --git a/doc/special_remotes/S3/comment_16_7b79f8b5ef88a2775d61b5ac5774d3e0._comment b/doc/special_remotes/S3/comment_16_7b79f8b5ef88a2775d61b5ac5774d3e0._comment new file mode 100644 index 0000000000..508cedca43 --- /dev/null +++ b/doc/special_remotes/S3/comment_16_7b79f8b5ef88a2775d61b5ac5774d3e0._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 16" + date="2013-08-23T17:39:56Z" + content=""" +Yes, you can specify the host to use when setting up the remote. It's actually documented earlier on this very page, if ou search for \"host\". Any S3 compatabile host will probably work -- the Internet Archive's S3 does, for example. +"""]] diff --git a/doc/special_remotes/rsync/comment_10_43e8fa3517c1f5935f02ad06fbed63dc._comment b/doc/special_remotes/rsync/comment_10_43e8fa3517c1f5935f02ad06fbed63dc._comment new file mode 100644 index 0000000000..185bd97ec5 --- /dev/null +++ b/doc/special_remotes/rsync/comment_10_43e8fa3517c1f5935f02ad06fbed63dc._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://cstork.org/" + nickname="Chris Stork" + subject="comment 10" + date="2013-08-25T20:59:41Z" + content=""" +@joey I don't understand you last comment where you state that special remotes can act as transfer repositories \"to transfer the files between computers that do not communicate directly\". If there's no communication, ie git pushes or pulls, between the computers then they don't know what file names the files on the special remote map to. They need to somehow communicate the git repo too, don't they? +"""]] diff --git a/doc/special_remotes/rsync/comment_11_8cafc1a8b37e6fb056185ec058c0c3e8._comment b/doc/special_remotes/rsync/comment_11_8cafc1a8b37e6fb056185ec058c0c3e8._comment new file mode 100644 index 0000000000..c8fc8831ac --- /dev/null +++ b/doc/special_remotes/rsync/comment_11_8cafc1a8b37e6fb056185ec058c0c3e8._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 11" + date="2013-08-26T18:36:03Z" + content=""" +@Chris yes in that case you still need, a central git repository (which need not be on a host that supports git-annex), or the assistant can use xmpp to sync the git data. +"""]] diff --git a/doc/special_remotes/rsync/comment_7_e122979ea811d9ef835ba05bb936190f._comment b/doc/special_remotes/rsync/comment_7_e122979ea811d9ef835ba05bb936190f._comment new file mode 100644 index 0000000000..8cb1d72b49 --- /dev/null +++ b/doc/special_remotes/rsync/comment_7_e122979ea811d9ef835ba05bb936190f._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="rsync remote is basically more intended for backups ?" + date="2013-08-17T17:40:47Z" + content=""" +If I get it correctly, it is mainly useable as a backup, which will accumulate contents of the objects managed by git-annex over time. + +It would be great to have a use case illustrating its use in concrete matters. Thanks in advance. +"""]] diff --git a/doc/special_remotes/rsync/comment_8_d566113318d0aa7500d76ffe1bd46069._comment b/doc/special_remotes/rsync/comment_8_d566113318d0aa7500d76ffe1bd46069._comment new file mode 100644 index 0000000000..1e6bf8aa43 --- /dev/null +++ b/doc/special_remotes/rsync/comment_8_d566113318d0aa7500d76ffe1bd46069._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 8" + date="2013-08-22T18:02:00Z" + content=""" +There are many use cases for a rsync special remote. You could use it as a backup. You could use it to archive files offline in a drive with encryption enabled so if the drive is stolen your data is not. You could `git annex move --to rsyncremote` large files when your local drive is getting full, and then `git annex move` the files back when free space is again available. You could have one repository copy files to a rsync remote, and then `git annex get` them on another repository, to transfer the files between computers that do not communicate directly. The git-annex assistant makes it easy to set up rsync remotes using this last scenario, which is referred to as a transfer repository, and arranges to drop files from the transfer repository once they have been transferred to all known clients. + +None of these use cases are particular to rsync remotes. Most special remotes can all be used in these and other ways. It largely doesn't matter for your use what underlying transport the special remote uses. +"""]] diff --git a/doc/special_remotes/rsync/comment_9_5dcf10a502b2d4feac46b620d43e9d00._comment b/doc/special_remotes/rsync/comment_9_5dcf10a502b2d4feac46b620d43e9d00._comment new file mode 100644 index 0000000000..b7690cf685 --- /dev/null +++ b/doc/special_remotes/rsync/comment_9_5dcf10a502b2d4feac46b620d43e9d00._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Added use cases to "special remotes"" + date="2013-08-22T20:23:13Z" + content=""" +Thanks @joeyh. I've taken the liberty to add your use case description to [[special remotes]]. Hope this helps. +"""]] diff --git a/doc/special_remotes/web/comment_1_0bd570025f6cd551349ea88a4729ac8e._comment b/doc/special_remotes/web/comment_1_0bd570025f6cd551349ea88a4729ac8e._comment new file mode 100644 index 0000000000..d01e17da35 --- /dev/null +++ b/doc/special_remotes/web/comment_1_0bd570025f6cd551349ea88a4729ac8e._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://olivier.berger.myopenid.com/" + nickname="obergix" + subject="Which URL prefix are supported ?" + date="2013-08-17T08:44:05Z" + content=""" +It is not clear whether only http:// URLs are supported. Can you list others ? +"""]] diff --git a/doc/special_remotes/web/comment_2_333141cc9ec6c26ffd19aa95303a91e3._comment b/doc/special_remotes/web/comment_2_333141cc9ec6c26ffd19aa95303a91e3._comment new file mode 100644 index 0000000000..ff20181175 --- /dev/null +++ b/doc/special_remotes/web/comment_2_333141cc9ec6c26ffd19aa95303a91e3._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="2001:4978:f:21a::2" + subject="comment 2" + date="2013-08-17T08:59:11Z" + content=""" +When it says \"arbitrary urls\", it means it. The only requirement is that the url be well formed and that wget or whatever command you have it configured to use via annex.web-download-command knows how to download it. +"""]] diff --git a/doc/special_remotes/xmpp.mdwn b/doc/special_remotes/xmpp.mdwn index 4c13e659c7..33fa1a0811 100644 --- a/doc/special_remotes/xmpp.mdwn +++ b/doc/special_remotes/xmpp.mdwn @@ -21,16 +21,19 @@ any other git remote. Since XMPP requires a client that is continually running to see incoming pushes, the XMPP remote cannot be used with git at the command line. -Server support status. - -1. Gmail jabber server is working properly. (Google apps users will have to edit `.git/annex/creds/xmpp` manually) - -2. [[Prosody|http://prosody.im/]] and [[Metronome|http://www.lightwitch.org/]] daemons are working properly. - -3. Ejabberd is [[failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/]]. ([[Authentication bug|https://support.process-one.net/browse/EJAB-1632]]: Fixed in debian unstable with version 2.1.10-5) - -4. jabberd14 is [[failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/#comment-4ce5aeabd12ca3016290b3d8255f6ef1]]. (No further information) - -5. Openfire/Tigase/iChat Server/jabberd2 are unverified/untested. +## XMPP server support status +[[!table data=""" +Provider|Status|Type|Notes +[[Gmail|http://gmail.com]]|Working|?|Google apps users will have to configure `.git/annex/creds/xmpp` manually +[[Coderollers|http://www.coderollers.com/xmpp-server/]]|Working|[[Openfire|http://www.igniterealtime.org/projects/openfire/]] +[[jabber.me|http://jabber.me/]]|Working|[[Tigase|http://www.tigase.org/]] +[[xmpp.ru.net|https://www.xmpp.ru.net]]|Working|[[jabberd2|http://jabberd2.org/]] +[[jabber.org|http://jabber.org]]|Working|[[Isode M-Link|http://www.isode.com/products/m-link.html]] +-|Working|[[Prosody|http://prosody.im/]]|No providers tested. +-|Working|[[Metronome|http://www.lightwitch.org/]]|No providers tested. +-|[[Failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/]]|ejabberd|[[Authentication bug|https://support.process-one.net/browse/EJAB-1632]]: Fixed in debian unstable with version 2.1.10-5 +-|[[Failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/#comment-4ce5aeabd12ca3016290b3d8255f6ef1]]|jabberd14|No further information +"""]] +List of providers: [[http://xmpp.net/]] See also: [[xmpp_protocol_design_notes|design/assistant/xmpp]] diff --git a/doc/tips/beware_of_SSD_wear_when_doing_fsck_on_large_special_remotes/comment_3_72d222020af4a9c6c753eb1ee7e1f1cf._comment b/doc/tips/beware_of_SSD_wear_when_doing_fsck_on_large_special_remotes/comment_3_72d222020af4a9c6c753eb1ee7e1f1cf._comment new file mode 100644 index 0000000000..2624a4fd34 --- /dev/null +++ b/doc/tips/beware_of_SSD_wear_when_doing_fsck_on_large_special_remotes/comment_3_72d222020af4a9c6c753eb1ee7e1f1cf._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="guilhem" + ip="46.239.117.180" + subject="comment 3" + date="2013-08-19T01:05:40Z" + content=""" +A nice feature would be to perform the `fsck` on the (encrypted) remote itself, as it would avoid to clutter either the network or the tmpdir. However, that requires some changes in git-annex's backend. Indeed it would no longer be enough to store a single digest per (plain) file: a new digest needs to be stored for each encrypted copy. It is not necessarily a big deal, but the backend would need to be reorganized carefully. +"""]] diff --git a/doc/tips/downloading_podcasts/comment_18_382f2b970738d9b1af577955c3083e90._comment b/doc/tips/downloading_podcasts/comment_18_382f2b970738d9b1af577955c3083e90._comment new file mode 100644 index 0000000000..9e32443159 --- /dev/null +++ b/doc/tips/downloading_podcasts/comment_18_382f2b970738d9b1af577955c3083e90._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://www.joachim-breitner.de/" + nickname="nomeata" + subject="--fast and --relaxed" + date="2013-08-16T07:27:59Z" + content=""" +Hi, + +the explanations to --fast and --relaxed on this page could be extended a bit. I looked it up in the man page, but it is not yet clear to me when I would use one or the other with feeds. Also, does “Next time you run git annex addurl it will only fetch any new items.” really only apply to --relaxed, and not --fast? + +Furthermore, it would be good if there were a template variable `itemnum` that I can use to ensure that `ls` prints the casts in the right order, even when the titles of the items are not helpful. + +Greetings, +Joachim +"""]] diff --git a/doc/tips/downloading_podcasts/comment_19_f76fc6835e5787b0156380bf09fd81ca._comment b/doc/tips/downloading_podcasts/comment_19_f76fc6835e5787b0156380bf09fd81ca._comment new file mode 100644 index 0000000000..41313a87d1 --- /dev/null +++ b/doc/tips/downloading_podcasts/comment_19_f76fc6835e5787b0156380bf09fd81ca._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 19" + date="2013-08-22T15:25:02Z" + content=""" +I would expect user:pass@site.com to work if the site is using http basic auth. `importfeed` just runs `wget` (or `curl`) to do all downloads, and wget's documentation says that works. It also says you can use ~/.netrc to store the password for a site. +"""]] diff --git a/doc/tips/downloading_podcasts/comment_20_65ebf3a3bbf0a2aebd2b69640b757e16._comment b/doc/tips/downloading_podcasts/comment_20_65ebf3a3bbf0a2aebd2b69640b757e16._comment new file mode 100644 index 0000000000..6060be6557 --- /dev/null +++ b/doc/tips/downloading_podcasts/comment_20_65ebf3a3bbf0a2aebd2b69640b757e16._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 20" + date="2013-08-22T15:29:11Z" + content=""" +The git-annex man page has a bit more to say about --relaxed and --fast. Their behavior when used with `importfeed` is the same as with `addurl`. + +If the podcast feed provides an `itemid`, you can use that in the filename template. I don't know how common that is. Due to the way `importfeed` works, it cannot keep track of eg, an incrementing item number itself. +"""]] diff --git a/doc/tips/flickrannex/comment_13_cf9dad91ee7d334c720adb3310aa0003._comment b/doc/tips/flickrannex/comment_13_cf9dad91ee7d334c720adb3310aa0003._comment deleted file mode 100644 index 71d44aff56..0000000000 --- a/doc/tips/flickrannex/comment_13_cf9dad91ee7d334c720adb3310aa0003._comment +++ /dev/null @@ -1,130 +0,0 @@ -[[!comment format=mdwn - username="https://www.google.com/accounts/o8/id?id=AItOawnaH44G3QbxBAYyDwy0PbvL0ls60XoaR3Y" - nickname="Nigel" - subject="re: git annex get failed -- debug" - date="2013-08-02T15:28:41Z" - content=""" -With debug turned on. - -[[!format bash \"\"\" - -initremote flickr (encryption setup) (shared cipher) ok -(Recording state in git...) -describe flickr ok -(Recording state in git...) -/home/nrb/repos/annex/laptop-annex -fsck walkthrough.sh (checksum...) ok -fsck walkthrough.sh~ (checksum...) ok -/home/nrb/repos/annex/laptop-annex -copy walkthrough.sh (gpg) (checking flickr...) 16:18:52 [flickrannex-0.1.5] : 'START' -16:18:52 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=checkpresent ANNEX_KEY=GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 ANNEX_HASH_1=kQ ANNEX_HASH_2=0P /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:18:52 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:18:52 [flickrannex-0.1.5] readFile : 'Done' -16:18:52 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:18:54 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:18:54 [flickrannex-0.1.5] main : 'Trying page: 1' -16:18:55 [flickrannex-0.1.5] main : 'Error. found nothing:{'pages': '1', 'cancreate': '1', 'total': '0', 'page': '1', 'perpage': '0'}' -16:18:55 [flickrannex-0.1.5] checkFile : 'GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 - u'gitannex' - '8086216@N08'' -16:18:55 [flickrannex-0.1.5] checkFile : 'No set exists, thus no files exists' -16:18:55 [flickrannex-0.1.5] : 'STOP: 2s' -(to flickr...) -16:18:55 [flickrannex-0.1.5] : 'START' -16:18:55 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=store ANNEX_KEY=GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 ANNEX_HASH_1=kQ ANNEX_HASH_2=0P ANNEX_FILE=/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:18:55 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:18:55 [flickrannex-0.1.5] readFile : 'Done' -16:18:55 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:18:57 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:18:58 [flickrannex-0.1.5] main : 'Trying page: 1' -16:18:58 [flickrannex-0.1.5] main : 'Error. found nothing:{'pages': '1', 'cancreate': '1', 'total': '0', 'page': '1', 'perpage': '0'}' -16:18:58 [flickrannex-0.1.5] postFile : '/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 to u'gitannex' - GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0' -16:18:58 [flickrannex-0.1.5] postFile : 'pre /home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 size: 1047 more than 40234050.' -16:18:58 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0' - 'rb'' -16:18:58 [flickrannex-0.1.5] readFile : 'Done' -16:18:58 [flickrannex-0.1.5] postFile : 'Uploading: /home/nrb/repos/gits/flickrannex/temp/encoded-GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0' -/home/nrb/repos/gits/flickrannex/flickrannex.py:92: FutureWarning: The behavior of this method will change in future versions. Use specific 'len(elem)' or 'elem is not None' test instead. - if res: -/home/nrb/repos/gits/flickrannex/flickrannex.py:100: FutureWarning: The behavior of this method will change in future versions. Use specific 'len(elem)' or 'elem is not None' test instead. - if res: -16:19:01 [flickrannex-0.1.5] postFile : 'Done: ' -16:19:01 [flickrannex-0.1.5] : 'STOP: 5s' -ok -copy walkthrough.sh~ (checking flickr...) 16:19:01 [flickrannex-0.1.5] : 'START' -16:19:01 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=checkpresent ANNEX_KEY=GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 ANNEX_HASH_1=m5 ANNEX_HASH_2=kz /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:19:01 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:19:01 [flickrannex-0.1.5] readFile : 'Done' -16:19:01 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:19:03 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:19:03 [flickrannex-0.1.5] main : 'Photoset gitannex found: ' -16:19:03 [flickrannex-0.1.5] main : 'Trying page: 1' -16:19:03 [flickrannex-0.1.5] checkFile : 'GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 - 72157634897264995L - '8086216@N08'' -16:19:03 [flickrannex-0.1.5] checkFile : 'No set exists, thus no files exists' -16:19:03 [flickrannex-0.1.5] : 'STOP: 1s' -(to flickr...) -16:19:03 [flickrannex-0.1.5] : 'START' -16:19:03 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=store ANNEX_KEY=GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 ANNEX_HASH_1=m5 ANNEX_HASH_2=kz ANNEX_FILE=/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:19:03 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:19:03 [flickrannex-0.1.5] readFile : 'Done' -16:19:03 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:19:05 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:19:05 [flickrannex-0.1.5] main : 'Photoset gitannex found: ' -16:19:05 [flickrannex-0.1.5] main : 'Trying page: 1' -16:19:05 [flickrannex-0.1.5] postFile : '/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 to 72157634897264995L - GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9' -16:19:05 [flickrannex-0.1.5] postFile : 'pre /home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 size: 1044 more than 40234050.' -16:19:05 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/annex/laptop-annex/.git/annex/tmp/GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9' - 'rb'' -16:19:05 [flickrannex-0.1.5] readFile : 'Done' -16:19:05 [flickrannex-0.1.5] postFile : 'Uploading: /home/nrb/repos/gits/flickrannex/temp/encoded-GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9' -/home/nrb/repos/gits/flickrannex/flickrannex.py:92: FutureWarning: The behavior of this method will change in future versions. Use specific 'len(elem)' or 'elem is not None' test instead. - if res: -/home/nrb/repos/gits/flickrannex/flickrannex.py:100: FutureWarning: The behavior of this method will change in future versions. Use specific 'len(elem)' or 'elem is not None' test instead. - if res: -16:19:08 [flickrannex-0.1.5] postFile : 'Done: ' -16:19:08 [flickrannex-0.1.5] : 'STOP: 4s' -ok -(Recording state in git...) -nrb@nrb-ThinkPad-T61:~/repos/annex/laptop-annex$ git annex whereis -whereis walkthrough.sh (3 copies) - 86491ded-899c-425d-9470-bf446cb06db1 -- flickr (the flickr library) - 8e766014-7154-4f4f-a04b-9d1b3d333db1 -- here (my laptop) - eed7055b-743b-4ab6-a390-29cfd326005d -- usbdrive (portable USB drive) -ok -whereis walkthrough.sh~ (3 copies) - 86491ded-899c-425d-9470-bf446cb06db1 -- flickr (the flickr library) - 8e766014-7154-4f4f-a04b-9d1b3d333db1 -- here (my laptop) - eed7055b-743b-4ab6-a390-29cfd326005d -- usbdrive (portable USB drive) -ok -nrb@nrb-ThinkPad-T61:~/repos/annex/laptop-annex$ git annex fsck --from flickr -fsck walkthrough.sh (gpg) (checking flickr...) 16:22:57 [flickrannex-0.1.5] : 'START' -16:22:57 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=checkpresent ANNEX_KEY=GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 ANNEX_HASH_1=kQ ANNEX_HASH_2=0P /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:22:57 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:22:57 [flickrannex-0.1.5] readFile : 'Done' -16:22:57 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:22:58 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:22:59 [flickrannex-0.1.5] main : 'Photoset gitannex found: ' -16:22:59 [flickrannex-0.1.5] main : 'Trying page: 1' -16:22:59 [flickrannex-0.1.5] checkFile : 'GPGHMACSHA1--280dd2d5003ad3962b1ecaa52ba45fdd44381fd0 - 72157634897264995L - '8086216@N08'' -16:22:59 [flickrannex-0.1.5] checkFile : 'No set exists, thus no files exists' -16:22:59 [flickrannex-0.1.5] : 'STOP: 2s' -(fixing location log) - ** Based on the location log, walkthrough.sh - ** was expected to be present, but its content is missing. -failed -fsck walkthrough.sh~ (checking flickr...) 16:22:59 [flickrannex-0.1.5] : 'START' -16:22:59 [flickrannex-0.1.5] main : 'ARGS: 'ANNEX_ACTION=checkpresent ANNEX_KEY=GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 ANNEX_HASH_1=m5 ANNEX_HASH_2=kz /home/nrb/repos/gits/flickrannex/flickrannex.py --dbglevel 1 --stderr'' -16:22:59 [flickrannex-0.1.5] readFile : ''/home/nrb/repos/gits/flickrannex/flickrannex.conf' - 'r'' -16:22:59 [flickrannex-0.1.5] readFile : 'Done' -16:22:59 [flickrannex-0.1.5] login : 'nrbray@yahoo.com' -16:23:01 [flickrannex-0.1.5] login : 'Done: '72157633920418017-5c0274bd421d7bb1' - None - '8086216@N08'' -16:23:01 [flickrannex-0.1.5] main : 'Photoset gitannex found: ' -16:23:01 [flickrannex-0.1.5] main : 'Trying page: 1' -16:23:01 [flickrannex-0.1.5] checkFile : 'GPGHMACSHA1--131f95d3bc932d23ef6af47cf49db3c04be4f0f9 - 72157634897264995L - '8086216@N08'' -16:23:01 [flickrannex-0.1.5] checkFile : 'No set exists, thus no files exists' -16:23:01 [flickrannex-0.1.5] : 'STOP: 1s' -(fixing location log) - ** Based on the location log, walkthrough.sh~ - ** was expected to be present, but its content is missing. -failed -(Recording state in git...) -git-annex: fsck: 2 failed - -\"\"\" ]] -"""]] diff --git a/doc/tips/imapannex.mdwn b/doc/tips/imapannex.mdwn new file mode 100644 index 0000000000..594687db49 --- /dev/null +++ b/doc/tips/imapannex.mdwn @@ -0,0 +1,27 @@ +imapannex +========= + +Hook program for gitannex to use imap as backend + +# Requirements: + + python2 + +# Install +Clone the git repository in your home folder. + + git clone git://github.com/TobiasTheViking/imapannex.git + +This should make a ~/imapannex folder + +# Setup +Run the program once to set it up. + + cd ~/imapannex; python2 imapannex.py + +# Commands for gitannex: + + git config annex.imap-hook '/usr/bin/python2 ~/imapannex/imapannex.py' + git annex initremote imap type=hook hooktype=imap encryption=shared + git annex describe imap "the imap library" + git annex content imap exclude=largerthan=30mb diff --git a/doc/tips/powerful_file_matching.mdwn b/doc/tips/powerful_file_matching.mdwn index d5d29377c4..47f8c8a64c 100644 --- a/doc/tips/powerful_file_matching.mdwn +++ b/doc/tips/powerful_file_matching.mdwn @@ -1,4 +1,4 @@ -git-annex has a powerful syntax for making it act on only certian files. +git-annex has a powerful syntax for making it act on only certain files. The simplest thing is to exclude some files, using wild cards: diff --git a/doc/tips/setup_a_public_repository_on_a_web_site.mdwn b/doc/tips/setup_a_public_repository_on_a_web_site.mdwn index e1fbd1e473..39b2912188 100644 --- a/doc/tips/setup_a_public_repository_on_a_web_site.mdwn +++ b/doc/tips/setup_a_public_repository_on_a_web_site.mdwn @@ -20,12 +20,34 @@ Here's how I set it up. --[[Joey]] 7. Instruct advanced users to clone a http url that ends with the "/.git/" directory. For example, for downloads.kitenet.net, the clone url is `https://downloads.kitenet.net/.git/` -8. Set up a git `post-receive` hook that runs `git annex merge`, and - the repository's working tree will automatically be updated when - you run `git annex sync` in a clone that can push to the repository. - (Needs git-annex version 4.20130703 or newer; older versions - can use `git annex sync` in the post-receive hook instead.) +8. Set up a git `post-receive` hook to update the repository's working tree + when changes are pushed to it. See below for details. When users clone over http, and run git-annex, it will automatically learn all about your repository and be able to download files right out of it, also using http. + +## post-receive hook + +If you have git-annex 4.20130703, the post-receive hook mentioned above +in step 8 just needs to run `git annex merge`. + +With older versions of git-annex, you can instead use `git annex sync`. + +There are two gotchas with some versions of git to be aware of when writing +this post-receive hook. + +1. The hook may be run with the current directory set to the `.git` + directory, and not the top of your work tree. So you need to `cd ..` or + similar in the hook. +2. `GIT_DIR` may be set to `.`, which will not be right after changing + directory. So you will probably want to unset it. + +Here's a post-receive hook that takes these problems into account: + +
+#!/bin/sh
+unset GIT_DIR
+cd ..
+git annex merge
+
diff --git a/doc/tips/using_the_web_as_a_special_remote.mdwn b/doc/tips/using_the_web_as_a_special_remote.mdwn index 3ce02a56a8..05b5e03a48 100644 --- a/doc/tips/using_the_web_as_a_special_remote.mdwn +++ b/doc/tips/using_the_web_as_a_special_remote.mdwn @@ -8,10 +8,16 @@ The web can be used as a [[special_remote|special_remotes]] too. Now the file is downloaded, and has been added to the annex like any other file. So it can be renamed, copied to other repositories, and so on. +To add a lot of urls at once, just list them all as parameters to +`git annex addurl`. + +## trust issues + Note that git-annex assumes that, if the web site does not 404, and has the right file size, the file is still present on the web, and this counts as -one [[copy|copies]] of the file. So it will let you remove your last copy, -trusting it can be downloaded again: +one [[copy|copies]] of the file. If the file still seems to be present +on the web, it will let you remove your last copy, trusting it can be +downloaded again: # git annex drop example.com_video.mpeg drop example.com_video.mpeg (checking http://example.com/video.mpeg) ok @@ -31,7 +37,9 @@ With the result that it will hang onto files: (Use --force to override this check, or adjust annex.numcopies.) failed -You can also add urls to any file already in the annex: +## attaching urls to existing files + +You can also attach urls to any file already in the annex: # git annex addurl --file my_cool_big_file http://example.com/cool_big_file addurl my_cool_big_file ok @@ -40,8 +48,10 @@ You can also add urls to any file already in the annex: 00000000-0000-0000-0000-000000000001 -- web 27a9510c-760a-11e1-b9a0-c731d2b77df9 -- here -To add a lot of urls at once, just list them all as parameters to -`git annex addurl`. +## configuring filenames + +By default, `addurl` will generate a filename for you. You can use +`--file=` to specify the filename to use. If you're adding a bunch of related files to a directory, or just don't like the default filenames generated by `addurl`, you can use `--pathdepth` @@ -55,3 +65,37 @@ number takes that many paths from the end. addurl 2012_01_video.mpeg (downloading http://example.com/videos/2012/01/video.mpeg) # git annex addurl http://example.com/videos/2012/01/video.mpeg --pathdepth=-2 addurl 01_video.mpeg (downloading http://example.com/videos/2012/01/video.mpeg) + +## videos + + + +There's support for downloading videos from sites like YouTube, Vimeo, +and many more. This relies on [quvi](http://quvi.sourceforge.net/) to find +urls to the actual videos files. + +When you have quvi installed, you can just +`git annex addurl http://youtube.com/foo` and it will detect that +it is a video and download the video content for offline viewing. + +Later, in another clone of the repository, you can run `git annex get` on +the file and it will also be downloaded with the help of quvi. This works +even if the video host has transcoded or otherwise changed the video +in the meantime; the assumption is that these video files are equivilant. + +There is an `annex.quvi-options` configuration setting that can be used +to pass parameters to quvi. For example, you could set `git config +annex.quvi-options "--format low"` to configure it to download low +quality videos from YouTube. + +Note that for performance reasons, the url is not checked for redirects, +so some shortened urls will not be detected. You can +either load the short url in a browser to get the full url, or you +can force use of quvi with redirect detection, by prepending "quvi:" to the +url. + +Downloading whole YouTube playlists is not currently supported by quvi. + +## podcasts + +This is done using `git annex importfeed`. See [[downloading podcasts]]. diff --git a/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_5_677e958c3f2effec7528b484aeb6478d._comment b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_5_677e958c3f2effec7528b484aeb6478d._comment new file mode 100644 index 0000000000..07b001c2ef --- /dev/null +++ b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_5_677e958c3f2effec7528b484aeb6478d._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawm5iosFbL2By7UFeViqkc6v-hoAtqILeDA" + nickname="Laszlo" + subject="comment 5" + date="2013-08-25T07:48:18Z" + content=""" +What is the problem with bittorrent protocol in general? +It is some technicality or purely philosophical? + +Best, + Laszlo + +"""]] diff --git a/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_6_56e53803fdede895cba717e6b6e9a1bb._comment b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_6_56e53803fdede895cba717e6b6e9a1bb._comment new file mode 100644 index 0000000000..41e1bda786 --- /dev/null +++ b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync/comment_6_56e53803fdede895cba717e6b6e9a1bb._comment @@ -0,0 +1,23 @@ +[[!comment format=mdwn + username="https://www.google.com/accounts/o8/id?id=AItOawmkBwMWvNKZZCge_YqobCSILPMeK6xbFw8" + nickname="develop" + subject="comment 6" + date="2013-08-25T08:39:15Z" + content=""" +I just did a cursory search on haskell torrent support. And the required pieces do seem to be be there. +https://github.com/jlouis/combinatorrent or https://github.com/astro/haskell-torrent for downloading. i'm not sure if either supports DHT, but that exists here https://github.com/aninhumer/haskell-dht + +That said, i think implementing this would require some quite major overhauls in the system. It probably won't be trivial to implement. + +Note: This is for straight \"bittorrent\", not for \"bittorrent sync\". Bittorrent sync is closed source, and while an API might come at some point, it doesn't currently exist. + +I do seem to recall joeyh talking about supporting further transport protocols(perhaps through hooks). So I'm adding the above links for future reference if this does get implemented. + +But IMHO, this doesn't seem like a trivial feature to add. It might have to take some refactoring of some core git-annex parts. Certain things have to be changed quite a bit. + +Currently a git-annex client doesn't really require anything(except rsync) to sync from a remote. With bittorrent with DHT support to share between clients, suddenly git-annex will have to maintain a constant bittorrent thread(maybe multiple) that constantly seeds all the files in the git-annex repository, while waiting for a potential remote to request data. + +So even if this happens, it is probably gonna take some time. + +Just my 2cents. +"""]] diff --git a/doc/todo/__96__git_annex_import_--lazy__96___--_Delete_everything_that__39__s_in_the_source_directory_and_also_in_the_target_annex.mdwn b/doc/todo/__96__git_annex_import_--lazy__96___--_Delete_everything_that__39__s_in_the_source_directory_and_also_in_the_target_annex.mdwn index c3f6816856..996c03461c 100644 --- a/doc/todo/__96__git_annex_import_--lazy__96___--_Delete_everything_that__39__s_in_the_source_directory_and_also_in_the_target_annex.mdwn +++ b/doc/todo/__96__git_annex_import_--lazy__96___--_Delete_everything_that__39__s_in_the_source_directory_and_also_in_the_target_annex.mdwn @@ -24,3 +24,6 @@ As per IRC 01:04:31 < RichiH> thus i would rather see this upstream and not hacked locally The only failure mode I see in the above is "file has been dropped elsewhere, numcopies not fulfilled, but that info is not synched to the local repo, yet" -- This could be worked around by always importing the data. + +> [[done]] as `git annex import --deduplicate`. +> --[[Joey]] diff --git a/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn b/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn new file mode 100644 index 0000000000..d48b4426f3 --- /dev/null +++ b/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn @@ -0,0 +1,3 @@ +As per DebConf13: Introduce a one-shot command to synchronize everything, including data, with the other remotes. + +Especially useful for the debconf annex. diff --git a/doc/todo/add_metadata_to_annexed_files/comment_1_38af9b352020194e9ace34d7dde188cf._comment b/doc/todo/add_metadata_to_annexed_files/comment_1_38af9b352020194e9ace34d7dde188cf._comment new file mode 100644 index 0000000000..8460300a79 --- /dev/null +++ b/doc/todo/add_metadata_to_annexed_files/comment_1_38af9b352020194e9ace34d7dde188cf._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T19:58:54Z" + content=""" +I don't know if git-annex is the right vehicle to fix this. It seems that a more generic fix that would work in non-git-annex repos would be better. + +I can answer your question though: The metadata such as urls and locations that git-annex stores in the git-annex branch is attached to objects, and not to work tree paths. +"""]] diff --git a/doc/todo/faster_gnupg_cipher/comment_3_bd0c975494333dfe558de048d888ace8._comment b/doc/todo/faster_gnupg_cipher/comment_3_bd0c975494333dfe558de048d888ace8._comment new file mode 100644 index 0000000000..d0b98b7f67 --- /dev/null +++ b/doc/todo/faster_gnupg_cipher/comment_3_bd0c975494333dfe558de048d888ace8._comment @@ -0,0 +1,17 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 3" + date="2013-08-19T13:44:35Z" + content=""" +AES-NI acceleration will be used by default providing you're using +the new modularized GnuPG (v2.x) and libgcrypt ≥ 1.5.0. Of course it +only speeds up AES encryption, while GnuPG uses CAST by default; you can +either set `personal-cipher-preferences` to AES or AES256 in your +`gpg.conf` or, as joeyh hinted at, set `remote..annex-gnupg-options` +as described in the manpage. + +By the way, I observed a significant speed up when using `--compress-algo none`. +Image, music and video files are typically hard to compress further, and it seems +that's where gpg spent most of its time, at least on the few files I benchmarked. +"""]] diff --git a/doc/todo/sync_my_local_git-annex_from_a_dump_remote/comment_3_b9f73375e2c732e798495f8ee6970c7c._comment b/doc/todo/sync_my_local_git-annex_from_a_dump_remote/comment_3_b9f73375e2c732e798495f8ee6970c7c._comment new file mode 100644 index 0000000000..df4be033bb --- /dev/null +++ b/doc/todo/sync_my_local_git-annex_from_a_dump_remote/comment_3_b9f73375e2c732e798495f8ee6970c7c._comment @@ -0,0 +1,14 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 3" + date="2013-08-24T16:35:33Z" + content=""" +Seems to me that this could easily be dealt with by installing git-annex on the webserver, making the directory there a git repository, and using either a cron job or `git annex watch` to commit files as they were changed there. + +Then you can make a direct mode, indirect mode, or even a bare clone on your local machine and use git-annex to get the files. + +Maybe you have good reasons for not wanting to go that route. And rsync on a direct mode repository should work, provided to tell it to not delete `.git`. :P I don't see any way to make rsync work in an indirect mode repository. As for trying to make git-annex handle this import over rsync itself in a way that would work in an indirect mode repository, let alone a bare repository -- I don't see a good way to do it and it seems quite special case and likely to get quite complicated to implement. + +In the meantime, I did implement `git annex mirror`, which I think is a much more interesting and generally useful tool to have. And could even be used in my recommended solution above. +"""]] diff --git a/doc/todo/wishlist:_Freeing_X_space_on_remote_Y.mdwn b/doc/todo/wishlist:_Freeing_X_space_on_remote_Y.mdwn new file mode 100644 index 0000000000..5fec39d98f --- /dev/null +++ b/doc/todo/wishlist:_Freeing_X_space_on_remote_Y.mdwn @@ -0,0 +1 @@ +As suggested during the first Gitify BoF during DebConf13: Adding a way to have on-demand dropping of content in a given remote would allow a user to quickly free up disk space on demand while still heeding numcopies etc. diff --git a/doc/todo/wishlist:___96__git_annex_drop_--relaxed__96__.mdwn b/doc/todo/wishlist:___96__git_annex_drop_--relaxed__96__.mdwn new file mode 100644 index 0000000000..626f5a03f9 --- /dev/null +++ b/doc/todo/wishlist:___96__git_annex_drop_--relaxed__96__.mdwn @@ -0,0 +1,5 @@ +Also suggested during the first Gitify BoF during DebConf13: + +`git annex drop` deletes immediately. In some situations a mechanism to tell git-annex "I would like to hold onto this data if possible, but if you need the space, please delete it" could be nice. + +An obvious question would be how to do cleanups. With the assistant, that's easy. On CLI, at the very least `git annex fsck` should list, and optionally delete, that data. diff --git a/doc/todo/wishlist:_dropping_git-annex_history.mdwn b/doc/todo/wishlist:_dropping_git-annex_history.mdwn new file mode 100644 index 0000000000..7aa2158076 --- /dev/null +++ b/doc/todo/wishlist:_dropping_git-annex_history.mdwn @@ -0,0 +1,26 @@ +In real life discussions with git-annex users at DebConf, the idea was proposed to have a way to drop the history of the git-annex branch, and replace it with a new branch with just the current state of the repository. + +The only thing that breaks when this is done, in theory, is `git annex log`, which can't show the location history +of files. + +The crucial thing is that this operation would only need to be done in one repository, and it would then record some information in its (new) git-annex branch, so when it was pushed to other repositories, git-annex there could notice that history had been dropped, and do the same. So, even if you have rarely used offline archive repositories, the history dropping would eventually reach them, without needing to remember to do it. + +There was speculation that it would be enough to record eg, the SHA of the top commit on the old branch. That may not be good enough, because another remote may have not gotten that SHA into its branch yet, or may have commits on top of that SHA. + +Maybe instead we want to record the SHA of the *first* commit to the old git-annex branch. This way, we can tell if the branch that got deleted is the one we're currently using. And if it is, we create a new branch with the current state of *our* branch, and then union merge the other branch into it. + +Hmm, another wrinkle is that, when this indication propigates from remote A to remote B, remote B may also have some git-annex branches available for remotes C and D, which have not transitioned, and E, which has transitioned already. It seems B should first union merge C and D into B, and then flatten B to B', and then union merge A and E into B'. + +I think that'd work! + +--[[Joey]] + +Will also allow dropping dead remotes from history. Just remove all +references to them when rewriting the branch. May or may not be desirable; +I sometimes care about dead remotes that I hope to one day recuscitate. +(OTOH, I can always run git annex fsck in them to get their location +tracking back, if I do manage to get them back.) + +--[[Joey]] + +See also : [[forum/safely_dropping_git-annex_history]] diff --git a/doc/todo/wishlist:_dropping_git-annex_history/comment_1_a4bee2e26b22a9bdaadc05b7227769ef._comment b/doc/todo/wishlist:_dropping_git-annex_history/comment_1_a4bee2e26b22a9bdaadc05b7227769ef._comment new file mode 100644 index 0000000000..043e674ed8 --- /dev/null +++ b/doc/todo/wishlist:_dropping_git-annex_history/comment_1_a4bee2e26b22a9bdaadc05b7227769ef._comment @@ -0,0 +1,10 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-24T19:39:45Z" + content=""" +BTW, a motivation for this is that some of us have old repositories that have been upgrades all the way from annex.version 1 and have a lot of cruft in them because of it. (I have repos that have been upgraded from annex.version 0, but this would not help with that cruft which is on the master branch!) + +Also, people worry that eg, a large copy back and forth bloats history, and having a way to unbloat it if it ever gets actually annoyingly bloated would stop them pestering me. ;) +"""]] diff --git a/doc/todo/wishlist:_perform_fsck_remotely.mdwn b/doc/todo/wishlist:_perform_fsck_remotely.mdwn new file mode 100644 index 0000000000..f2187d9122 --- /dev/null +++ b/doc/todo/wishlist:_perform_fsck_remotely.mdwn @@ -0,0 +1,39 @@ +Currently, when `fsck`'ing a remote, files are first downloaded to a temporary +file locally, decrypted if needed, and finally digested; the temporary file is +then either thrown away, or quarantined, depending on the value of that digest. + +Whereas this approach works with any kind of remote, in the particular case +where the user is granted execution rights on the digest command, one could +avoid cluttering the network and digest the file remotely. I propose the +addition of a per-remote git option `annex-remote-fsck` to switch between the +two behaviors. + + +There is an issue with encrypted specialremotes, though. As hinted at +[[here|tips/beware_of_SSD_wear_when_doing_fsck_on_large_special_remotes/#comment-70055f166f7eeca976021d24a736b471]], +since the digest of a ciphertext can't be deduced from that of a plaintext in +general one would needs, before sending an encrypted file to such a remote, to +digest it and store that digest somewhere (together with the cipher's size and +perhaps other meta-information). + +The usual directory structure (`.../.../{backend}-s{size}--{digest}.log`) seems +perfectly suitable to store these informations. Lines there would look like +`{timestamp}s {numcopy} {UUID} {remote digest}`. Of course, it implies that +remote digest commands are trustworthy (are doing the right thing), and that +the digest output are not tampered by others who have access to the git repo. +But that's outside the current threat model, I guess. + +Actually, since git-annex always includes a MDC in the ciphertexts, we could do +something clever and even avoid running a digest algorithm. According to the +[[OpenPGP standard|https://tools.ietf.org/html/rfc4880#section-5.14]] the MDC +is essentially a SHA-1 hash of the plaintext. I'm still investigating if it's +even possible, but in theory it would be enough (with non-chained ciphers at +least) to download a few bytes from the encrypted remote, decrypt those bytes +to retrieve the hash, and compare that hash with the known value. Of course +there is a downside here, namely that files tampered anywhere but on the MDC +packets would not be detected by `fsck` (but gpg will warn when decrypting the +file). + + +My 2 cents :-) Is there something I missed? I suppose there was a reason to +perform `fsck` locally at the first place... diff --git a/doc/todo/wishlist:_perform_fsck_remotely/comment_1_db92311dcdb1ef0ab0413f83e191c70c._comment b/doc/todo/wishlist:_perform_fsck_remotely/comment_1_db92311dcdb1ef0ab0413f83e191c70c._comment new file mode 100644 index 0000000000..6bf6af23ae --- /dev/null +++ b/doc/todo/wishlist:_perform_fsck_remotely/comment_1_db92311dcdb1ef0ab0413f83e191c70c._comment @@ -0,0 +1,15 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 1" + date="2013-08-22T15:18:35Z" + content=""" +The only reason fsck is done locally for remotes is ease of implementation and it being a generic operation that supports any kind of special remote. + +Seems that the the only types of remotes where a remote fsck is a possibility are some rsync remotes and git remotes. +git remotes already have git-annex installed, so the fsck could be run locally on the remote system using it. + +I don't know if I see a benefit with the MDC check. Any non-malicious data corruption on the remote is likely to affect the body of the file and not the small portion that holds the MDC. So checking the MDC does not seem much better than the current existence check done by `git annex fsck --fast --from remote`. + +As for storing the remote digest on the git-annex branch, my initial reaction was just that it's potentially a lot of bloat. Thinking about it some more, when using non-shared encryption, there is currently no way, given just a clone of a git repository, to match up files in git with encrypted objects stored on a special remote. So storing the remote digest might be considered to weaken the security. +"""]] diff --git a/doc/todo/wishlist:_perform_fsck_remotely/comment_2_2f0dbaf143d94290bfbebb6869eb7241._comment b/doc/todo/wishlist:_perform_fsck_remotely/comment_2_2f0dbaf143d94290bfbebb6869eb7241._comment new file mode 100644 index 0000000000..5418ff991e --- /dev/null +++ b/doc/todo/wishlist:_perform_fsck_remotely/comment_2_2f0dbaf143d94290bfbebb6869eb7241._comment @@ -0,0 +1,12 @@ +[[!comment format=mdwn + username="guilhem" + ip="129.16.20.209" + subject="comment 2" + date="2013-08-22T16:56:55Z" + content=""" +Oh yeah, the MDC paragraph was pretty much pointless indeed. Oops :-P + +I agree that this would potentially add some noise to the index, and weaken the +security, but depending on the threat model and people's preferences that's an +option that's worth considering IMHO. +"""]] diff --git a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote.mdwn b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote.mdwn index 3e08bb8d9f..229dc258b7 100644 --- a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote.mdwn +++ b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote.mdwn @@ -11,12 +11,12 @@ The [[Web special remote|special remotes/web]] could possibly be improved by det > > --[[Joey]] -> > There's a library for this called [quvi][] which supports many +> > There's a library for this called [quvi](http://quvi.sourceforge.net/) which supports many > > different sites and also allows fetching the URL (as opposed to just > > downloading the file). It seems to me this would be the best tool > > for this task. One problem to consider here is that a single youtube > > URL may yield different file contents depending on the quality > > chosen. Also, it seems that the URLs guessed by quvi may be > > ephemeral. --[[anarcat]] -> > -> > [quvi]: http://quvi.sourceforge.net/ + +> [[done]]!!! --[[Joey]] diff --git a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_2_81f7f893ac36c145b31f02db6a682a17._comment b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_2_81f7f893ac36c145b31f02db6a682a17._comment new file mode 100644 index 0000000000..a25b3c89d5 --- /dev/null +++ b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_2_81f7f893ac36c145b31f02db6a682a17._comment @@ -0,0 +1,20 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="quvi thoughts. excited!" + date="2013-08-22T18:22:51Z" + content=""" +Anarcat's quvi suggestion is interesting, because it seems to simplify the whole thing down to just `addurl`, which git-annex is already good at. + +If quvi manages to find the url that can be used to download the actual video file, without needing to run a special downloader, then all you really need, it seems, is `git annex addurl --relaxed $(quvi youtube-url)` The --relaxed will make git-annex not care if the content or size of the url's content varies in the future. Since --relaxed skips the actual download, you'd want to follow that with `git annex get`, since we don't know how long these urls will last.. + +I suppose git-annex could, if quvi is available, make any attempt to download a web special remote url that +matches the `quvi --support` output run the url through quvi to get the real url and download that instead. The difficulties with this approach: + +* would need to read and parse `quvi --support` every time it gets an url from the web special remote? (I don't think I'd want to link with libquvi, although that would be possible, just because this is an edge thing.) +* what it an url that had been supported stopped being supported -- we'd not want to download the raw url in that case +* putting the quvi support here doesn't allow relaxed mode to be set when `addurl` adds the url. + +Maybe it would be better to keep the support in `addurl`, and record the url generated by quvi. That url would probably be more likely to break in the future, but that kind of breakage is why `git annex untrust web` is wise.. +Keeping the support in `addurl` would also let it use the title that quvi also returns to determine the filename it creates. +"""]] diff --git a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_3_a7e3cd68c5e5f05139151a58f358df95._comment b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_3_a7e3cd68c5e5f05139151a58f358df95._comment new file mode 100644 index 0000000000..c4d8cf754e --- /dev/null +++ b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_3_a7e3cd68c5e5f05139151a58f358df95._comment @@ -0,0 +1,13 @@ +[[!comment format=mdwn + username="http://joeyh.name/" + ip="4.154.0.63" + subject="comment 3" + date="2013-08-22T18:44:15Z" + content=""" +Since the quvi urls are quite likely to break as the CDNs etc change things around, maybe it would be better to somehow have addurl tag an url as needing to be downloaded with quvi. Then `git annex get` could re-run quvi to get an url to download. + +We could expand url syntax for this. `quvi:http://youtube.com/foo` +This also allows for future expansion for other similar things. + +I'd be inclined to still make `addurl` automatically try quvi to see if an url is supported, rather than requiring the user fix up the url themselves. But if trying quvi turns out to be too expensive, manually specifying it in the url would also work. +"""]] diff --git a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_4_a57947ed257b28bbe995a68bfeb5eeaa._comment b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_4_a57947ed257b28bbe995a68bfeb5eeaa._comment new file mode 100644 index 0000000000..ee0ab45e71 --- /dev/null +++ b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_4_a57947ed257b28bbe995a68bfeb5eeaa._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://rmunn.myopenid.com/" + nickname="rmunn" + subject="comment 4" + date="2013-08-24T15:31:36Z" + content=""" +Either quvi or youtube-dl might be a good possibility: youtube-dl has the --get-url option (or -g for short) that outputs just the download URL (and nothing else) to stdout. So if for some reason quvi turned out not to be suitable, it wouldn't necessarily mean the idea would have to be abandoned. +"""]] diff --git a/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_5_a0612ae05dbda7f7935be648b42b30fc._comment b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_5_a0612ae05dbda7f7935be648b42b30fc._comment new file mode 100644 index 0000000000..38ac095118 --- /dev/null +++ b/doc/todo/wishlist:_special-case_handling_of_Youtube_URLs_in_Web_special_remote/comment_5_a0612ae05dbda7f7935be648b42b30fc._comment @@ -0,0 +1,8 @@ +[[!comment format=mdwn + username="https://id.koumbit.net/anarcat" + ip="72.0.72.144" + subject="aaaaawesome!" + date="2013-08-26T04:43:27Z" + content=""" +wow, thanks! i am happy my little suggestion led to an actual implentation, great! +"""]] diff --git a/git-annex.cabal b/git-annex.cabal index 8644372799..0183ca232f 100644 --- a/git-annex.cabal +++ b/git-annex.cabal @@ -1,5 +1,5 @@ Name: git-annex -Version: 4.20130815 +Version: 4.20130827 Cabal-Version: >= 1.8 License: GPL-3 Maintainer: Joey Hess @@ -76,7 +76,7 @@ Executable git-annex extensible-exceptions, dataenc, SHA, process, json, base (>= 4.5 && < 4.8), monad-control, MonadCatchIO-transformers, IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process, - SafeSemaphore, uuid, random, dlist, unix-compat + SafeSemaphore, uuid, random, dlist, unix-compat, aeson -- Need to list these because they're generated from .hsc files. Other-Modules: Utility.Touch Utility.Mounts Include-Dirs: Utility @@ -142,7 +142,7 @@ Executable git-annex Build-Depends: yesod, yesod-default, yesod-static, yesod-form, yesod-core, case-insensitive, http-types, transformers, wai, wai-logger, warp, - blaze-builder, crypto-api, hamlet, clientsession, aeson, + blaze-builder, crypto-api, hamlet, clientsession, template-haskell, data-default CPP-Options: -DWITH_WEBAPP diff --git a/standalone/android/term.patch b/standalone/android/term.patch index b83c30e982..5f7d403359 100644 --- a/standalone/android/term.patch +++ b/standalone/android/term.patch @@ -501,8 +501,8 @@ index 8a3a4ac..824025d 100644 + + /* Reading from the fifo blocks until a url is written + * to it. */ -+ BufferedReader buf = new BufferedReader(new FileReader(webAppFifo)); + while (true) { ++ BufferedReader buf = new BufferedReader(new FileReader(webAppFifo)); + String s = buf.readLine(); + try { + Intent intent = new Intent(Intent.ACTION_VIEW, Uri.parse(s)); diff --git a/standalone/windows/build.sh b/standalone/windows/build.sh index 670b418d00..56aa58f317 100644 --- a/standalone/windows/build.sh +++ b/standalone/windows/build.sh @@ -26,15 +26,6 @@ rm -f git-annex-installer.exe # for haskell libraries to link them with the cygwin library. cabal update || true -MISSINGH_VERSION="1.2.0.1" - -rm -rf MissingH-${MISSINGH_VERSION} -cabal unpack MissingH -cd MissingH-${MISSINGH_VERSION} -withcyg patch -p1 <../standalone/windows/haskell-patches/ccc5967426a14eb7e8978277ed4fa937f8e0c514.patch -cabal install || true -cd .. - cabal install --only-dependencies -f"$FLAGS" # Detect when the last build was an incremental build and failed, diff --git a/standalone/windows/haskell-patches/ccc5967426a14eb7e8978277ed4fa937f8e0c514.patch b/standalone/windows/haskell-patches/ccc5967426a14eb7e8978277ed4fa937f8e0c514.patch deleted file mode 100644 index 02b6bd63d3..0000000000 --- a/standalone/windows/haskell-patches/ccc5967426a14eb7e8978277ed4fa937f8e0c514.patch +++ /dev/null @@ -1,75 +0,0 @@ -From 017b26c0198d6982e47600b66235d01990e49fef Mon Sep 17 00:00:00 2001 -From: mvoidex -Date: Fri, 18 Jan 2013 15:22:03 +0400 -Subject: [PATCH 1/2] Fixed error (getModificationTime returns UTCTime, not - ClockTime) - ---- - src/System/IO/WindowsCompat.hs | 7 ++++++- - 1 file changed, 6 insertions(+), 1 deletion(-) - -diff --git a/src/System/IO/WindowsCompat.hs b/src/System/IO/WindowsCompat.hs -index d910dca..38820bb 100644 ---- a/src/System/IO/WindowsCompat.hs -+++ b/src/System/IO/WindowsCompat.hs -@@ -56,6 +56,8 @@ import System.IO.StatCompat - import System.Posix.Consts - import System.Time.Utils - import System.Directory -+import Data.Time -+import Data.Time.Clock.POSIX - - -- these types aren't defined here - -@@ -112,6 +114,9 @@ otherModes = 0o00007 - accessModes :: FileMode - accessModes = ownerModes .|. groupModes .|. otherModes - -+utcTimeToSeconds :: Num a => UTCTime -> a -+utcTimeToSeconds = fromInteger . floor . utcTimeToPOSIXSeconds -+ - ----------- stat - type FileStatus = FileStatusCompat - getFileStatus :: FilePath -> IO FileStatus -@@ -120,7 +125,7 @@ getFileStatus fp = - isdir <- doesDirectoryExist fp - perms <- getPermissions fp - modct <- getModificationTime fp -- let epochtime = clockTimeToEpoch modct -+ let epochtime = utcTimeToSeconds modct - return $ FileStatusCompat {deviceID = -1, - fileID = -1, - fileMode = if isfile then regularFileMode --- -1.8.1.6 - - -From 6991e46b613fd929fd8e9bc49ae13c003a3b740c Mon Sep 17 00:00:00 2001 -From: Hamish Mackenzie -Date: Sun, 12 May 2013 18:08:16 +1200 -Subject: [PATCH 2/2] Fix for older versions of directory (where - getModificationTime still returns ClockTime) - ---- - src/System/IO/WindowsCompat.hs | 4 ++++ - 1 file changed, 4 insertions(+) - -diff --git a/src/System/IO/WindowsCompat.hs b/src/System/IO/WindowsCompat.hs -index 38820bb..8f7b476 100644 ---- a/src/System/IO/WindowsCompat.hs -+++ b/src/System/IO/WindowsCompat.hs -@@ -125,7 +125,11 @@ getFileStatus fp = - isdir <- doesDirectoryExist fp - perms <- getPermissions fp - modct <- getModificationTime fp -+#if MIN_VERSION_directory(1,2,0) - let epochtime = utcTimeToSeconds modct -+#else -+ let epochtime = clockTimeToEpoch modct -+#endif - return $ FileStatusCompat {deviceID = -1, - fileID = -1, - fileMode = if isfile then regularFileMode --- -1.8.1.6 -