Merge branch 'master' into bootstrap3

Conflicts:
	debian/changelog
This commit is contained in:
Joey Hess 2014-05-02 15:32:49 -03:00
commit 2aed2d8510
129 changed files with 2173 additions and 80 deletions

View file

@ -16,6 +16,8 @@ module Annex.Ssh (
sshCachingTo,
inRepoWithSshCachingTo,
runSshCaching,
sshAskPassEnv,
runSshAskPass
) where
import qualified Data.Map as M
@ -230,7 +232,7 @@ sshReadPort params = (port, reverse args)
{- When this env var is set, git-annex runs ssh with parameters
- to use the socket file that the env var contains.
-
- This is a workaround for GiT_SSH not being able to contain
- This is a workaround for GIT_SSH not being able to contain
- additional parameters to pass to ssh. -}
sshCachingEnv :: String
sshCachingEnv = "GIT_ANNEX_SSHCACHING"
@ -268,8 +270,17 @@ sshCachingTo remote g
where
uncached = return g
runSshCaching :: [String] -> String -> IO ()
runSshCaching :: [String] -> FilePath -> IO ()
runSshCaching args sockfile = do
let args' = toCommand (sshConnectionCachingParams sockfile) ++ args
let p = proc "ssh" args'
exitWith =<< waitForProcess . processHandle =<< createProcess p
{- When this env var is set, git-annex is being used as a ssh-askpass
- program, and should read the password from the specified location,
- and output it for ssh to read. -}
sshAskPassEnv :: String
sshAskPassEnv = "GIT_ANNEX_SSHASKPASS"
runSshAskPass :: FilePath -> IO ()
runSshAskPass passfile = putStrLn =<< readFile passfile

View file

@ -0,0 +1,53 @@
{- git-annex assistant CredPair cache.
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
module Assistant.CredPairCache (
cacheCred,
getCachedCred,
expireCachedCred,
) where
import Assistant.Types.CredPairCache
import Types.Creds
import Assistant.Common
import Utility.ThreadScheduler
import qualified Data.Map as M
import Control.Concurrent
{- Caches a CredPair, but only for a limited time, after which it
- will expire.
-
- Note that repeatedly caching the same CredPair
- does not reset its expiry time.
-}
cacheCred :: CredPair -> Seconds -> Assistant ()
cacheCred (login, password) expireafter = do
cache <- getAssistant credPairCache
liftIO $ do
changeStrict cache $ M.insert login password
void $ forkIO $ do
threadDelaySeconds expireafter
changeStrict cache $ M.delete login
getCachedCred :: Login -> Assistant (Maybe Password)
getCachedCred login = do
cache <- getAssistant credPairCache
liftIO $ M.lookup login <$> readMVar cache
expireCachedCred :: Login -> Assistant ()
expireCachedCred login = do
cache <- getAssistant credPairCache
liftIO $ changeStrict cache $ M.delete login
{- Update map strictly to avoid keeping references to old creds in memory. -}
changeStrict :: CredPairCache -> (M.Map Login Password -> M.Map Login Password) -> IO ()
changeStrict cache a = modifyMVar_ cache $ \m -> do
let !m' = a m
return m'

View file

@ -44,6 +44,7 @@ import Assistant.Types.Buddies
import Assistant.Types.NetMessager
import Assistant.Types.ThreadName
import Assistant.Types.RemoteControl
import Assistant.Types.CredPairCache
newtype Assistant a = Assistant { mkAssistant :: ReaderT AssistantData IO a }
deriving (
@ -70,6 +71,7 @@ data AssistantData = AssistantData
, buddyList :: BuddyList
, netMessager :: NetMessager
, remoteControl :: RemoteControl
, credPairCache :: CredPairCache
}
newAssistantData :: ThreadState -> DaemonStatusHandle -> IO AssistantData
@ -89,6 +91,7 @@ newAssistantData st dstatus = AssistantData
<*> newBuddyList
<*> newNetMessager
<*> newRemoteControl
<*> newCredPairCache
runAssistant :: AssistantData -> Assistant a -> IO a
runAssistant d a = runReaderT (mkAssistant a) d

View file

@ -63,7 +63,11 @@ dbusThread urlrenderer = do
wasmounted <- liftIO $ swapMVar mvar nowmounted
handleMounts urlrenderer wasmounted nowmounted
liftIO $ forM_ mountChanged $ \matcher ->
#if MIN_VERSION_dbus(0,10,7)
void $ addMatch client matcher handleevent
#else
listen client matcher handleevent
#endif
, do
liftAnnex $
warning "No known volume monitor available through dbus; falling back to mtab polling"

View file

@ -112,8 +112,13 @@ checkNetMonitor client = do
-}
listenNMConnections :: Client -> (Bool -> IO ()) -> IO ()
listenNMConnections client setconnected =
listen client matcher $ \event -> mapM_ handle
(map dictionaryItems $ mapMaybe fromVariant $ signalBody event)
#if MIN_VERSION_dbus(0,10,7)
void $ addMatch client matcher
#else
listen client matcher
#endif
$ \event -> mapM_ handle
(map dictionaryItems $ mapMaybe fromVariant $ signalBody event)
where
matcher = matchAny
{ matchInterface = Just "org.freedesktop.NetworkManager"
@ -142,10 +147,10 @@ listenNMConnections client setconnected =
-}
listenWicdConnections :: Client -> (Bool -> IO ()) -> IO ()
listenWicdConnections client setconnected = do
listen client connmatcher $ \event ->
match connmatcher $ \event ->
when (any (== wicd_success) (signalBody event)) $
setconnected True
listen client statusmatcher $ \event -> handle (signalBody event)
match statusmatcher $ \event -> handle (signalBody event)
where
connmatcher = matchAny
{ matchInterface = Just "org.wicd.daemon"
@ -160,7 +165,12 @@ listenWicdConnections client setconnected = do
handle status
| any (== wicd_disconnected) status = setconnected False
| otherwise = noop
match matcher a =
#if MIN_VERSION_dbus(0,10,7)
void $ addMatch client matcher a
#else
listen client matcher a
#endif
#endif
handleConnection :: Assistant ()

View file

@ -46,6 +46,7 @@ import Assistant.WebApp.Types
#ifndef mingw32_HOST_OS
import Utility.LogFile
#endif
import Types.Key (keyBackendName)
import Data.Time.Clock.POSIX
import qualified Data.Text as T
@ -82,6 +83,10 @@ sanityCheckerStartupThread startupdelay = namedThreadUnchecked "SanityCheckerSta
{- Fix up ssh remotes set up by past versions of the assistant. -}
liftIO $ fixUpSshRemotes
{- Clean up old temp files. -}
liftAnnex cleanOldTmpMisc
liftAnnex cleanReallyOldTmp
{- If there's a startup delay, it's done here. -}
liftIO $ maybe noop (threadDelaySeconds . Seconds . fromIntegral . durationSeconds) startupdelay
@ -258,3 +263,54 @@ checkOldUnused urlrenderer = go =<< annexExpireUnused <$> liftAnnex Annex.getGit
#else
debug [show $ renderTense Past msg]
#endif
{- Files may be left in misctmp by eg, an interrupted add of files
- by the assistant, which hard links files to there as part of lockdown
- checks. Delete these files if they're more than a day old.
-
- Note that this is not safe to run after the Watcher starts up, since it
- will create such files, and due to hard linking they may have old
- mtimes. So, this should only be called from the
- sanityCheckerStartupThread, which runs before the Watcher starts up.
-
- Also, if a git-annex add is being run at the same time the assistant
- starts up, its tmp files could be deleted. However, the watcher will
- come along and add everything once it starts up anyway, so at worst
- this would make the git-annex add fail unexpectedly.
-}
cleanOldTmpMisc :: Annex ()
cleanOldTmpMisc = do
now <- liftIO getPOSIXTime
let oldenough = now - (60 * 60 * 24)
tmp <- fromRepo gitAnnexTmpMiscDir
liftIO $ mapM_ (cleanOld (<= oldenough)) =<< dirContentsRecursive tmp
{- While .git/annex/tmp is now only used for storing partially transferred
- objects, older versions of git-annex used it for misctemp. Clean up any
- files that might be left from that, by looking for files whose names
- cannot be the key of an annexed object. Only delete files older than
- 1 week old.
-
- Also, some remotes such as rsync may use this temp directory for storing
- eg, encrypted objects that are being transferred. So, delete old
- objects that use a GPGHMAC backend.
-}
cleanReallyOldTmp :: Annex ()
cleanReallyOldTmp = do
now <- liftIO getPOSIXTime
let oldenough = now - (60 * 60 * 24 * 7)
tmp <- fromRepo gitAnnexTmpObjectDir
liftIO $ mapM_ (cleanjunk (<= oldenough)) =<< dirContentsRecursive tmp
where
cleanjunk check f = case fileKey (takeFileName f) of
Nothing -> cleanOld check f
Just k
| "GPGHMAC" `isPrefixOf` keyBackendName k ->
cleanOld check f
| otherwise -> noop
cleanOld :: (POSIXTime -> Bool) -> FilePath -> IO ()
cleanOld check f = do
mtime <- realToFrac . modificationTime <$> getFileStatus f
when (check mtime) $
nukeFile f

View file

@ -18,11 +18,8 @@ import Assistant.Types.UrlRenderer
import Assistant.DaemonStatus
import Assistant.Alert
import Utility.NotificationBroadcaster
import Utility.Tmp
import qualified Annex
import qualified Build.SysConfig
import qualified Utility.Url as Url
import qualified Annex.Url as Url
import qualified Git.Version
import Types.Distribution
#ifdef WITH_WEBAPP
@ -62,7 +59,7 @@ upgraderThread urlrenderer = namedThread "Upgrader" $
checkUpgrade :: UrlRenderer -> Assistant ()
checkUpgrade urlrenderer = do
debug [ "Checking if an upgrade is available." ]
go =<< getDistributionInfo
go =<< downloadDistributionInfo
where
go Nothing = debug [ "Failed to check if upgrade is available." ]
go (Just d) = do
@ -86,16 +83,3 @@ canUpgrade urgency urlrenderer d = ifM autoUpgradeEnabled
noop
#endif
)
getDistributionInfo :: Assistant (Maybe GitAnnexDistribution)
getDistributionInfo = do
uo <- liftAnnex Url.getUrlOptions
liftIO $ withTmpFile "git-annex.tmp" $ \tmpfile h -> do
hClose h
ifM (Url.downloadQuiet distributionInfoUrl tmpfile uo)
( readish <$> readFileStrict tmpfile
, return Nothing
)
distributionInfoUrl :: String
distributionInfoUrl = fromJust Build.SysConfig.upgradelocation ++ ".info"

View file

@ -0,0 +1,18 @@
{- git-annex assistant CredPair cache.
-
- Copyright 2014 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Assistant.Types.CredPairCache where
import Types.Creds
import Control.Concurrent
import qualified Data.Map as M
type CredPairCache = MVar (M.Map Login Password)
newCredPairCache :: IO CredPairCache
newCredPairCache = newMVar M.empty

View file

@ -32,7 +32,11 @@ import Config.Files
import Utility.ThreadScheduler
import Utility.Tmp
import Utility.UserInfo
import Utility.Gpg
import qualified Utility.Lsof as Lsof
import qualified Build.SysConfig
import qualified Utility.Url as Url
import qualified Annex.Url as Url
import qualified Data.Map as M
import Data.Tuple.Utils
@ -313,3 +317,48 @@ upgradeSanityCheck = ifM usingDistribution
usingDistribution :: IO Bool
usingDistribution = isJust <$> getEnv "GIT_ANNEX_STANDLONE_ENV"
downloadDistributionInfo :: Assistant (Maybe GitAnnexDistribution)
downloadDistributionInfo = do
uo <- liftAnnex Url.getUrlOptions
liftIO $ withTmpDir "git-annex.tmp" $ \tmpdir -> do
let infof = tmpdir </> "info"
let sigf = infof ++ ".sig"
ifM (Url.downloadQuiet distributionInfoUrl infof uo
<&&> Url.downloadQuiet distributionInfoSigUrl sigf uo
<&&> verifyDistributionSig sigf)
( readish <$> readFileStrict infof
, return Nothing
)
distributionInfoUrl :: String
distributionInfoUrl = fromJust Build.SysConfig.upgradelocation ++ ".info"
distributionInfoSigUrl :: String
distributionInfoSigUrl = distributionInfoUrl ++ ".sig"
{- Verifies that a file from the git-annex distribution has a valid
- signature. Pass the detached .sig file; the file to be verified should
- be located next to it.
-
- The gpg keyring used to verify the signature is located in
- trustedkeys.gpg, next to the git-annex program.
-}
verifyDistributionSig :: FilePath -> IO Bool
verifyDistributionSig sig = do
p <- readProgramFile
if isAbsolute p
then withTmpDir "git-annex-gpg.tmp" $ \gpgtmp -> do
let trustedkeys = takeDirectory p </> "trustedkeys.gpg"
boolSystem gpgcmd
[ Param "--no-default-keyring"
, Param "--no-auto-check-trustdb"
, Param "--no-options"
, Param "--homedir"
, File gpgtmp
, Param "--keyring"
, File trustedkeys
, Param "--verify"
, File sig
]
else return False

View file

@ -7,7 +7,6 @@ import Control.Applicative
import System.Environment (getArgs)
import Control.Monad.IfElse
import Control.Monad
import System.IO
import Build.TestConfig
import Build.Version
@ -63,11 +62,7 @@ shaTestCases l = map make l
key = "sha" ++ show n
search [] = return Nothing
search (c:cmds) = do
putStr $ "(" ++ c
hFlush stdout
sha <- externalSHA c n "/dev/null"
putStr $ ":" ++ show sha ++ ")"
hFlush stdout
if sha == Right knowngood
then return $ Just c
else search cmds

View file

@ -199,5 +199,11 @@ run args = do
#ifdef WITH_EKG
_ <- forkServer "localhost" 4242
#endif
maybe (dispatch True args cmds gitAnnexOptions [] header Git.CurrentRepo.get)
(runSshCaching args) =<< getEnv sshCachingEnv
go envmodes
where
go [] = dispatch True args cmds gitAnnexOptions [] header Git.CurrentRepo.get
go ((v, a):rest) = maybe (go rest) a =<< getEnv v
envmodes =
[ (sshCachingEnv, runSshCaching args)
, (sshAskPassEnv, runSshAskPass)
]

View file

@ -120,6 +120,7 @@ linuxstandalone-nobuild: Build/Standalone Build/LinuxMkLibs
ln -sf git-annex "$(LINUXSTANDALONE_DEST)/bin/git-annex-shell"
zcat standalone/licences.gz > $(LINUXSTANDALONE_DEST)/LICENSE
cp doc/logo_16x16.png doc/logo.svg $(LINUXSTANDALONE_DEST)
cp standalone/trustedkeys.gpg $(LINUXSTANDALONE_DEST)
./Build/Standalone "$(LINUXSTANDALONE_DEST)"
@ -150,6 +151,7 @@ osxapp: Build/Standalone Build/OSXMkLibs
ln -sf git-annex "$(OSXAPP_BASE)/git-annex-shell"
gzcat standalone/licences.gz > $(OSXAPP_BASE)/LICENSE
cp $(OSXAPP_BASE)/LICENSE tmp/build-dmg/LICENSE.txt
cp standalone/trustedkeys.gpg $(OSXAPP_BASE)
./Build/Standalone $(OSXAPP_BASE)

View file

@ -87,9 +87,8 @@ uuidDescriptions = M.unionWith addName <$> uuidMap <*> remoteMap name
addName :: String -> RemoteName -> String
addName desc n
| desc == n = desc
| null desc = n
| otherwise = n ++ " (" ++ desc ++ ")"
| desc == n || null desc = "[" ++ n ++ "]"
| otherwise = desc ++ " [" ++ n ++ "]"
{- When a name is specified, looks up the remote matching that name.
- (Or it can be a UUID.) -}

View file

@ -9,4 +9,6 @@ module Types.Creds where
type Creds = String -- can be any data that contains credentials
type CredPair = (String, String) -- login, password
type CredPair = (Login, Password)
type Login = String
type Password = String -- todo: use securemem

View file

@ -62,7 +62,7 @@ query ch send receive = do
s <- readMVar ch
restartable s (send $ coProcessTo s) $ const $
restartable s (hFlush $ coProcessTo s) $ const $
restartable s (receive $ coProcessFrom s) $
restartable s (receive $ coProcessFrom s)
return
where
restartable s a cont

View file

@ -9,6 +9,7 @@
module Utility.DBus where
import Utility.PartialPrelude
import Utility.Exception
import DBus.Client
@ -22,7 +23,7 @@ type ServiceName = String
listServiceNames :: Client -> IO [ServiceName]
listServiceNames client = do
reply <- callDBus client "ListNames" []
return $ fromMaybe [] $ fromVariant (methodReturnBody reply !! 0)
return $ fromMaybe [] $ fromVariant =<< headMaybe (methodReturnBody reply)
callDBus :: Client -> MemberName -> [Variant] -> IO MethodReturn
callDBus client name params = call_ client $

View file

@ -36,7 +36,7 @@ daemonize logfd pidfile changedirectory a = do
_ <- forkProcess child1
out
where
checkalreadyrunning f = maybe noop (const $ alreadyRunning)
checkalreadyrunning f = maybe noop (const alreadyRunning)
=<< checkDaemon f
child1 = do
_ <- createSession

View file

@ -111,7 +111,7 @@ roughSize units short i
| i < 0 = '-' : findUnit units' (negate i)
| otherwise = findUnit units' i
where
units' = reverse $ sort units -- largest first
units' = sortBy (flip compare) units -- largest first
findUnit (u@(Unit s _ _):us) i'
| i' >= s = showUnit i' u

View file

@ -43,7 +43,7 @@ dirContents d = map (d </>) . filter (not . dirCruft) <$> getDirectoryContents d
- When the directory does not exist, no exception is thrown,
- instead, [] is returned. -}
dirContentsRecursive :: FilePath -> IO [FilePath]
dirContentsRecursive topdir = dirContentsRecursiveSkipping (const False) True topdir
dirContentsRecursive = dirContentsRecursiveSkipping (const False) True
{- Skips directories whose basenames match the skipdir. -}
dirContentsRecursiveSkipping :: (FilePath -> Bool) -> Bool -> FilePath -> IO [FilePath]

View file

@ -18,7 +18,7 @@ import Utility.Data
{- Catches IO errors and returns a Bool -}
catchBoolIO :: IO Bool -> IO Bool
catchBoolIO a = catchDefaultIO False a
catchBoolIO = catchDefaultIO False
{- Catches IO errors and returns a Maybe -}
catchMaybeIO :: IO a -> IO (Maybe a)

View file

@ -145,7 +145,7 @@ findPubKeys :: String -> IO KeyIds
findPubKeys for = KeyIds . parse . lines <$> readStrict params
where
params = [Params "--with-colons --list-public-keys", Param for]
parse = catMaybes . map (keyIdField . split ":")
parse = mapMaybe (keyIdField . split ":")
keyIdField ("pub":_:_:_:f:_) = Just f
keyIdField _ = Nothing
@ -195,7 +195,7 @@ genSecretKey keytype passphrase userid keysize =
Algo n -> show n
, Just $ "Key-Length: " ++ show keysize
, Just $ "Name-Real: " ++ userid
, Just $ "Expire-Date: 0"
, Just "Expire-Date: 0"
, if null passphrase
then Nothing
else Just $ "Passphrase: " ++ passphrase

View file

@ -17,5 +17,5 @@ showImprecise precision n
int :: Integer
(int, frac) = properFraction n
remainder = round (frac * 10 ^ precision) :: Integer
pad0s s = (take (precision - length s) (repeat '0')) ++ s
pad0s s = replicate (precision - length s) '0' ++ s
striptrailing0s = reverse . dropWhile (== '0') . reverse

View file

@ -59,7 +59,7 @@ parseDuration = Duration <$$> go 0
fromDuration :: Duration -> String
fromDuration Duration { durationSeconds = d }
| d == 0 = "0s"
| otherwise = concat $ map showunit $ go [] units d
| otherwise = concatMap showunit $ go [] units d
where
showunit (u, n)
| n > 0 = show n ++ [u]

View file

@ -49,7 +49,7 @@ inTop top f = top ++ f
- link to. Note that some of the libraries may not exist
- (eg, linux-vdso.so) -}
parseLdd :: String -> [FilePath]
parseLdd = catMaybes . map (getlib . dropWhile isSpace) . lines
parseLdd = mapMaybe (getlib . dropWhile isSpace) . lines
where
getlib l = headMaybe . words =<< lastMaybe (split " => " l)

View file

@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns, CPP #-}
{-# LANGUAGE CPP #-}
module Utility.Lsof where
@ -110,7 +110,7 @@ parseFormatted s = bundle $ go [] $ lines s
{- Parses lsof's default output format. -}
parseDefault :: LsofParser
parseDefault = catMaybes . map parseline . drop 1 . lines
parseDefault = mapMaybe parseline . drop 1 . lines
where
parseline l = case words l of
(command : spid : _user : _fd : _type : _device : _size : _node : rest) ->

View file

@ -64,10 +64,10 @@ generate = simplify . process MAny . tokenGroups
process m [] = m
process m ts = uncurry process $ consume m ts
consume m ((One And):rest) = term (m `MAnd`) rest
consume m ((One Or):rest) = term (m `MOr`) rest
consume m ((One Not):rest) = term (\p -> m `MAnd` (MNot p)) rest
consume m ((One (Operation o)):rest) = (m `MAnd` MOp o, rest)
consume m (One And:rest) = term (m `MAnd`) rest
consume m (One Or:rest) = term (m `MOr`) rest
consume m (One Not:rest) = term (\p -> m `MAnd` (MNot p)) rest
consume m (One (Operation o):rest) = (m `MAnd` MOp o, rest)
consume m (Group g:rest) = (process m g, rest)
consume m (_:rest) = consume m rest
consume m [] = (m, [])

4
debian/changelog vendored
View file

@ -2,6 +2,10 @@ git-annex (5.20140422) UNRELEASED; urgency=medium
* webapp: Switched to bootstrap 3.
Thanks, Sören Brunk.
* Standalone builds now check gpg signatures before upgrading.
* Simplified repository description line format. The remote name,
if any, is always in square brackets after the description.
* assistant: Clean up stale tmp files on startup.
-- Joey Hess <joeyh@debian.org> Fri, 02 May 2014 15:28:53 -0300

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnov5q9_Cl4Ps5NoYE08yE01NLSvBANnY8"
nickname="Eric"
subject="Does it not work in Direct Mode?"
date="2014-04-26T09:41:20Z"
content="""
Looks great, but I got the impression that Assistant would mirror the files from my computer to my external hard drive, and I can't seem to get it to do that.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawlr2Bj0Mzqwzl28cbrotcQUbOFoaPB3B_Y"
nickname="Tomasz"
subject="how to disable assistant"
date="2014-04-28T10:21:59Z"
content="""
assistant daemon now starts at boot and pushes all annexed files to other repos... I'd like to do it on my own. I can stop daemon from webapp, but it starts again on boot - how Do I disable it from autostarting ?
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="http://johan.kiviniemi.name/"
nickname="Johan"
subject="comment 10"
date="2014-05-01T01:33:10Z"
content="""
Note to self: I experienced this bug with the standalone tarball release (5.20140421) as well, so its not caused by something that is different on my system wrt. git-annexs dependencies etc.
"""]]

View file

@ -0,0 +1,18 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawmz9DnN5ESPLLRN0Q5a6fpELMFTYSkWTFs"
nickname="Steve"
subject="Stock RHEL git-annex is old & buggy"
date="2014-04-23T17:35:29Z"
content="""
The stock git-annex bundled with Red Hat Enterprise Linux server (release 6.5) contains the old, buggy version that throws the \"No such file or directory\" error described above. The RHEL 6.5 version is:
$ git annex version
git-annex version: 3.20120523
local repository version: 3
default repository version: 3
supported repository versions: 3
upgrade supported from repository versions: 0 1 2
Installing a more recent version (such as 5.20140411-gda795e0) solves the problem.
"""]]

View file

@ -0,0 +1,19 @@
### Please describe the problem.
In lieu of a better place to ask/report this. Is it possible to have an email sent when bugs are moved into another category? I get emails on comments but not much when the bugs are moved elsewhere - they just seem to disappear.
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,23 @@
### Please describe the problem.
The git-annex annex repo at <https://downloads.kitenet.net/.git/> is not available. This is the address mentioned at <http://git-annex.branchable.com/publicrepos/>.
### What steps will reproduce the problem?
$ git clone https://downloads.kitenet.net/.git/
Cloning into 'downloads.kitenet.net'...
fatal: repository 'https://downloads.kitenet.net/.git/' not found
### Please provide any additional information below.
Have tried various combinations of the URL, but nothing works. It was like this a week ago too, but I didn't report it because I thought it was a temporary error due to some server reconfiguration or something.
[[!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.
"""]]
> [[fixed|done]] --[[Joey]]

View file

@ -0,0 +1,26 @@
### Please describe the problem.
Hi,
On OSX the web-app keeps notifying me of an upgrade, I choose to run it but nothing seems to happen.
The debug logs show that the upgrade is skipped as it's redundant.
### What steps will reproduce the problem?
Have upgrades set to notify.
### What version of git-annex are you using? On what operating system?
Current.
### 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
[2014-04-25 08:26:30 BST] Upgrader: An upgrade of git-annex is available. (version 5.20140421)
[2014-04-25 08:27:02 BST] main: Skipping redundant upgrade
# End of transcript or log.
"""]]

View file

@ -0,0 +1,9 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 1"
date="2014-04-25T07:36:09Z"
content="""
The upgrade notifications seem to appear when switching between repositories in the web-app - are repositories treated separately? Or perhaps notifications sent per repo?
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://id.koumbit.net/anarcat"
ip="72.0.72.144"
subject="comment 2"
date="2014-04-25T13:25:43Z"
content="""
i think this problem was quickly mentionned in [[devblog/day_157__upgrade_checking]], can you provide a full debug log?
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 3"
date="2014-04-26T20:26:35Z"
content="""
I'm pretty sure that was the sum total of the log (even with debug on). Only the brevity of it makes me doubt myself.
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 4"
date="2014-04-27T00:02:41Z"
content="""
What version of git-annex do you have running?
I suspect that if you look around, you will find you have a git-annex-5.20140421 directory in either your home directory or next to where you installed the DMG.
"""]]

View file

@ -0,0 +1,14 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 5"
date="2014-04-27T11:10:49Z"
content="""
Hi,
Yes there is a git-annex.app.5.20140421 directory in $HOME. And it looks as though I'm running git-annex.app.5.20140420 - even though I manually tried to upgrade by downloading
https://downloads.kitenet.net/git-annex/OSX/current/10.9_Mavericks/git-annex.dmg
Running `$HOME/git-annex.app.5.20140421/.../git-annex` gives me `5.20140420-ga25b8bb`. So the downloaded version even though labeled 5.20140421 contains 5.20140420.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 6"
date="2014-04-27T11:14:40Z"
content="""
And I still think there is a slight bug in there somewhere. If due to packaging errors an upgrade doesn't apply and the logs are smart enough to notice it's redundant then there shouldn't be continued notifications of an available upgrade...
"""]]

View file

@ -0,0 +1,59 @@
[[!comment format=mdwn
username="ayutheos"
ip="49.124.129.253"
subject="comment 6"
date="2014-04-23T08:56:58Z"
content="""
I upgraded git to 1.9.0.msysgit.0, and managed to initialise git-annex:
user@NOTEBOOK /d/pictures
$ git init
Initialized empty Git repository in D:/pictures/.git/
user@NOTEBOOK /d/pictures
$ git annex init \"laptop photos\"
init laptop photos
Detected a filesystem without fifo support.
Disabling ssh connection caching.
Detected a crippled filesystem.
Enabling direct mode.
ok
(Recording state in git...)
But there's a message that it detected a crippled filesystem? What does that mean?
Running `git status` gives:
user@NOTEBOOK /d/pictures
$ git st
fatal: This operation must be run in a work tree
And then I run `git init`
user@NOTEBOOK /d/pictures
$ git init
Reinitialized existing Git repository in D:/pictures/.git/
user@NOTEBOOK /d/pictures
$ git st
On branch annex/direct/master
Initial commit
Untracked files:
(use \"git add <file>...\" to include in what will be committed)
2011/
2012/
2013/
2014/
dump/
to burn/
nothing added to commit but untracked files present (use \"git add\" to track)
..and git works ok. Any suggestions what might be wrong?
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="108.236.230.124"
subject="comment 7"
date="2014-04-23T17:47:59Z"
content="""
Ok, I am tempted to close this bug if it only happens with an older version of msysgit. It really is looking like a bug in git, or in the msysgit port.
The \"crippled filesystem\" is normal on Windows. git-annex does not try to use symblic links on Windows, and so is limited to working in [[direct_mode]].
"""]]

View file

@ -0,0 +1,38 @@
### Please describe the problem.
### What steps will reproduce the problem?
$ git init
Initialized empty Git repository in /cygdrive/c/Temp/.git/
$ git-annex init
init
Detected a filesystem without fifo support.
Disabling ssh connection caching.
Detected a crippled filesystem.
Disabling core.symlinks.
Enabling direct mode.
fatal: You are on a branch yet to be born
git-annex.exe: git [Param "checkout",Param "-q",Param "-B",Param "annex/direct/master"] failed
$ git checkout -B annex/direct/master
fatal: You are on a branch yet to be born
### What version of git-annex are you using? On what operating system?
Running under cygwin bash
$ git --version
git version 1.7.9
$ git-annex version
git-annex version: 5.20140421-g78d6aa1
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV DNS Feeds Quvi TDFA CryptoHash
key/value backends: SHA256E SHA1E SHA512E SHA224E SHA384E SKEIN256E SKEIN512E SHA256 SHA1 SHA512 SHA224 SHA384 SKEIN256 SKEIN512 WORM URL
remote types: git gcrypt S3 bup directory rsync web webdav tahoe glacier hook external

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-27T00:13:49Z"
content="""
This looks similar to [[bugs/git-annex_fails_to_initialize_under_Windows]], which was solved by upgrading to a newer version of msysgit.
git 1.7.9 is extremely old (years). Probably the empty commit that is done when switching to direct mode, precisely to avoid this problem, fails, because the pre-built git-annex for windows is targeting a modern version of git, from msysgit.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawkYmMFDdf3GJ9Oba6NCVkzGc4JyB9WavMs"
nickname="Xinruo"
subject="comment 2"
date="2014-04-27T11:58:13Z"
content="""
OK installing git 1.9.2 from msysgit solves the problem. I thought I have read somewhere that you used cygwin for Windows development and didn't know that git from cygwin is too old. Thanks for the help!
"""]]

View file

@ -0,0 +1,23 @@
### Please describe the problem.
Running `git annex group here manual` and `git annex group here client` results in the nonsensical group of "manual client". Should there be checking for the reserved "standard" group words?
The intention from the webapp and docs reads as though these groups should be mutually exclusive.
Also it would be nice if `git annex group here` returned the list of groups (I put this as a wishlist item but think it perhaps warrants a bug mention).
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,27 @@
### Please describe the problem.
git-annex is back on the radar now that the jabber requirement has been dropped! :-)
But, it seems as though when I create a remote repo via the webapp it always makes it a bare git repo. Even when I specify the "client usage grouping".
If I manually create two repos on ssh enabled servers, manually link them, and fire up the assistant they are awesomely kept in sync (with no bare repo in sight).
### What steps will reproduce the problem?
Use the webapp to try to create a client usage remote repo.
### What version of git-annex are you using? On what operating system?
Latest as of post.
### 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.
"""]]
> [[notabug|done]] --[[Joey]]

View file

@ -0,0 +1,12 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-24T18:00:52Z"
content="""
Please use descriptive bug titles.
The webapp configures some common use cases, not every possible use case. Running git-annex assistant on a remote server to keep a directory there updated is not a relatively common use case. You can do it if you want; and if someone provided a very complelling UI markup that made sense to regular users it might be added to the webap (but this seems unlikely.
As it is, the webapp set up bare git repositories on remotes, because that is by far the most common useful way to use git on a remote server. And if the webapp's local pairing interface is used, two existing non-bare client repositories will be paired, and the new remotedaemon will help keep the in sync.
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 2"
date="2014-04-24T18:43:50Z"
content="""
hmmm - I think that it's arguable that if in the repository group drop down I select \"client\" then the remote repo should *not* be bare.
I would predict that this new functionality will supercede the existing use-cases in terms of popularity. It's very cool that all my machines can be kept in sync with just ssh - a walkthrough showing desktop, laptop, and phone all just syncing (i.e., without the cloud transfer repo and jabber complications) makes a much simpler and compelling advert for this cool code! But it won't happen unless the GUI supports it...
"""]]

View file

@ -0,0 +1,136 @@
### Please describe the problem.
Hi,
I have a number of repos that I created both by hand and via the web-app. Some manual, some client and one backup groupings.
When creating by hand I manually set the annex-cost to 100 (but I notice the webapp sets local costs to 175 - not 100 as per the man page).
(I'm assuming the creation by hand is still just to `git add remote` on both sides).
When I run `git-annex sync --content` I do seem to get the local remote (the cheapest cost) that I want.
When I use the assistant I get every odd behaviour. It will quite happily choose from any of the available repos with no descernible pattern.
Even more strangely sometimes it queues all the transfers to use the local connection but then at the actual transfer it switches to use the public connection (I have two remotes for one repo: when on the local network and when on the internet). This is reflected in the webapps UI.
For the snippet of logs below I see the files queued as the remote "Dancingfrog" (on the internnal network) then for the transfer the web page switches to "Home" (the public network). I think the data is actually transferred over the public network as it's much slower than compared to explicit repo transfers from the cli.
<pre>
[2014-04-27 05:11:47 BST] TransferWatcher: transfer starting: Download UUID "c3cec307-367b-4373-8cb9-a3da67cee745" Dizzee Rascal/Tounge N' Cheek/03 Dance Wiv Me [Ft. Calvin Harris & Chrome].mp3 Nothing
[2014-04-27 05:11:47 BST] TransferWatcher: transfer starting: Download UUID "c3cec307-367b-4373-8cb9-a3da67cee745" Dizzee Rascal/Tounge N' Cheek/03 Dance Wiv Me [Ft. Calvin Harris & Chrome].mp3 Nothing
SHA256E-s6759929--a822e83c3448716e793fb9d1d1b1523c2492c84ba07f5c093899810fbdfe5621.mp3
0 0% 0.00kB/s 0:00:00
163,840 2% 159.20kB/s 0:00:41
360,448 5% 159.56kB/s 0:00:40
524,288 7% 155.01kB/s 0:00:40
688,128 10% 154.59kB/s 0:00:39
851,968 12% 153.18kB/s 0:00:38 [2014-04-27 05:11:54 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","ls-tree","--full-tree","-z","--","refs/heads/git-annex","uuid.log","remote.log","trust.log","group.log","numcopies.log","schedule.log","preferred-content.log","required-content.log","group-preferred-content.log"]
1,015,808 15% 149.92kB/s 0:00:38 To gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mus
617edaf..f016a03 git-annex -> synced/git-annex
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","git-annex"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","isilon","master"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..f016a03fc92aebba14b239cc3647478b1fb9f78f","--oneline","-n1"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..7339a1fdd007d7a528b7e2eb82c2aeedca511920","--oneline","-n1"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..00f5e110ca77b9b5103e1b568ea6aa9d9d9dbb81","--oneline","-n1"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..ab90c337053a61111060540d2f60ce20b44cc2d9","--oneline","-n1"]
[2014-04-27 05:11:56 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..88d99a7ef2d37d1a6180e5dd66a4559927a58eaf","--oneline","-n1"]
1,146,880 16% 98.64kB/s 0:00:56
1,507,328 22% 129.55kB/s 0:00:40
1,671,168 24% 126.84kB/s 0:00:40 [2014-04-27 05:12:00 BST] Pusher: Syncing with dancingfrog, rss, isilon
[2014-04-27 05:12:00 BST] chat: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","hash-object","-w","--stdin-paths","--no-filters"]
[2014-04-27 05:12:00 BST] feed: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","update-index","-z","--index-info"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
(Recording state in git...)
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","write-tree"]
[2014-04-27 05:12:00 BST] chat: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","commit-tree","86e5513adfc0d1f64cabd3ca3902738d45d809ad","-p","refs/heads/git-annex"]
[2014-04-27 05:12:00 BST] call: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","update-ref","refs/heads/git-annex","8808dc8effc3572ae1421461ff44574e900917bf"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","symbolic-ref","HEAD"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","refs/heads/master"]
[2014-04-27 05:12:00 BST] Pusher: pushing to [Remote { name ="dancingfrog" },Remote { name ="rss" },Remote { name ="isilon" }]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","git-annex"]
[2014-04-27 05:12:00 BST] call: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","branch","-f","synced/master"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
[2014-04-27 05:12:00 BST] call: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","dancingfrog","+git-annex:synced/git-annex","master:synced/master"]
[2014-04-27 05:12:00 BST] call: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","rss","+git-annex:synced/git-annex","master:synced/master"]
[2014-04-27 05:12:00 BST] call: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","isilon","+git-annex:synced/git-annex","master:synced/master"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..8808dc8effc3572ae1421461ff44574e900917bf","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..7339a1fdd007d7a528b7e2eb82c2aeedca511920","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..00f5e110gcrypt: Development version -- Repository format MAY CHANGE
ca77b9b5103e1b568ea6aa9d9d9dbb81","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..f016a03fc92aebba14b239cc3647478b1fb9f78f","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..ab90c337053a61111060540d2f60ce20b44cc2d9","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..88d99a7ef2d37d1a6180e5dd66a4559927a58eaf","--oneline","-n1"]
To ssh://10.23.33.19/Volumes/Media/iTunes Media/Music
f016a03..8808dc8 git-annex -> synced/git-annex
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","git-annex"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","dancingfrog","master"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..8808dc8effc3572ae1421461ff44574e900917bf","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..7339a1fdd007d7a528b7e2eb82c2aeedca511920","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..00f5e110ca77b9b5103e1b568ea6aa9d9d9dbb81","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..ab90c337053a61111060540d2f60ce20b44cc2d9","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..f016a03fc92aebba14b239cc3647478b1fb9f78f","--oneline","-n1"]
[2014-04-27 05:12:00 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..88d99a7ef2d37d1a6180e5dd66a4559927a58eaf","--oneline","-n1"]
1,835,008 27% 125.00kB/s 0:00:39 To rss:Music
f016a03..8808dc8 git-annex -> synced/git-annex
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","git-annex"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","rss","master"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..8808dc8effc3572ae1421461ff44574e900917bf","--oneline","-n1"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..7339a1fdd007d7a528b7e2eb82c2aeedca511920","--oneline","-n1"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..00f5e110ca77b9b5103e1b568ea6aa9d9d9dbb81","--oneline","-n1"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..ab90c337053a61111060540d2f60ce20b44cc2d9","--oneline","-n1"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..f016a03fc92aebba14b239cc3647478b1fb9f78f","--oneline","-n1"]
[2014-04-27 05:12:01 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..88d99a7ef2d37d1a6180e5dd66a4559927a58eaf","--oneline","-n1"]
gcrypt: Decrypting manifest
gpg: Signature made Sun 27 Apr 2014 05:11:41 BST using DSA key ID 29C42E01
gpg: Good signature from "Matt Ford (Work) <matt.ford@manchester.ac.uk>"
gpg: aka "Matt Ford <matt@dancingfrog.co.uk>"
gcrypt: Encrypting to: -R 68D8501429C42E01
gcrypt: Requesting manifest signature
gpg: 68D8501429C42E01: skipped: public key already present
1,998,848 29% 180.87kB/s 0:00:26
2,162,688 31% 135.56kB/s 0:00:33 To gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mus
f016a03..8808dc8 git-annex -> synced/git-annex
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","git-annex"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","show-ref","--hash","refs/heads/git-annex"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","push","isilon","master"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..8808dc8effc3572ae1421461ff44574e900917bf","--oneline","-n1"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..7339a1fdd007d7a528b7e2eb82c2aeedca511920","--oneline","-n1"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..00f5e110ca77b9b5103e1b568ea6aa9d9d9dbb81","--oneline","-n1"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..ab90c337053a61111060540d2f60ce20b44cc2d9","--oneline","-n1"]
[2014-04-27 05:12:03 BST] read: git ["--git-dir=/home/matt/Music/.git","--work-tree=/home/matt/Music","log","refs/heads/git-annex..88d99a7ef2d37d1a6180e5dd66a4559927a58eaf","--oneline","-n1"]
2,326,528 34% 139.74kB/s 0:00:31
3,637,248 53% 397.83kB/s 0:00:07
4,423,680 65% 556.91kB/s 0:00:04
5,079,040 75% 692.27kB/s 0:00:02
5,636,096 83% 781.05kB/s 0:00:01
× Synced with dancingfrog, rss, isilon
× Downloaded 11 Bad Be..viour.mp3 10 Holida..rome].mp3 09 Leisure.mp3 08 Money Money.mp3 07 Dirtee Cash.mp3 06 Chilli..n Dem.mp3 05 Can't .. More.mp3 04 Freaky..reaky.mp3 03 Dance ..rome].mp3 02 Road Rage.mp3 and 8 other files
× Synced with rss
× Performed startup scan
× Synced with dancingfrog, isilon
</pre>
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 1"
date="2014-04-27T04:25:58Z"
content="""
By the way these are indirect repos if that would make a difference.
"""]]

View file

@ -0,0 +1,55 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 2"
date="2014-04-27T11:48:18Z"
content="""
Here's the `.git/config`
<pre>
[core]
repositoryformatversion = 0
filemode = true
bare = false
logallrefupdates = true
[branch \"master\"]
remote = home
merge = refs/heads/master
[annex]
uuid = 105776ba-bd78-4884-9126-aeb7c1e6da21
version = 5
diskreserve = 100 megabytes
autoupgrade = ask
debug = true
fscknudge = true
[remote \"dancingfrog\"]
url = ssh://10.23.33.19/Volumes/Media/iTunes Media/Music
fetch = +refs/heads/*:refs/remotes/dancingfrog/*
annex-uuid = c3cec307-367b-4373-8cb9-a3da67cee745
annex-cost = 100
annex-sync = true
[remote \"home\"]
url = home:/Volumes/Media/iTunes Media/Music
fetch = +refs/heads/*:refs/remotes/home/*
annex-uuid = c3cec307-367b-4373-8cb9-a3da67cee745
annex-sync = true
annex-cost = 200
[remote \"isilon\"]
url = gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mus
fetch = +refs/heads/*:refs/remotes/isilon/*
gcrypt-participants = 68D8501429C42E01
gcrypt-signingkey = 68D8501429C42E01
gcrypt-id = :id:92R1j7+L9r5LuWDi2ZlW
annex-gcrypt = true
annex-uuid = 949a8fc3-6334-5f5e-887d-b1e5725ea443
annex-sync = true
annex-cost = 250
[remote \"rss\"]
url = rss:Music
fetch = +refs/heads/*:refs/remotes/rss/*
annex-uuid = 79ff3c20-fab3-44dd-88f7-cc1a41eb73d6
annex-sync = true
annex-cost = 200
</pre>
"""]]

View file

@ -0,0 +1,31 @@
### Please describe the problem.
Running `git-annex enableremote remote` without a suitable key available leaves a partially unconfigured git remote.
Subsequently making the key available and running `git-annex enableremote remote` a second time fails as the remote now partially exists.
Removing the remote with `git remote remove remote` and then re-running `git-annex enable remote` seems to do the trick.
However, I notice that even after syncing my special remotes are missing some details in the git config file - namely the `annex-gcrypt` and `annex-uuid` (there may have been more). I fixed by adding the details from a working repo.
Finally, when I initially created the gcrypt repo (by hand) I specified the remote as a local directory on the machine in question i.e. `gcrypt::/matt/mnt/isilon/rss/zzalsmf3/git-annex/mus` I then decided to make it available and changed it (via `git remote rename` to `gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mus`. Unfortunately on other machines when I `git enableremote` it recovers the original remote which obviously doesn't work - how can I update this setting?
Phew!
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,33 @@
### Please describe the problem.
The output of git-annex info can be confusing as the format rules change based on positioning
repository mode: indirect
trusted repositories: 0
semitrusted repositories: 5
00000000-0000-0000-0000-000000000001 -- web
105776ba-bd78-4884-9126-aeb7c1e6da21 -- UoM Laptop
79ff3c20-fab3-44dd-88f7-cc1a41eb73d6 -- here (UoM Desktop Client)
949a8fc3-6334-5f5e-887d-b1e5725ea443 -- isilon (UoM Isilon Encrypted Git Backup)
c3cec307-367b-4373-8cb9-a3da67cee745 -- home (Mac Mini Home Client)
Here we see the description surrounded in brackets and also not in brackets. The second annex listed does not have a name (as there is no git remote configured). Always including the brackets or an additional setting I think would make things much clearer esp. when setting things up.
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]
[[done]] --[[Joey]]

View file

@ -0,0 +1,23 @@
### Please describe the problem.
Not sure if it's a bug, but pls explain why it sync files and how to stop it by cfg.
Repos. created with Assistant - git annex sync i an indirect mode not only fetch metadata but also a files. What is the correct way to disable file sync (so only broken links are created in working tree)
Desired:
to boostrap annex infrastructure with assistant, but then some repos switch to indirect mode (while still synced by assistant/webapp) but only metadata (not files). Files to be fetched on request (like git annex get xyz/*) when needed.
### What steps will reproduce the problem?
1. with git annex webapp create two repos on two nodes (Alice and Bob).
2. pair them using discovery on local lan
3. on Bob stop assistant and fire "git annex indirect"
4. add files to Alice repo
5. run git annex sync on Bob repo from CLI
Bob's repo not only sync metadata but also retrive files.
The documentation says "sync" only sync metadata.
### What version of git-annex are you using? On what operating system?
git-annex version: 5.20140420-ga25b8bb

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawmBUR4O9mofxVbpb8JV9mEbVfIYv670uJo"
nickname="Justin"
subject="comment 1"
date="2014-04-30T20:54:05Z"
content="""
On this screen: http://git-annex.branchable.com/assistant/example.png click settings next to each repo
Set the type to manual: https://git-annex.branchable.com/assistant/repogroups.png
"""]]

View file

@ -0,0 +1,16 @@
### Please describe the problem.
This URL:
http://downloads.kitenet.net/git-annex/OSX/current/10.7.5_Lion/git-annex.dmg
currently points to a DMG with an .app that has ctime/mtime of Dec 29.
After launching the app, the About screen says this:
Version: 5.20131230-g684f2e6
> Nobody is autobuilding git-annex for old versions of OSX, which
> is why the download page says, "**warning: not being updated any longer**"
>
> So, not a bug, and nothing ca be done, unless someone steps up to run an
> autobuilder. You can of course build it from source yourself. [[done]]
> --[[Joey]]

View file

@ -0,0 +1,19 @@
### Please describe the problem.
I have to run the webapp to do upgrades...it would be nice to have a CLI. I would hate for the CLI to be less featured than the webapp. Unless I've missed it in the man page?
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,28 @@
### Please describe the problem.
git annex installer on Windows only installs git-annex-licenses.txt git-annex-uninstall.exe git-annex.exe
This makes git-annex unusable over ssh (Windows box runs cygwin sshd).
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
Windows 7 64bit
git annex version
git-annex version: 5.20140421-g78d6aa1
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV DNS Feeds Quvi TDFA CryptoHash
key/value backends: SHA256E SHA1E SHA512E SHA224E SHA384E SKEIN256E SKEIN512E SHA256 SHA1 SHA512 SHA224 SHA384 SKEIN256 SKEIN512 WORM URL
remote types: git gcrypt S3 bup directory rsync web webdav tahoe glacier hook external
### 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.
"""]]

View file

@ -0,0 +1,23 @@
### Please describe the problem.
I've setup a gcrypt based git backup repository as per the examples here:
http://git-annex.branchable.com/tips/fully_encrypted_git_repositories_with_gcrypt/
It all seems to work well until I try to do any kind git annex operation from the console on the gcrypted repo on the remote server. If I run a `git annex fsck` (this seems a reasonable thing to do) then it initialises the encrypted remote with a different uuid to the one in the creation step. The initial repository that created the repo seems to work okay but it's no longer possible to add further repositories without getting conflicting uuid errors.
### What steps will reproduce the problem?
### What version of git-annex are you using? On what operating system?
### 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.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 1"
date="2014-04-27T15:04:09Z"
content="""
Thinking about it some more perhaps it's not a reasonable thing to do if you don't want people to be able to discover info about the repo. However it would be good to somehow prevent git-annex from running a local init operation when working with a gcrypt repo.
"""]]

View file

@ -0,0 +1,16 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 2"
date="2014-04-27T19:19:22Z"
content="""
I'm having a pretty bad time with gcrypt based repos. Seemingly at random a `git-annex sync` will occasionally decide that the remote repo doesn't exist and then attempt to create a new one - it generates a new gcryptid and the repository seems lost.
This sometimes happens after a good few hours of use, sometimes it happens immediately after creation (but maybe due to the fact that annexs are sullied by previous bad attempts). I've cleaned up making the repo dead, removing via `git remote` and editing the remote.log in the git-annex branch. No idea if that's enough.
What do you need from me to try to sort this?
Cheers,
Matt.
"""]]

View file

@ -0,0 +1,164 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 3"
date="2014-04-29T03:00:59Z"
content="""
Hi, I'm finally through trial and error am able to reproduce the bug...
On OSX using version 5.20140420-ga25b8bb the creation of an gcrypt remote via initremote does not work properly. See the attached debug log for what happens - no errors but subsequent syncs fail and creates a new repo.
Using linux and version 5.20140421-g515d251 to create the gcrypt does work without issue. Interestingly the OSX client will happily use the linux created repo without problem (at least it hasn't borked it yet). This suggests something up in the creation step. Perhaps this is fixed in the later version (see the other bug about the latest OSX upgrade having the older binary)? But I didn't see anything in the change log about it? But I did see the gcrypt script in the manifest now...
<pre>~/iMovies $ git annex initremote isilon-2 type=gcrypt gitrepo=ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2 keyid=matt@dancingfrog.co.uk
[2014-04-29 01:54:47 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"git-annex\"]
[2014-04-29 01:54:47 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
[2014-04-29 01:54:47 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..3269adaaa41b42dab88399e8212d77301967f436\",\"--oneline\",\"-n1\"]
git [2014-04-29 01:54:47 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..4dc8becdffd42c9af57e0d1007892516f2114c0e\",\"--oneline\",\"-n1\"]
[2014-04-29 01:54:47 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..13d8993b7d9a89ea4198ec3edd63aa575745c64c\",\"--oneline\",\"-n1\"]
[2014-04-29 01:54:47 BST] chat: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"cat-file\",\"--batch\"]
initremote isilon-2 (encryption setup) [2014-04-29 01:54:47 BST] read: gpg [\"--batch\",\"--no-tty\",\"--use-agent\",\"--quiet\",\"--trust-model\",\"always\",\"--with-colons\",\"--list-public-keys\",\"matt@dancingfrog.co.uk\"]
[2014-04-29 01:54:47 BST] read: gpg [\"--batch\",\"--no-tty\",\"--use-agent\",\"--quiet\",\"--trust-model\",\"always\",\"--gen-random\",\"--armor\",\"2\",\"512\"]
[2014-04-29 01:54:47 BST] chat: gpg [\"--batch\",\"--no-tty\",\"--use-agent\",\"--quiet\",\"--trust-model\",\"always\",\"--recipient\",\"68D8501429C42E01\",\"--encrypt\",\"--no-encrypt-to\",\"--no-default-recipient\",\"--force-mdc\",\"--no-textmode\"]
(hybrid cipher with gpg key 68D8501429C42E01) [2014-04-29 01:54:47 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"remote\",\"add\",\"isilon-2\",\"gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2\"]
[2014-04-29 01:54:47 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"config\",\"remote.isilon-2.gcrypt-participants\",\"68D8501429C42E01\"]
[2014-04-29 01:54:47 BST] read: git [\"config\",\"--null\",\"--list\"]
[2014-04-29 01:54:48 BST] read: gpg [\"--batch\",\"--no-tty\",\"--use-agent\",\"--quiet\",\"--trust-model\",\"always\",\"--with-colons\",\"--list-secret-keys\",\"--fixed-list-mode\"]
[2014-04-29 01:54:48 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"config\",\"remote.isilon-2.gcrypt-signingkey\",\"68D8501429C42E01\"]
[2014-04-29 01:54:48 BST] read: git [\"config\",\"--null\",\"--list\"]
[2014-04-29 01:54:48 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"fetch\",\"isilon-2\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
[2014-04-29 01:54:49 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"push\",\"isilon-2\",\"refs/heads/git-annex\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
gcrypt: Setting up new repository
gcrypt: Remote ID is :id:oWSdoSaFhKA19TcXRHPS
Counting objects: 4170, done.
Compressing objects: 100% (3113/3113), done.
Total 4170 (delta 149), reused 146 (delta 3)
gcrypt: Encrypting to: -R 68D8501429C42E01
gcrypt: Requesting manifest signature
You need a passphrase to unlock the secret key for
user: \"Matt Ford (Work) <matt.ford@manchester.ac.uk>\"
1024-bit DSA key, ID 29C42E01, created 2010-03-10
gpg: 68D8501429C42E01: skipped: public key already present
To gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
* [new branch] git-annex -> git-annex
[2014-04-29 01:54:52 BST] read: git [\"config\",\"--null\",\"--list\"]
[2014-04-29 01:54:52 BST] call: ssh [\"-S\",\".git/annex/ssh/rss\",\"-o\",\"ControlMaster=auto\",\"-o\",\"ControlPersist=yes\",\"-T\",\"rss\",\"git-annex-shell 'gcryptsetup' '/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2' ':id:oWSdoSaFhKA19TcXRHPS'\"]
ok
[2014-04-29 01:54:53 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"config\",\"remote.isilon-2.annex-gcrypt\",\"shell\"]
[2014-04-29 01:54:53 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"config\",\"remote.isilon-2.annex-uuid\",\"8fc5d933-d76f-5a61-b3a0-96b909e3f06c\"]
ok
[2014-04-29 01:54:53 BST] chat: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"hash-object\",\"-w\",\"--stdin-paths\",\"--no-filters\"]
[2014-04-29 01:54:53 BST] feed: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"update-index\",\"-z\",\"--index-info\"]
[2014-04-29 01:54:53 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
(Recording state in git...)
[2014-04-29 01:54:53 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"write-tree\"]
[2014-04-29 01:54:53 BST] chat: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"commit-tree\",\"8c27761996045cb6daf7dc83920e15bfe0f2b2ed\",\"-p\",\"refs/heads/git-annex\"]
[2014-04-29 01:54:53 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"update-ref\",\"refs/heads/git-annex\",\"0755de89ac06bb3babc73de294a550d9b62f39f1\"]
[2014-04-29 01:54:53 BST] read: ssh [\"-O\",\"stop\",\"-S\",\"rss\",\"-o\",\"ControlMaster=auto\",\"-o\",\"ControlPersist=yes\",\"localhost\"]
~/iMovies $ git annex sync
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"git-annex\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..0755de89ac06bb3babc73de294a550d9b62f39f1\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..4dc8becdffd42c9af57e0d1007892516f2114c0e\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..3269adaaa41b42dab88399e8212d77301967f436\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..13d8993b7d9a89ea4198ec3edd63aa575745c64c\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:55 BST] chat: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"cat-file\",\"--batch\"]
commit [2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"commit\",\"-a\",\"-m\",\"git-annex automatic sync\"]
ok
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"symbolic-ref\",\"HEAD\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"refs/heads/master\"]
[2014-04-29 01:57:55 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/heads/synced/master\"]
[2014-04-29 01:57:55 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/master..refs/heads/synced/master\",\"--oneline\",\"-n1\"]
pull isilon
[2014-04-29 01:57:55 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"fetch\",\"isilon\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov
[2014-04-29 01:57:56 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon/master\"]
[2014-04-29 01:57:56 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/master..refs/remotes/isilon/master\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:56 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon/synced/master\"]
[2014-04-29 01:57:56 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/synced/master..refs/remotes/isilon/synced/master\",\"--oneline\",\"-n1\"]
ok
pull isilon-2
[2014-04-29 01:57:57 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"fetch\",\"isilon-2\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
[2014-04-29 01:57:57 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon-2/master\"]
[2014-04-29 01:57:57 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon-2/synced/master\"]
ok
[2014-04-29 01:57:57 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"git-annex\"]
[2014-04-29 01:57:57 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
[2014-04-29 01:57:57 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..0755de89ac06bb3babc73de294a550d9b62f39f1\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:58 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..4dc8becdffd42c9af57e0d1007892516f2114c0e\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:58 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..3269adaaa41b42dab88399e8212d77301967f436\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:58 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/heads/git-annex..13d8993b7d9a89ea4198ec3edd63aa575745c64c\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:58 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"branch\",\"-f\",\"synced/master\"]
[2014-04-29 01:57:58 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon/synced/master\"]
[2014-04-29 01:57:58 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/remotes/isilon/synced/master..refs/heads/synced/master\",\"--oneline\",\"-n1\"]
[2014-04-29 01:57:58 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon/git-annex\"]
[2014-04-29 01:57:58 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"log\",\"refs/remotes/isilon/git-annex..git-annex\",\"--oneline\",\"-n1\"]
push isilon
[2014-04-29 01:57:58 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"push\",\"isilon\",\"+git-annex:synced/git-annex\",\"master:synced/master\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov
gcrypt: Setting up new repository
gcrypt: Remote ID is :id:p4cHPeAFIRIvZTnm4UrK
Counting objects: 5649, done.
Compressing objects: 100% (4579/4579), done.
Total 5649 (delta 151), reused 146 (delta 3)
gcrypt: Encrypting to: -R 68D8501429C42E01
gcrypt: Requesting manifest signature
You need a passphrase to unlock the secret key for
user: \"Matt Ford (Work) <matt.ford@manchester.ac.uk>\"
1024-bit DSA key, ID 29C42E01, created 2010-03-10
gpg: 68D8501429C42E01: skipped: public key already present
To gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov
* [new branch] git-annex -> synced/git-annex
* [new branch] master -> synced/master
[2014-04-29 01:58:01 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"push\",\"isilon\",\"master\"]
You need a passphrase to unlock the secret key for
user: \"Matt Ford (Work) <matt.ford@manchester.ac.uk>\"
1024-bit DSA key, ID 29C42E01, created 2010-03-10
ok
[2014-04-29 01:58:03 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"show-ref\",\"--verify\",\"-q\",\"refs/remotes/isilon-2/synced/master\"]
push isilon-2
[2014-04-29 01:58:03 BST] call: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"push\",\"isilon-2\",\"+git-annex:synced/git-annex\",\"master:synced/master\"]
gcrypt: Development version -- Repository format MAY CHANGE
gcrypt: Repository not found: ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
gcrypt: Setting up new repository
gcrypt: Remote ID is :id:wTHlCd+vFviIzoTDv2Xu
Counting objects: 5649, done.
Compressing objects: 100% (4579/4579), done.
Total 5649 (delta 152), reused 146 (delta 3)
gcrypt: Encrypting to: -R 68D8501429C42E01
gcrypt: Requesting manifest signature
You need a passphrase to unlock the secret key for
user: \"Matt Ford (Work) <matt.ford@manchester.ac.uk>\"
1024-bit DSA key, ID 29C42E01, created 2010-03-10
gpg: 68D8501429C42E01: skipped: public key already present
To gcrypt::ssh://rss/home/matt/mnt/isilon/rss/zzalsmf3/git-annex/mov2
* [new branch] git-annex -> synced/git-annex
* [new branch] master -> synced/master
[2014-04-29 01:58:06 BST] read: git [\"--git-dir=/Volumes/Media/iTunes Media/Movies/.git\",\"--work-tree=/Volumes/Media/iTunes Media/Movies\",\"push\",\"isilon-2\",\"master\"]
You need a passphrase to unlock the secret key for
user: \"Matt Ford (Work) <matt.ford@manchester.ac.uk>\"
1024-bit DSA key, ID 29C42E01, created 2010-03-10
ok
[2014-04-29 01:58:09 BST] read: ssh [\"-O\",\"stop\",\"-S\",\"rss\",\"-o\",\"ControlMaster=auto\",\"-o\",\"ControlPersist=yes\",\"localhost\"]
</pre>
"""]]

View file

@ -0,0 +1,25 @@
### Please describe the problem.
Can't access X console after returning to work overnight.
### What steps will reproduce the problem?
1. Create git-annex remote repository, with git annex assistance, connected via ssh, using ssh-agent key for authentication.
2. "ssh-add -D" to delete the ssh key when not attending computer. Forget to kill git-annex assistant.
3. Lock screen with xscreeensaver.
4. Return to work. Unlock screen. Find keyboard and mouse not responding. However there are no dialog boxes on screen.
5. Open up text console, kill the numerous ssh-askpass processes. Find more ssh-askpass processes. Kill the git-annex processes, then kill the ssh-askpass processes. Find I can access the x console again.
### What version of git-annex are you using? On what operating system?
Version 5.20140320~bpo70+1 in Debian backports.
### Please provide any additional information below.
This isn't git-annex's fault, but it is a serious problem with using git-annex assistant.
Suspect ssh-askpass isn't displaying dialog properly as it conflicts with xscreensaver, which is running at the time.
Not really sure what the solution is.
Unfortunately, Out of time for today, will double check this report makes sense tomorrow.

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-05-01T13:56:32Z"
content="""
This will be fixed by [[design/assistant/sshpassword]], assuming I make it bypass the OS's IMHO superior ssh-askpass and use its own.
It would be better to file a bug on the actual program you had problems with though, which is not git-annex.
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 2"
date="2014-05-01T14:04:12Z"
content="""
Actually, no, that is only going to handle ssh password prompting the one time needed to set up a passwordless dedicated ssh key.
It may be that it makes sense to *always* set up such a key, which would bypass the normal key handling, and so avoid this problem. Currently, the assumption is that if you have gone to the bother to already set up a login to a host, without a password being needed, it makes sense for the assistant to use that configuration.
"""]]

View file

@ -0,0 +1,45 @@
### Please describe the problem.
- Add remote ssh repository (from add more repositories menu)
- Repos sync even files, but remote repo is marked (metadata only) - there is Fail on sync with this repository.
The actual issue is that UUID was not found. I checked the logs and it's obvious that git-annex-shell was not found on the remote.
### What steps will reproduce the problem?
I have
Linux box with (ZSH as a primary shell) where ~/.zshrc contains "export PATH=/path/to/annex:$PATH)
MacOSX box with (ZSH as a primary shell) where ~/.zshrc and ~/.bash contains "export PATH=/path/to/annex:$PATH)
The issue appears both directions.
When I use ssh to connect remote host git-annex-shell is on PATH and works.
I guess you don't have full shell context of the user.
Worth to mention, that add remote repo (using a discovery - local computer) works well in the same repo.
### What version of git-annex are you using? On what operating system?
git-annex version 5.20140420-ga25b8bb
### Please provide any additional information below.
Can't find the original original log, but once repo created it contains "zsh:1: git-annex-shell not found" so it later switch repository to (metadata only) mode.
This frequently repeat in the log:
[[!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
Please make sure you have the correct access rights
and the repository exists.
Permission denied, please try again.
Permission denied, please try again.
Permission denied (publickey,password).
fatal: Could not read from remote repository.
# End of transcript or log.
"""]]

View file

@ -0,0 +1,44 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawmTIL7ubr5opWM69Q5VtCxuxC2H0SSnzic"
nickname="Petr"
subject="Additional info"
date="2014-04-29T05:07:26Z"
content="""
Not the above was done using git-annex webapp. I have also tried the same from cmdline with the same results:
[[!format sh \"\"\"
#Once remote added
➜ test_move_bp git:(annex/direct/master) git annex enableremote macrepo
zsh:1: command not found: git-annex-shell
Remote macrepo does not have git-annex installed; setting annex-ignore
git-annex: Unknown special remote name.
(No special remotes are currently known; perhaps use initremote instead?)
#However the ssh works fine:
➜ test_move_bp git:(annex/direct/master) ssh pmichalec@ape-mac-mini.local
Last login: Tue Apr 29 06:19:29 2014
➜ ~ which git-annex-shell
/Applications/git-annex.app/Contents/MacOS/git-annex-shell
➜ ~ /Applications/git-annex.app/Contents/MacOS/git-annex-shell
git-annex-shell: bad parameters
Usage: git-annex-shell [-c] command [parameters ...] [option ...]
Plumbing commands:
commit DIRECTORY commits any staged changes to the git-annex branch
configlist DIRECTORY outputs relevant git configuration
dropkey DIRECTORY KEY ... drops annexed content for specified keys
gcryptsetup DIRECTORY VALUE sets up gcrypt repository
inannex DIRECTORY KEY ... checks if keys are present in the annex
notifychanges DIRECTORY sends notification when git refs are changed
recvkey DIRECTORY KEY runs rsync in server mode to receive content
sendkey DIRECTORY KEY runs rsync in server mode to send content
transferinfo DIRECTORY KEY updates sender on number of bytes of content received
\"\"\"]]
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 2"
date="2014-04-29T21:03:41Z"
content="""
You need to fix your system so that git-annex-shell in in PATH automatically wheneven you ssh into it, and then it will work.
I'm sorry, but I can't help you do so. I suggest you read the documentation for your login shell.
"""]]

View file

@ -0,0 +1,21 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawmTIL7ubr5opWM69Q5VtCxuxC2H0SSnzic"
nickname="Petr"
subject="SOLVED"
date="2014-04-29T21:42:39Z"
content="""
You were right.
When executed command over SSH it does not perform login (so .**rc files are not necessarily loaded).
Zsh:
.zprofile or rather .zshenv (is loaded, use these to set PATH)
Note: .profile is not loaded at all (it's Bash stuff)
Bash:
.bashrc is said to be loaded but not .profile
See:
http://shreevatsa.wordpress.com/2008/03/30/zshbash-startup-files-loading-order-bashrc-zshrc-etc/
http://superuser.com/questions/187639/zsh-not-hitting-profile
https://wiki.archlinux.org/index.php/zsh
"""]]

View file

@ -10,3 +10,40 @@ securely?
This might come down to a simple change to the webapp to prompt for the
password, and then rather a lot of pain to make the webapp use HTTPS so we
can be pretty sure noone is sniffing the (localhost) connection.
## ssh-askpass approach
* If ssh-askpass is in PATH, or `SSH_ASKPASS` is set, do nothing.
(Unless webapp is run remotely.)
* Otherwise, have the assistant set `SSH_ASKPASS` to a command that will
cause the webapp to read the password and forward it on. Also, set
DISPLAY to ensure that ssh runs the program.
Looking at ssh.exe, I think this will even work on windows; it contains the
code to run ssh-askpass.
### securely handling the password
* Maybe force upgrade webapp to https? Locally, the risk would be that
root could tcpdump and read password, so not large risk. If webapp
is being accessed remotely, absolutely: require https.
* Use hs-securemem to store password.
* Avoid storing password for long. Erase it after webapp setup of remote
is complete. Time out after 10 minutes and erase it.
* Prompt using a html field name that does not trigger web browser password
saving if possible.
### ssh-askpass shim, and password forwarding
`SSH_ASKPASS` needs to be set to a program (probably git-annex)
which gets the password from the webapp, and outputs it to stdout.
Seems to call for the webapp and program to communicate over a local
socket (locked down so only user can access) or environment.
Environment is not as secure (easily snooped by root).
Local socket probably won't work on Windows. Could just use a temp file.
Note that the webapp can probe to see if ssh needs a password, and can
prompt the user for it before running ssh and the ssh-askpass shim.
This avoids some complexity, and perhaps some attack vectors,
if the shim cannot requst an arbitrary password prompt.

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawnXybLxkPMYpP3yw4b_I6IdC3cKTD-xEdU"
nickname="Matt"
subject="comment 1"
date="2014-04-29T10:10:04Z"
content="""
Can you do something similar for gpg-agent? Or do it instead with a ssh supported gpg-agent?
"""]]

View file

@ -71,3 +71,24 @@ repositories have a non-git out of band signaling mechanism. This could,
for example, be used by laptopB to tell laptopA that it's trying to send
a file directly to laptopC. laptopA could then defer the upload to the
cloud for a while.
## syncing only requested content
In some situations, nodes only want particular files, and not everything.
(Or don't have the bandwidth to get everything.) A way to handle this,
that should work in a fully ad-hoc, offline distributed network,
suggested by Vincenzo Tozzi:
* Nodes generate a request for a specific file they want, committed
to git somewhere.
* This request has a TTL (of eg 3).
* When syncing, copy the requests that a node has, and decrease their TTL
by 1. Requests with a TTL of 0 have timed out and are not copied.
(So, requests are stored in git, but on eg, per-node branches.)
* Only copy content to nodes that have a request for it (either one
originating with them, or one they copied from another node).
* Each request indicates the requesting node, so once no nodes have an
active request for a particular file, it's ok to drop it from the
transfer nodes (honoring numcopies etc of course).
A simulation of a network using this method is in [[simroutes.hs]]

View file

@ -0,0 +1,250 @@
-- Simulation of non-flood syncing of content, across a network of nodes.
module Main where
import System.Random
import Control.Monad.Random
import Control.Monad
import Control.Applicative
import Data.Ratio
import Data.Ord
import Data.List
import qualified Data.Set as S
{-
- Tunable values
-}
totalFiles :: Int
totalFiles = 10
-- How likely is a given file to be wanted by any particular node?
probabilityFilesWanted :: Probability
probabilityFilesWanted = 0.10
-- How many different locations can each transfer node move between?
-- (Min, Max)
transferDestinationsRange :: (Int, Int)
transferDestinationsRange = (2, 5)
-- Controls how likely transfer nodes are to move around in a given step
-- of the simulation.
-- (They actually move slightly less because they may start to move and
-- pick the same location they are at.)
-- (Min, Max)
transferMoveFrequencyRange :: (Probability, Probability)
transferMoveFrequencyRange = (0.10, 1.00)
-- counts both immobile and transfer nodes as hops, so double Vince's
-- theoretical TTL of 3.
maxTTL :: TTL
maxTTL = TTL 6
minTTL :: TTL
minTTL = TTL 1
numImmobileNodes :: Int
numImmobileNodes = 10
numTransferNodes :: Int
numTransferNodes = 20
numSteps :: Int
numSteps = 100
-- IO code
main = putStrLn . summarize =<< evalRandIO (simulate numSteps =<< genNetwork)
-- Only pure code below :)
data Network = Network [ImmobileNode] [TransferNode]
deriving (Show, Eq)
data ImmobileNode = ImmobileNode NodeRepo
deriving (Show, Eq)
-- Index in the Network's list of ImmobileNodes.
type ImmobileNodeIdx = Int
data TransferNode = TransferNode
{ currentlocation :: ImmobileNodeIdx
, possiblelocations :: [ImmobileNodeIdx]
, movefrequency :: Probability
, transferrepo :: NodeRepo
}
deriving (Show, Eq)
data NodeRepo = NodeRepo
{ wantFiles :: [Request]
, haveFiles :: S.Set File
}
deriving (Show, Eq)
data File = File Int
deriving (Show, Eq, Ord)
randomFile :: (RandomGen g) => Rand g File
randomFile = File <$> getRandomR (0, totalFiles)
data Request = Request File TTL
deriving (Show)
-- compare ignoring TTL
instance Eq Request where
(Request f1 _) == (Request f2 _) = f1 == f2
requestedFile :: Request -> File
requestedFile (Request f _) = f
requestTTL :: Request -> TTL
requestTTL (Request _ ttl) = ttl
data TTL = TTL Int
deriving (Show, Eq, Ord)
incTTL :: TTL -> TTL
incTTL (TTL t) = TTL (t + 1)
decTTL :: TTL -> TTL
decTTL (TTL t) = TTL (t - 1)
staleTTL :: TTL -> Bool
staleTTL (TTL t) = t < 1
-- Origin of a request starts one higher than max, since the TTL
-- will decrement the first time the Request is transferred to another node.
originTTL :: TTL
originTTL = incTTL maxTTL
randomRequest :: (RandomGen g) => Rand g Request
randomRequest = Request
<$> randomFile
<*> pure originTTL
type Probability = Float
randomProbability :: (RandomGen g) => Rand g Probability
randomProbability = getRandomR (0, 1)
simulate :: (RandomGen g) => Int -> Network -> Rand g Network
simulate 0 net = return net
simulate c net = simulate (c - 1) =<< step net
-- Each step of the simulation, check if each TransferNode wants to move,
-- and if so:
-- 1. It and its current location exchange their Requests.
-- 2. And they exchange any requested files.
-- 3. Move it to a new random location.
--
-- Note: This implementation does not exchange requests between two
-- TransferNodes that both arrive at the same location at the same step,
-- and then move away in the next step.
step :: (RandomGen g) => Network -> Rand g Network
step (Network immobiles transfers) = go immobiles [] transfers
where
go is c [] = return (Network is c)
go is c (t:ts) = do
r <- randomProbability
if movefrequency t <= r
then do
let (is1, (currentloc:is2)) = splitAt (currentlocation t) is
let (currentloc', t') = exchangeRequestsFiles currentloc t
t'' <- move t'
go (is1 ++ currentloc' : is2) (c ++ [t'']) ts
else go is (c ++ [t]) ts
type Exchanger = ImmobileNode -> TransferNode -> (ImmobileNode, TransferNode)
exchangeRequestsFiles :: Exchanger
exchangeRequestsFiles (ImmobileNode ir) t@(TransferNode { transferrepo = tr }) =
( ImmobileNode (go ir tr)
, t { transferrepo = go tr ir }
)
where
go r1 r2 = r1
{ wantFiles = foldr addRequest (wantFiles r1) (wantFiles r2)
, haveFiles = S.foldr (addFile (wantFiles r1)) (haveFiles r1) (haveFiles r2)
}
-- Adds a file to the set, when there's a request for it.
addFile :: [Request] -> File -> S.Set File -> S.Set File
addFile rs f fs
| any (\r -> f == requestedFile r) rs = S.insert f fs
| otherwise = fs
-- Decrements TTL, and avoids adding request with a stale TTL, or a
-- request for an already added file with the same or a lower TTL.
addRequest :: Request -> [Request] -> [Request]
addRequest (Request f ttl) rs
| staleTTL ttl' = rs
| any (\r -> requestTTL r >= ttl) similar = rs
| otherwise = r' : other
where
ttl' = decTTL ttl
r' = Request f ttl'
(other, similar) = partition (/= r') rs
move :: (RandomGen g) => TransferNode -> Rand g TransferNode
move t = do
newloc <- randomfrom (possiblelocations t)
return $ t { currentlocation = newloc }
genNetwork :: (RandomGen g) => Rand g Network
genNetwork = do
immobiles <- sequence (replicate numImmobileNodes mkImmobile)
transfers <- sequence (replicate numTransferNodes (mkTransfer immobiles))
return $ Network immobiles transfers
mkImmobile :: (RandomGen g) => Rand g ImmobileNode
mkImmobile = ImmobileNode <$> genrepo
where
genrepo = NodeRepo
-- The files this node wants.
-- Currently assumes each file is equally popular.
<$> sequence (replicate (truncate (fromIntegral totalFiles * probabilityFilesWanted)) randomRequest)
-- The files this node already has.
--
-- We'll assume equal production, so split the total
-- number of files amoung the immobile nodes.
-- (This will produce some duplication of files
-- (consider birthday paradox), and some missing files.)
--
-- TODO: Some immobile nodes are internet connected,
-- and these should all share their files automatically)
-- (Also when running the sim.)
<*> (S.fromList <$> sequence (replicate (totalFiles `div` numImmobileNodes) randomFile))
mkTransfer :: (RandomGen g) => [ImmobileNode] -> Rand g TransferNode
mkTransfer immobiles = do
-- Transfer nodes are given random routes. May be simplistic.
-- Also, some immobile nodes will not be serviced by any transfer nodes.
numpossiblelocs <- getRandomR transferDestinationsRange
possiblelocs <- sequence (replicate numpossiblelocs (randomfrom indexes))
currentloc <- randomfrom possiblelocs
movefreq <- getRandomR transferMoveFrequencyRange
-- transfer nodes start out with no files or requests in their repo
let repo = (NodeRepo [] S.empty)
return $ TransferNode currentloc possiblelocs movefreq repo
where
indexes = [0..length immobiles - 1]
randomfrom :: (RandomGen g) => [a] -> Rand g a
randomfrom l = do
i <- getRandomR (1, length l)
return $ l !! (i - 1)
summarize :: Network -> String
summarize (Network is _ts) = unlines $ map (\(d, s) -> d ++ ": " ++ s)
[ ("Total wanted files",
show (sum (overis (length . findoriginreqs . wantFiles . repo))))
, ("Wanted files that were not transferred to requesting node",
show (sum (overis (S.size . findunsatisfied . repo))))
--, ("List of files not transferred", show unsatisfied)
, ("Immobile nodes at end", show is)
]
where
findoriginreqs = filter (\r -> requestTTL r == originTTL)
findunsatisfied r =
let wantedfs = S.fromList $ map requestedFile (findoriginreqs (wantFiles r))
in S.difference wantedfs (haveFiles r)
repo (ImmobileNode r) = r
overis f = map f is

View file

@ -0,0 +1,15 @@
[[!comment format=mdwn
username="tdussa"
ip="217.84.74.69"
subject="Why not automatically add the whole date?"
date="2014-04-30T20:41:20Z"
content="""
Hi,
apologies if I am missing something, but from what I understand, git-annex will automatically add the year and the month from a file's mtime to its metadata if instructed to do so.
So... What about the day (or the time, for that matter?)? What is the reasoning behind the decision not to add those bits automatically? And, is there a way to get git-annex to add those bits of information automatically as well (besides the obvious way of creating a pre-commit-hook script to that effect)?
THX & Cheers,
Toby.
"""]]

View file

@ -6,13 +6,13 @@ Now in the
* Month 1 [[!traillink assistant/encrypted_git_remotes]]
* Month 2 [[!traillink assistant/disaster_recovery]]
* Month 3 user-driven features and polishing [[!traillink todo/direct_mode_guard]] [[!traillink assistant/upgrading]]
* Month 3 [[!traillink todo/direct_mode_guard]] [[!traillink assistant/upgrading]]
* Month 4 [[!traillink assistant/windows text="Windows webapp"]], Linux arm, [[!traillink todo/support_for_writing_external_special_remotes]]
* Month 5 user-driven features and polishing
* Month 6 get Windows out of beta, [[!traillink design/metadata text="metadata and views"]]
* Month 7 user-driven features and polishing
* **Month 8 [[!traillink git-remote-daemon]] [[!traillink assistant/telehash]]**
* Month 9 [[!traillink assistant/gpgkeys]] [[!traillink assistant/sshpassword]]
* **Month 8 [[!traillink git-remote-daemon]]**
* Month 9 Brazil!, [[!traillink assistant/sshpassword]]
* Month 10 get [[assistant/Android]] out of beta
* Month 11 [[!traillink assistant/chunks]] [[!traillink assistant/deltas]]
* Month 12 user-driven features and polishing
* Month 11 [[!traillink assistant/chunks]], [[!traillink assistant/deltas]], [[!traillink assistant/gpgkeys]] (pick 2?)
* Month 12 [[!traillink assistant/telehash]]

View file

@ -0,0 +1,14 @@
I hope this will be a really good release. Didn't get all the way to
[[design/assistant/telehash]] this month, but the remotedaemon is pretty sweet. Updated [[design/roadmap]]
pushes telehash back again.
The files in this release are now gpg signed, after recently moving the
downloads site to a dedicated server, which has a dedicated gpg key.
You can verify the detached signatures as an additional security check
over trusting SSL. The automatic upgrade code doesn't check the gpg
signatures yet.
Sören Brunk has ported the webapp to Bootstrap 3.
<https://github.com/brunksn/git-annex/tree/bootstrap3>
The branch is not ready for merging yet (it would break the Debian stable
backports), but that was a nice surprise.

View file

@ -0,0 +1,22 @@
Now git-annex's self-upgrade code will check the gpg signature of a
new version before using it.
To do this I had to include the gpg public keys into the
git-annex distribution, and that raised the question of which public keys
to include. Currently I have both the dedicated git-annex distribution
signing key, and my own gpg key as a backup in case I somehow misplace the
former.
Also spent a while looking at the recent logs on the web server. There
seem to be around 600 users of the assistant with
upgrade checking enabled. That breaks down to 68% Linux amd64, 20% Linux
i386, 11% OSX Mavericks, and 0.5% OSX Lion.
Most are upgrading successfully, but there are a few that seem to
repeatedly fail for some reason. (Not counting the OSX Lion, which will
probably never find an upgrade available.) I hope that someone who is
experiencing an upgrade failure gets in touch with some debug logs.
In the same time period, around 450 unique hosts manually downloaded a
git-anex distribution. Also compare with Debian popcon, which has 1200
reporting git-annex users.

View file

@ -0,0 +1,10 @@
Next month the roadmap has me working on [[design/assistant/sshpassword]].
That will be a nice UI improvement and I'd be very surprised if it takes
more than a week, which is great.
Getting a jump on it today, investigating using `SSH_ASKPASS`. It seems this
will even work on Windows! Preliminary design in [[design/assistant/sshpassword]].
Time to get on a plane to a plane to a plane to Brasilia!
[[!meta date="Fri, 25 Apr 2014 16:32:36 -0400"]]

View file

@ -0,0 +1,12 @@
Today was mostly spent driving across Brazil, but I had energy this evening
for a little work on git-annex.
Made the assistant delete old temporary files on startup. I've had
scattered reports of a few users whose `.git/annex/tmp` contained many
files, apparently put there by the assistant when it locks down a file
prior to annexing it. That seems it could possibly be a bug -- or it could
just be unclean shutdowns interrupting the assistant. Anyway, this will
deal with any source of tmp cruft, and I made sure to preserve
tmp files for partially downloaded content.
[[!meta date="Sun, 27 Apr 2014 22:12:55 -0300"]]

View file

@ -0,0 +1,20 @@
Reviewed Sören's updated bootstrap3 patch, which appeared while I was
[traveling](http://joeyh.name/blog/entry/the_real_Brazil/). Sören
kindly fixed it to work with Debian stable's old version of Yesod,
which was quite a lot of work. The new new bootstrap3 UI looks nice,
found a few minor issues, but expect to be able to merge it soon.
Started on [[design/assistant/sshpassword]] groundwork. Added a simple
password cache to the assistant, with automatic expiration, and made
git-annex be able to be run by ssh as the `SSH_ASKPASS` program.
The main difficulty will be changing the webapp's UI to prompt for the ssh
password when one is needed. There are several code paths in ssh remote
setup where a password might be needed. Since the cached password expires,
it may need to be prompted for at any of those points. Since a new page is
loading, it can't pop up a prompt on the current page; it needs to redirect
to a password prompt page and then redirect back to the action that needed
the password. ...At least, that's one way to do it.
I'm going to sleep on it and hope I dream up a better way.
[[!meta date="Tue, 29 Apr 2014 18:33:53 -0400"]]

View file

@ -0,0 +1,13 @@
I've moved out of implementation mode (unable to concentrate enough), and
into high-level design mode.
[[Syncing efficiency|design/assistant/syncing/efficiency]] has been an open TODO for years,
to find a way to avoid flood filling the network, and find more efficient
ways to ensure data only gets to the nodes that want it. Relatedly,
Android devices often need a way to mark individual files they want to have.
Had a [very productive discussion with Vince and Fernao](http://joeyh.name/blog/entry/who_needs_whiteboards_when_you_have_strange_seed_pods_from_the_jungle/)
and I think we're heading toward a design that will address both these
needs, as well as some more Brazil-specific use cases, about which more
later.
Today's work was sponsored by Casa do Boneco.

View file

@ -0,0 +1,5 @@
I would like to use git-annex with [S3 reduced redundancy storace (RRS)](https://aws.amazon.com/s3/faqs/#rrs_anchor), a cheaper S3 service with an higher chance of seeing your files disappear overnight. This means that git-annex may think that a certain files has been copied to a S3 remote while, in fact, it is no longer there.
I would like to check that the files S3 are really there and, if some files are not, record that we lost that copy. In the case of S3, either the data is there and it is complete or it is not there at all, so there is no need to check the data itself, just the presence of the files.
Is there a way to check that all the files that are supposed to be in a S3 remote are still there?

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 2"
date="2014-04-24T18:12:59Z"
content="""
git annex fsck --fast --from $yours3remote
"""]]

View file

@ -0,0 +1,14 @@
Hi,
I really like git-annex for sharing contents with all my devices. But i have a problem with the assistant on my phone, i don't know how to git annex get some file but not all.
For example i have this on a remote:
repository:
- big file1
- big file2
- big file3
I have this repository on my phone. I would like to be able to checkout out only "big file2" directly within the assistant.
How can i achieve that?
Thank you.

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-24T18:15:15Z"
content="""
[[preferred_content]] expressions can be used to do that. Works best if all the files you want have some extension or are in a specific directory.
There are some [[preferred_content/standard_groups]] that might do what you want, particularly the \"manual\" one.
"""]]

View file

@ -0,0 +1,12 @@
[[!comment format=mdwn
username="elfangor"
ip="176.57.244.101"
subject="comment 2"
date="2014-04-28T13:12:07Z"
content="""
Thanks for your reply.
The Standard group \"manual\" seems to be what i need. The last thing i'd like to now is, is there a way to do git annex get on the assistant(on the webui) on my phone? (I know i can do this on the shell opened, but it's not that easy to write from the phone.) I guess it's not implemented, and i understand that it should be a lot of work to add a file browser in the ui where you can git annex get, and git annex add from it.
Thanks again for your answer, really helpfull: I have a better idea on how i will structur my git annex repositories.
"""]]

View file

@ -0,0 +1 @@
Here is my situation, Say I have a repo that is 3 TBs (lets call this repo A has full copy of everything.) and I have 3 other drives all 1 TB each lets call them B C D, then I have partial checkouts on my laptops D E. What I would like to do is, have two copies of all files in A and BCD I would like to threat BCD as a group acting like a single repo so A distributes files evenly to drives in group BCD. I also want copies in D and E to not count towards num of files. As for the latter even though I set D and E as untrusted annex still counts copies on those repos If a get a file in D assistant drops a copy from one of the trusted repos A or BCD I have to move it back instead of just dropping it. Also How can I or is it possible to set BCD to act as a group so A distributes files among drives currently I can do this using find/get but it turns it into a math problem every time a add a file to A I have to manually check which disk has most space navigate to it check files with less copies then 2 and get them.

View file

@ -0,0 +1 @@
I am currently using rsync.net to keep my notes in sync, both git repo and the content (gpg encrypted) is stored there. Instead of creating two other repos on a server that I have which has git-annex installed where I can actually use remote daemon. Is it possible to create a repo containing both the git repo and the content encrypted from the command line?

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-27T00:31:18Z"
content="""
Why not go all the way and encrypt the git repository stored on the remote server too? [[special_remotes/gcrypt]]
When you have git-annex-shell installed on the remote server, the remote daemon should work for gcrypt repositories as well as normal non-encrypted git repositories.
"""]]

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8"
nickname="Hamza"
subject="comment 2"
date="2014-04-28T09:14:12Z"
content="""
I would love to use gcrypt and I tried it but the problem is at every sync it will ask for my pass phrase even though the key used to encrypt the repo is pass phrase less it goes through the keys in my keychain and asks me to unlock all my keys one by one.
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-24T18:08:00Z"
content="""
If you use git-annex from the OSX .dmg, it will set up a ~/.ssh/git-annex-shell, which is the only command that is needed when git-annex is using an OSX server as a remote. Since version 5.20140421, the webapp will also use ~/.ssh/git-annex-wrapper, which the .dmg also sets up, to run some commands like git.
The upshot is that this should not affect git-annex when installed from the .dmg on the OSX server. If you build git-annex from source yourself, you do need to make sure that it and git end up in PATH.
"""]]

View file

@ -0,0 +1,11 @@
[[!comment format=mdwn
username="http://mildred.fr/"
nickname="Mildred"
subject="submodules with git-annex in direct mode"
date="2014-04-27T14:05:20Z"
content="""
Does this work well even with direct mode ?
How is this managed in direct mode ?
Coming back from direct mode to indirect mode (required when I want to run git commands) I found that the .gitmodules file was an annex symlink (to .git/annex/objects/...). I just recovered from corrupt repository and may have made mistakes, but is this a risk under normal curcumstances ?
"""]]

View file

@ -0,0 +1,4 @@
Hi,
I'm wondering what the difference between the network signal and network sync icons are in the web-app? Nothing stands out to me why some repos have one some the other?

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-26T23:03:46Z"
content="""
The signal icon shows when there's a direct connection to another repositoriry. This leats your repository immediately learn when there is a change, triggering a sync. Without any signal icons, there's no fast syncing when changes are made, so the webapp will prompt for you to set up such a connection.
"""]]

View file

@ -0,0 +1,11 @@
My directory .git/annex/misctmp is quite filled up with files like P39923, P33083, and also with 7 characters P310000 up to P331998. The beginning of these filenames may come from the annexed files, which all start with 'P3'.
There is a total of 12198 of them (4.0TB... yes this repo is quite big ;)).
Each of those has the content of individual annexed files (about 300-400MB targzipped files). Sometimes they are hard liked to each other, up to 8 copies.
Since I have copied+dropped the whole repo content to other repos, there should be nothing left locally. I have verified several of those files (the annexed files which are identical to the misctmp/* files), are they indeed are located elsewhere, and not "here".
So I was wondering if it is safe to remove them, and why are they not listed by git annex unused?
Thanks for your help!!

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="http://joeyh.name/"
ip="209.250.56.114"
subject="comment 1"
date="2014-04-27T00:16:49Z"
content="""
You can delete them.
AFAIK this should only happen if the assistant is interrupted while it's adding files. I plan to make the assistant clean up old tmp files on startup.
"""]]

View file

@ -0,0 +1,10 @@
[[!comment format=mdwn
username="https://www.google.com/accounts/o8/id?id=AItOawmdbVIGiDH8KarAGAy8y2FHJD_F990JzXI"
nickname="François"
subject="comment 2"
date="2014-04-27T05:21:48Z"
content="""
Indeed I had to interrupt the add a few times.
Thanks!
"""]]

View file

@ -0,0 +1,15 @@
I'm trying to set up a ssh remote on Android using the latest 5.20140421. For some
reason the assistant fails to set up passwordless login on the remote server. It
adds the required line in `.ssh/authorized_keys` on the server side, but it still
keeps asking for the password for every connection. Nothing suspicious appears in
the assistant's log. Also, if I set up a ssh remote on a different directory on the
same server, a new key is generated and added to `authorized_keys`, but the passwordless
login still doesn't work.
I didn't file a bug since this would make for a very lousy bug report. How could I
look more into what's causing this? Where should the generated keys reside on the
Android filesystem?
I think it would be useful for the assistant to check that the generated ssh keys are
working properly, and inform the user and/or try to set them up again if there is a
problem, instead of silently falling back to asking for the login password on the console.

View file

@ -0,0 +1,14 @@
[[!comment format=mdwn
username="http://schnouki.net/"
nickname="Schnouki"
subject="comment 3"
date="2014-04-22T14:59:47Z"
content="""
Not running the assistant (freshly rebooted NAS, checked with `ps ax | grep annex`), not running any other git command. Still happened, until a few minutes ago: I found the cause for this issue... and it's quite frustrating.
Every now and then, I interrupt a running `git annex sync` with Ctrl+C. And sometimes this causes my NAS repository to end up with `bare = true` in its `.git/config`. When this happens, I just remove the offending line and call it a day. Now I just added a `bare = false` line to that file, and that solved the problem. It seems that somehow, if you don't explicitely tell git that your repo is not bare, it considers it as a bare repository -- and the final push from `git annex sync` actually updates the `master` branch without updating the work tree.
This is probably not a bug in git-annex, but rather a weird behaviour in git -- and for sure something I didn't expect to happend. But anyway it works now :) Leaving this here in case it helps other people.
Joey, thanks again for your time and your help.
"""]]

Some files were not shown because too many files have changed in this diff Show more