diff --git a/.gitignore b/.gitignore
index c7f456d233..b842cc93c1 100644
--- a/.gitignore
+++ b/.gitignore
@@ -28,3 +28,4 @@ cabal-dev
# OSX related
.DS_Store
.virthualenv
+.tasty-rerun-log
diff --git a/.mailmap b/.mailmap
new file mode 100644
index 0000000000..46423bd59b
--- /dev/null
+++ b/.mailmap
@@ -0,0 +1,6 @@
+Joey Hess http://joey.kitenet.net/
+Joey Hess http://joeyh.name/
+Joey Hess http://joeyh.name/
+Yaroslav Halchenko
+Yaroslav Halchenko http://yarikoptic.myopenid.com/
+Yaroslav Halchenko https://www.google.com/accounts/o8/id?id=AItOawnx8kHW66N3BqmkVpgtXDlYMvr8TJ5VvfY
diff --git a/Annex.hs b/Annex.hs
index 583cb0e023..87a06615e6 100644
--- a/Annex.hs
+++ b/Annex.hs
@@ -34,7 +34,6 @@ module Annex (
import "mtl" Control.Monad.Reader
import "MonadCatchIO-transformers" Control.Monad.CatchIO
-import System.Posix.Types (Fd)
import Control.Concurrent
import Common
@@ -46,6 +45,7 @@ import Git.CheckAttr
import Git.CheckIgnore
import Git.SharedRepository
import qualified Git.Queue
+import Types.Key
import Types.Backend
import Types.GitConfig
import qualified Types.Remote
@@ -56,6 +56,8 @@ import Types.Group
import Types.Messages
import Types.UUID
import Types.FileMatcher
+import Types.NumCopies
+import Types.LockPool
import qualified Utility.Matcher
import qualified Data.Map as M
import qualified Data.Set as S
@@ -75,7 +77,7 @@ newtype Annex a = Annex { runAnnex :: ReaderT (MVar AnnexState) IO a }
)
type Matcher a = Either [Utility.Matcher.Token a] (Utility.Matcher.Matcher a)
-type PreferredContentMap = M.Map UUID (Utility.Matcher.Matcher (S.Set UUID -> FileInfo -> Annex Bool))
+type PreferredContentMap = M.Map UUID (Utility.Matcher.Matcher (S.Set UUID -> MatchInfo -> Annex Bool))
-- internal state storage
data AnnexState = AnnexState
@@ -94,8 +96,9 @@ data AnnexState = AnnexState
, checkattrhandle :: Maybe CheckAttrHandle
, checkignorehandle :: Maybe (Maybe CheckIgnoreHandle)
, forcebackend :: Maybe String
- , forcenumcopies :: Maybe Int
- , limit :: Matcher (FileInfo -> Annex Bool)
+ , globalnumcopies :: Maybe NumCopies
+ , forcenumcopies :: Maybe NumCopies
+ , limit :: Matcher (MatchInfo -> Annex Bool)
, uuidmap :: Maybe UUIDMap
, preferredcontentmap :: Maybe PreferredContentMap
, shared :: Maybe SharedRepository
@@ -103,12 +106,14 @@ data AnnexState = AnnexState
, trustmap :: Maybe TrustMap
, groupmap :: Maybe GroupMap
, ciphers :: M.Map StorableCipher Cipher
- , lockpool :: M.Map FilePath Fd
+ , lockpool :: LockPool
, flags :: M.Map String Bool
, fields :: M.Map String String
, cleanup :: M.Map String (Annex ())
, inodeschanged :: Maybe Bool
, useragent :: Maybe String
+ , errcounter :: Integer
+ , unusedkeys :: Maybe (S.Set Key)
}
newState :: GitConfig -> Git.Repo -> AnnexState
@@ -128,6 +133,7 @@ newState c r = AnnexState
, checkattrhandle = Nothing
, checkignorehandle = Nothing
, forcebackend = Nothing
+ , globalnumcopies = Nothing
, forcenumcopies = Nothing
, limit = Left []
, uuidmap = Nothing
@@ -143,6 +149,8 @@ newState c r = AnnexState
, cleanup = M.empty
, inodeschanged = Nothing
, useragent = Nothing
+ , errcounter = 0
+ , unusedkeys = Nothing
}
{- Makes an Annex state object for the specified git repo.
diff --git a/Annex/Branch.hs b/Annex/Branch.hs
index 3256b65fb3..ee3cd71e28 100644
--- a/Annex/Branch.hs
+++ b/Annex/Branch.hs
@@ -18,6 +18,7 @@ module Annex.Branch (
forceUpdate,
updateTo,
get,
+ getHistorical,
change,
commit,
forceCommit,
@@ -197,7 +198,13 @@ getLocal file = go =<< getJournalFileStale file
go Nothing = getRaw file
getRaw :: FilePath -> Annex String
-getRaw file = withIndex $ L.unpack <$> catFile fullname file
+getRaw = getRef fullname
+
+getHistorical :: RefDate -> FilePath -> Annex String
+getHistorical date = getRef (Git.Ref.dateRef fullname date)
+
+getRef :: Ref -> FilePath -> Annex String
+getRef ref file = withIndex $ L.unpack <$> catFile ref file
{- Applies a function to modifiy the content of a file.
-
@@ -252,8 +259,7 @@ commitIndex' jl branchref message parents = do
committedref <- inRepo $ Git.Branch.commitAlways message fullname parents
setIndexSha committedref
parentrefs <- commitparents <$> catObject committedref
- when (racedetected branchref parentrefs) $ do
- liftIO $ print ("race detected", branchref, parentrefs, "committing", (branchref, parents))
+ when (racedetected branchref parentrefs) $
fixrace committedref parentrefs
where
-- look for "parent ref" lines and return the refs
diff --git a/Annex/Branch/Transitions.hs b/Annex/Branch/Transitions.hs
index 84cd1bbd94..95d47257a3 100644
--- a/Annex/Branch/Transitions.hs
+++ b/Annex/Branch/Transitions.hs
@@ -41,6 +41,7 @@ dropDead f content trustmap = case getLogVariety f of
in if null newlog
then RemoveFile
else ChangeFile $ Presence.showLog newlog
+ Just SingleValueLog -> PreserveFile
Nothing -> PreserveFile
dropDeadFromUUIDBasedLog :: TrustMap -> UUIDBased.Log String -> UUIDBased.Log String
diff --git a/Annex/Content.hs b/Annex/Content.hs
index 316f05be0a..6aef77830e 100644
--- a/Annex/Content.hs
+++ b/Annex/Content.hs
@@ -1,6 +1,6 @@
{- git-annex file content managing
-
- - Copyright 2010-2013 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -35,7 +35,6 @@ module Annex.Content (
) where
import System.IO.Unsafe (unsafeInterleaveIO)
-import System.PosixCompat.Files
import Common.Annex
import Logs.Location
@@ -57,6 +56,10 @@ import Annex.Content.Direct
import Annex.ReplaceFile
import Annex.Exception
+#ifdef mingw32_HOST_OS
+import Utility.WinLock
+#endif
+
{- Checks if a given key's content is currently present. -}
inAnnex :: Key -> Annex Bool
inAnnex key = inAnnexCheck key $ liftIO . doesFileExist
@@ -90,60 +93,105 @@ inAnnex' isgood bad check key = withObjectLoc key checkindirect checkdirect
{- A safer check; the key's content must not only be present, but
- is not in the process of being removed. -}
inAnnexSafe :: Key -> Annex (Maybe Bool)
-inAnnexSafe = inAnnex' (fromMaybe False) (Just False) go
+inAnnexSafe key = inAnnex' (fromMaybe False) (Just False) go key
where
- go f = liftIO $ openforlock f >>= check
+ is_locked = Nothing
+ is_unlocked = Just True
+ is_missing = Just False
+
+ go contentfile = maybe (checkindirect contentfile) (checkdirect contentfile)
+ =<< contentLockFile key
+
#ifndef mingw32_HOST_OS
+ checkindirect f = liftIO $ openforlock f >>= check is_missing
+ {- In direct mode, the content file must exist, but
+ - the lock file often generally won't exist unless a removal is in
+ - process. This does not create the lock file, it only checks for
+ - it. -}
+ checkdirect contentfile lockfile = liftIO $
+ ifM (doesFileExist contentfile)
+ ( openforlock lockfile >>= check is_unlocked
+ , return is_missing
+ )
openforlock f = catchMaybeIO $
openFd f ReadOnly Nothing defaultFileFlags
-#else
- openforlock _ = return $ Just ()
-#endif
- check Nothing = return is_missing
-#ifndef mingw32_HOST_OS
- check (Just h) = do
+ check _ (Just h) = do
v <- getLock h (ReadLock, AbsoluteSeek, 0, 0)
closeFd h
return $ case v of
Just _ -> is_locked
Nothing -> is_unlocked
+ check def Nothing = return def
#else
- check (Just _) = return is_unlocked
+ checkindirect _ = return is_missing
+ {- In Windows, see if we can take a shared lock. If so,
+ - remove the lock file to clean up after ourselves. -}
+ checkdirect contentfile lockfile =
+ ifM (liftIO $ doesFileExist contentfile)
+ ( modifyContent lockfile $ liftIO $ do
+ v <- lockShared lockfile
+ case v of
+ Nothing -> return is_locked
+ Just lockhandle -> do
+ dropLock lockhandle
+ void $ tryIO $ nukeFile lockfile
+ return is_unlocked
+ , return is_missing
+ )
#endif
-#ifndef mingw32_HOST_OS
- is_locked = Nothing
-#endif
- is_unlocked = Just True
- is_missing = Just False
+
+{- Direct mode and especially Windows has to use a separate lock
+ - file from the content, since locking the actual content file
+ - would interfere with the user's use of it. -}
+contentLockFile :: Key -> Annex (Maybe FilePath)
+contentLockFile key = ifM isDirect
+ ( Just <$> calcRepo (gitAnnexContentLock key)
+ , return Nothing
+ )
{- Content is exclusively locked while running an action that might remove
- it. (If the content is not present, no locking is done.) -}
lockContent :: Key -> Annex a -> Annex a
-#ifndef mingw32_HOST_OS
lockContent key a = do
- file <- calcRepo $ gitAnnexLocation key
- bracketIO (openforlock file >>= lock) unlock (const a)
+ contentfile <- calcRepo $ gitAnnexLocation key
+ lockfile <- contentLockFile key
+ maybe noop setuplockfile lockfile
+ bracketAnnex (liftIO $ lock contentfile lockfile) (unlock lockfile) (const a)
where
- {- Since files are stored with the write bit disabled, have
+ alreadylocked = error "content is locked"
+ setuplockfile lockfile = modifyContent lockfile $
+ void $ liftIO $ tryIO $
+ writeFile lockfile ""
+ cleanuplockfile lockfile = modifyContent lockfile $
+ void $ liftIO $ tryIO $
+ nukeFile lockfile
+#ifndef mingw32_HOST_OS
+ lock contentfile Nothing = opencontentforlock contentfile >>= dolock
+ lock _ (Just lockfile) = openforlock lockfile >>= dolock . Just
+ {- Since content files are stored with the write bit disabled, have
- to fiddle with permissions to open for an exclusive lock. -}
- openforlock f = catchMaybeIO $ ifM (doesFileExist f)
+ opencontentforlock f = catchMaybeIO $ ifM (doesFileExist f)
( withModifiedFileMode f
(`unionFileModes` ownerWriteMode)
- open
- , open
+ (openforlock f)
+ , openforlock f
)
- where
- open = openFd f ReadWrite Nothing defaultFileFlags
- lock Nothing = return Nothing
- lock (Just fd) = do
+ openforlock f = openFd f ReadWrite Nothing defaultFileFlags
+ dolock Nothing = return Nothing
+ dolock (Just fd) = do
v <- tryIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0)
case v of
- Left _ -> error "content is locked"
+ Left _ -> alreadylocked
Right _ -> return $ Just fd
- unlock Nothing = noop
- unlock (Just l) = closeFd l
+ unlock mlockfile mfd = do
+ maybe noop cleanuplockfile mlockfile
+ liftIO $ maybe noop closeFd mfd
#else
-lockContent _key a = a -- no locking for Windows!
+ lock _ (Just lockfile) = maybe alreadylocked (return . Just) =<< lockExclusive lockfile
+ lock _ Nothing = return Nothing
+ unlock mlockfile mlockhandle = do
+ liftIO $ maybe noop dropLock mlockhandle
+ maybe noop cleanuplockfile mlockfile
#endif
{- Runs an action, passing it a temporary filename to get,
@@ -377,6 +425,7 @@ removeAnnex :: Key -> Annex ()
removeAnnex key = withObjectLoc key remove removedirect
where
remove file = cleanObjectLoc key $ do
+ secureErase file
liftIO $ nukeFile file
removeInodeCache key
removedirect fs = do
@@ -385,11 +434,18 @@ removeAnnex key = withObjectLoc key remove removedirect
mapM_ (resetfile cache) fs
resetfile cache f = whenM (sameInodeCache f cache) $ do
l <- inRepo $ gitAnnexLink f key
- top <- fromRepo Git.repoPath
- cwd <- liftIO getCurrentDirectory
- let top' = fromMaybe top $ absNormPath cwd top
- let l' = relPathDirToFile top' (fromMaybe l $ absNormPath top' l)
- replaceFile f $ makeAnnexLink l'
+ secureErase f
+ replaceFile f $ makeAnnexLink l
+
+{- Runs the secure erase command if set, otherwise does nothing.
+ - File may or may not be deleted at the end; caller is responsible for
+ - making sure it's deleted. -}
+secureErase :: FilePath -> Annex ()
+secureErase file = maybe noop go =<< annexSecureEraseCommand <$> Annex.getGitConfig
+ where
+ go basecmd = void $ liftIO $
+ boolSystem "sh" [Param "-c", Param $ gencmd basecmd]
+ gencmd = massReplace [ ("%file", shellEscape file) ]
{- Moves a key's file out of .git/annex/objects/ -}
fromAnnex :: Key -> FilePath -> Annex ()
diff --git a/Annex/Content/Direct.hs b/Annex/Content/Direct.hs
index a5d71288b2..b60ab9b1b3 100644
--- a/Annex/Content/Direct.hs
+++ b/Annex/Content/Direct.hs
@@ -52,10 +52,12 @@ associatedFiles key = do
associatedFilesRelative :: Key -> Annex [FilePath]
associatedFilesRelative key = do
mapping <- calcRepo $ gitAnnexMapping key
- liftIO $ catchDefaultIO [] $ do
- h <- openFile mapping ReadMode
+ liftIO $ catchDefaultIO [] $ withFile mapping ReadMode $ \h -> do
fileEncoding h
- lines <$> hGetContents h
+ -- Read strictly to ensure the file is closed
+ -- before changeAssociatedFiles tries to write to it.
+ -- (Especially needed on Windows.)
+ lines <$> hGetContentsStrict h
{- Changes the associated files information for a key, applying a
- transformation to the list. Returns new associatedFiles value. -}
@@ -66,15 +68,10 @@ changeAssociatedFiles key transform = do
let files' = transform files
when (files /= files') $ do
modifyContent mapping $
- liftIO $ viaTmp write mapping $ unlines files'
+ liftIO $ viaTmp writeFileAnyEncoding mapping $
+ unlines files'
top <- fromRepo Git.repoPath
return $ map (top >) files'
- where
- write file content = do
- h <- openFile file WriteMode
- fileEncoding h
- hPutStr h content
- hClose h
{- Removes the list of associated files. -}
removeAssociatedFiles :: Key -> Annex ()
diff --git a/Annex/Drop.hs b/Annex/Drop.hs
new file mode 100644
index 0000000000..71263dc618
--- /dev/null
+++ b/Annex/Drop.hs
@@ -0,0 +1,124 @@
+{- dropping of unwanted content
+ -
+ - Copyright 2012-2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Annex.Drop where
+
+import Common.Annex
+import Logs.Trust
+import Config.NumCopies
+import Types.Remote (uuid)
+import Types.Key (key2file)
+import qualified Remote
+import qualified Command.Drop
+import Command
+import Annex.Wanted
+import Annex.Exception
+import Config
+import Annex.Content.Direct
+
+import qualified Data.Set as S
+import System.Log.Logger (debugM)
+
+type Reason = String
+
+{- Drop a key from local and/or remote when allowed by the preferred content
+ - and numcopies settings.
+ -
+ - The UUIDs are ones where the content is believed to be present.
+ - The Remote list can include other remotes that do not have the content;
+ - only ones that match the UUIDs will be dropped from.
+ - If allowed to drop fromhere, that drop will be tried first.
+ -
+ - A remote can be specified that is known to have the key. This can be
+ - used an an optimisation when eg, a key has just been uploaded to a
+ - remote.
+ -
+ - In direct mode, all associated files are checked, and only if all
+ - of them are unwanted are they dropped.
+ -
+ - The runner is used to run commands, and so can be either callCommand
+ - or commandAction.
+ -}
+handleDropsFrom :: [UUID] -> [Remote] -> Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> CommandActionRunner -> Annex ()
+handleDropsFrom locs rs reason fromhere key afile knownpresentremote runner = do
+ fs <- ifM isDirect
+ ( do
+ l <- associatedFilesRelative key
+ return $ if null l
+ then maybeToList afile
+ else l
+ , return $ maybeToList afile
+ )
+ n <- getcopies fs
+ if fromhere && checkcopies n Nothing
+ then go fs rs =<< dropl fs n
+ else go fs rs n
+ where
+ getcopies fs = do
+ (untrusted, have) <- trustPartition UnTrusted locs
+ numcopies <- if null fs
+ then getNumCopies
+ else maximum <$> mapM getFileNumCopies fs
+ return (NumCopies (length have), numcopies, S.fromList untrusted)
+
+ {- Check that we have enough copies still to drop the content.
+ - When the remote being dropped from is untrusted, it was not
+ - counted as a copy, so having only numcopies suffices. Otherwise,
+ - we need more than numcopies to safely drop. -}
+ checkcopies (have, numcopies, _untrusted) Nothing = have > numcopies
+ checkcopies (have, numcopies, untrusted) (Just u)
+ | S.member u untrusted = have >= numcopies
+ | otherwise = have > numcopies
+
+ decrcopies (have, numcopies, untrusted) Nothing =
+ (NumCopies (fromNumCopies have - 1), numcopies, untrusted)
+ decrcopies v@(_have, _numcopies, untrusted) (Just u)
+ | S.member u untrusted = v
+ | otherwise = decrcopies v Nothing
+
+ go _ [] _ = noop
+ go fs (r:rest) n
+ | uuid r `S.notMember` slocs = go fs rest n
+ | checkcopies n (Just $ Remote.uuid r) =
+ dropr fs r n >>= go fs rest
+ | otherwise = noop
+
+ checkdrop fs n u a
+ | null fs = check $ -- no associated files; unused content
+ wantDrop True u (Just key) Nothing
+ | otherwise = check $
+ allM (wantDrop True u (Just key) . Just) fs
+ where
+ check c = ifM c
+ ( dodrop n u a
+ , return n
+ )
+
+ dodrop n@(have, numcopies, _untrusted) u a =
+ ifM (safely $ runner $ a numcopies)
+ ( do
+ liftIO $ debugM "drop" $ unwords
+ [ "dropped"
+ , fromMaybe (key2file key) afile
+ , "(from " ++ maybe "here" show u ++ ")"
+ , "(copies now " ++ show (fromNumCopies have - 1) ++ ")"
+ , ": " ++ reason
+ ]
+ return $ decrcopies n u
+ , return n
+ )
+
+ dropl fs n = checkdrop fs n Nothing $ \numcopies ->
+ Command.Drop.startLocal afile numcopies key knownpresentremote
+
+ dropr fs r n = checkdrop fs n (Just $ Remote.uuid r) $ \numcopies ->
+ Command.Drop.startRemote afile numcopies key r
+
+ slocs = S.fromList locs
+
+ safely a = either (const False) id <$> tryAnnex a
+
diff --git a/Annex/Exception.hs b/Annex/Exception.hs
index 91347583e4..11613d51b7 100644
--- a/Annex/Exception.hs
+++ b/Annex/Exception.hs
@@ -14,6 +14,7 @@
module Annex.Exception (
bracketIO,
+ bracketAnnex,
tryAnnex,
tryAnnexIO,
throwAnnex,
@@ -29,6 +30,9 @@ import Common.Annex
bracketIO :: IO v -> (v -> IO b) -> (v -> Annex a) -> Annex a
bracketIO setup cleanup = M.bracket (liftIO setup) (liftIO . cleanup)
+bracketAnnex :: Annex v -> (v -> Annex b) -> (v -> Annex a) -> Annex a
+bracketAnnex = M.bracket
+
{- try in the Annex monad -}
tryAnnex :: Annex a -> Annex (Either SomeException a)
tryAnnex = M.try
diff --git a/Annex/FileMatcher.hs b/Annex/FileMatcher.hs
index cded857a23..158f3e787b 100644
--- a/Annex/FileMatcher.hs
+++ b/Annex/FileMatcher.hs
@@ -1,6 +1,6 @@
{- git-annex file matching
-
- - Copyright 2012, 2013 Joey Hess
+ - Copyright 2012-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -28,18 +28,25 @@ import qualified Data.Set as S
type FileMatcher = Matcher MatchFiles
checkFileMatcher :: FileMatcher -> FilePath -> Annex Bool
-checkFileMatcher matcher file = checkFileMatcher' matcher file S.empty True
+checkFileMatcher matcher file = checkMatcher matcher Nothing (Just file) S.empty True
-checkFileMatcher' :: FileMatcher -> FilePath -> AssumeNotPresent -> Bool -> Annex Bool
-checkFileMatcher' matcher file notpresent def
+checkMatcher :: FileMatcher -> Maybe Key -> AssociatedFile -> AssumeNotPresent -> Bool -> Annex Bool
+checkMatcher matcher mkey afile notpresent def
| isEmpty matcher = return def
- | otherwise = do
- matchfile <- getTopFilePath <$> inRepo (toTopFilePath file)
- let fi = FileInfo
- { matchFile = matchfile
- , relFile = file
- }
- matchMrun matcher $ \a -> a notpresent fi
+ | otherwise = case (mkey, afile) of
+ (_, Just file) -> go =<< fileMatchInfo file
+ (Just key, _) -> go (MatchingKey key)
+ _ -> return def
+ where
+ go mi = matchMrun matcher $ \a -> a notpresent mi
+
+fileMatchInfo :: FilePath -> Annex MatchInfo
+fileMatchInfo file = do
+ matchfile <- getTopFilePath <$> inRepo (toTopFilePath file)
+ return $ MatchingFile $ FileInfo
+ { matchFile = matchfile
+ , relFile = file
+ }
matchAll :: FileMatcher
matchAll = generate []
@@ -65,11 +72,14 @@ parseToken checkpresent checkpreferreddir groupmap t
| t `elem` tokens = Right $ token t
| t == "present" = use checkpresent
| t == "inpreferreddir" = use checkpreferreddir
+ | t == "unused" = Right (Operation limitUnused)
| otherwise = maybe (Left $ "near " ++ show t) use $ M.lookup k $
M.fromList
[ ("include", limitInclude)
, ("exclude", limitExclude)
, ("copies", limitCopies)
+ , ("lackingcopies", limitLackingCopies False)
+ , ("approxlackingcopies", limitLackingCopies True)
, ("inbackend", limitInBackend)
, ("largerthan", limitSize (>))
, ("smallerthan", limitSize (<))
diff --git a/Init.hs b/Annex/Init.hs
similarity index 99%
rename from Init.hs
rename to Annex/Init.hs
index 56bccfa0c1..616bda69b5 100644
--- a/Init.hs
+++ b/Annex/Init.hs
@@ -7,7 +7,7 @@
{-# LANGUAGE CPP #-}
-module Init (
+module Annex.Init (
ensureInitialized,
isInitialized,
initialize,
diff --git a/Annex/Journal.hs b/Annex/Journal.hs
index 8b88ab2fbf..3f31cb941a 100644
--- a/Annex/Journal.hs
+++ b/Annex/Journal.hs
@@ -20,6 +20,10 @@ import Annex.Exception
import qualified Git
import Annex.Perms
+#ifdef mingw32_HOST_OS
+import Utility.WinLock
+#endif
+
{- Records content for a file in the branch to the journal.
-
- Using the journal, rather than immediatly staging content to the index
@@ -116,13 +120,8 @@ lockJournal a = do
l <- noUmask mode $ createFile lockfile mode
waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
return l
-#else
- lock lockfile _mode = do
- writeFile lockfile ""
- return lockfile
-#endif
-#ifndef mingw32_HOST_OS
unlock = closeFd
#else
- unlock = removeFile
+ lock lockfile _mode = waitToLock $ lockExclusive lockfile
+ unlock = dropLock
#endif
diff --git a/Annex/Link.hs b/Annex/Link.hs
index 30d8c2ae8c..234e4cb2a8 100644
--- a/Annex/Link.hs
+++ b/Annex/Link.hs
@@ -51,19 +51,15 @@ getAnnexLinkTarget file = ifM (coreSymlinks <$> Annex.getGitConfig)
| otherwise -> return Nothing
Nothing -> fallback
- probefilecontent f = do
- h <- openFile f ReadMode
+ probefilecontent f = withFile f ReadMode $ \h -> do
fileEncoding h
-- The first 8k is more than enough to read; link
-- files are small.
s <- take 8192 <$> hGetContents h
-- If we got the full 8k, the file is too large
if length s == 8192
- then do
- hClose h
- return ""
- else do
- hClose h
+ then return ""
+ else
-- If there are any NUL or newline
-- characters, or whitespace, we
-- certianly don't have a link to a
diff --git a/Annex/LockPool.hs b/Annex/LockPool.hs
index a9a0f31019..5fc167d287 100644
--- a/Annex/LockPool.hs
+++ b/Annex/LockPool.hs
@@ -1,6 +1,6 @@
{- git-annex lock pool
-
- - Copyright 2012 Joey Hess
+ - Copyright 2012, 2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -9,13 +9,16 @@
module Annex.LockPool where
-import qualified Data.Map as M
-import System.Posix.Types (Fd)
-
import Common.Annex
import Annex
+import Types.LockPool
+
+import qualified Data.Map as M
+
#ifndef mingw32_HOST_OS
import Annex.Perms
+#else
+import Utility.WinLock
#endif
{- Create a specified lock file, and takes a shared lock. -}
@@ -26,31 +29,32 @@ lockFile file = go =<< fromPool file
go Nothing = do
#ifndef mingw32_HOST_OS
mode <- annexFileMode
- fd <- liftIO $ noUmask mode $
+ lockhandle <- liftIO $ noUmask mode $
openFd file ReadOnly (Just mode) defaultFileFlags
- liftIO $ waitToSetLock fd (ReadLock, AbsoluteSeek, 0, 0)
+ liftIO $ waitToSetLock lockhandle (ReadLock, AbsoluteSeek, 0, 0)
#else
- liftIO $ writeFile file ""
- let fd = 0
+ lockhandle <- liftIO $ waitToLock $ lockShared file
#endif
- changePool $ M.insert file fd
+ changePool $ M.insert file lockhandle
unlockFile :: FilePath -> Annex ()
unlockFile file = maybe noop go =<< fromPool file
where
- go fd = do
+ go lockhandle = do
#ifndef mingw32_HOST_OS
- liftIO $ closeFd fd
+ liftIO $ closeFd lockhandle
+#else
+ liftIO $ dropLock lockhandle
#endif
changePool $ M.delete file
-getPool :: Annex (M.Map FilePath Fd)
+getPool :: Annex LockPool
getPool = getState lockpool
-fromPool :: FilePath -> Annex (Maybe Fd)
+fromPool :: FilePath -> Annex (Maybe LockHandle)
fromPool file = M.lookup file <$> getPool
-changePool :: (M.Map FilePath Fd -> M.Map FilePath Fd) -> Annex ()
+changePool :: (LockPool -> LockPool) -> Annex ()
changePool a = do
m <- getPool
changeState $ \s -> s { lockpool = a m }
diff --git a/Annex/Wanted.hs b/Annex/Wanted.hs
index 04dcc1c1ca..42f813bbbc 100644
--- a/Annex/Wanted.hs
+++ b/Annex/Wanted.hs
@@ -14,19 +14,16 @@ import Annex.UUID
import qualified Data.Set as S
{- Check if a file is preferred content for the local repository. -}
-wantGet :: Bool -> AssociatedFile -> Annex Bool
-wantGet def Nothing = return def
-wantGet def (Just file) = isPreferredContent Nothing S.empty file def
+wantGet :: Bool -> Maybe Key -> AssociatedFile -> Annex Bool
+wantGet def key file = isPreferredContent Nothing S.empty key file def
{- Check if a file is preferred content for a remote. -}
-wantSend :: Bool -> AssociatedFile -> UUID -> Annex Bool
-wantSend def Nothing _ = return def
-wantSend def (Just file) to = isPreferredContent (Just to) S.empty file def
+wantSend :: Bool -> Maybe Key -> AssociatedFile -> UUID -> Annex Bool
+wantSend def key file to = isPreferredContent (Just to) S.empty key file def
{- Check if a file can be dropped, maybe from a remote.
- Don't drop files that are preferred content. -}
-wantDrop :: Bool -> Maybe UUID -> AssociatedFile -> Annex Bool
-wantDrop def _ Nothing = return $ not def
-wantDrop def from (Just file) = do
+wantDrop :: Bool -> Maybe UUID -> Maybe Key -> AssociatedFile -> Annex Bool
+wantDrop def from key file = do
u <- maybe getUUID (return . id) from
- not <$> isPreferredContent (Just u) (S.singleton u) file def
+ not <$> isPreferredContent (Just u) (S.singleton u) key file def
diff --git a/Assistant.hs b/Assistant.hs
index d4786f99ad..800a3ef786 100644
--- a/Assistant.hs
+++ b/Assistant.hs
@@ -145,7 +145,7 @@ startDaemon assistant foreground startdelay cannotrun listenhost startbrowser =
, assist $ transferPollerThread
, assist $ transfererThread
, assist $ daemonStatusThread
- , assist $ sanityCheckerDailyThread
+ , assist $ sanityCheckerDailyThread urlrenderer
, assist $ sanityCheckerHourlyThread
, assist $ problemFixerThread urlrenderer
#ifdef WITH_CLIBS
diff --git a/Assistant/Alert.hs b/Assistant/Alert.hs
index 055e66de50..192952f56b 100644
--- a/Assistant/Alert.hs
+++ b/Assistant/Alert.hs
@@ -1,6 +1,6 @@
{- git-annex assistant alerts
-
- - Copyright 2012, 2013 Joey Hess
+ - Copyright 2012-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -253,13 +253,32 @@ upgradingAlert = activityAlert Nothing [ fromString "Upgrading git-annex" ]
upgradeFinishedAlert :: Maybe AlertButton -> GitAnnexVersion -> Alert
upgradeFinishedAlert button version =
- baseUpgradeAlert (maybe [] (:[]) button) $ fromString $
+ baseUpgradeAlert (maybeToList button) $ fromString $
"Finished upgrading git-annex to version " ++ version
upgradeFailedAlert :: String -> Alert
upgradeFailedAlert msg = (errorAlert msg [])
{ alertHeader = Just $ fromString "Upgrade failed." }
+unusedFilesAlert :: [AlertButton] -> String -> Alert
+unusedFilesAlert buttons message = Alert
+ { alertHeader = Just $ fromString $ unwords
+ [ "Old and deleted files are piling up --"
+ , message
+ ]
+ , alertIcon = Just InfoIcon
+ , alertPriority = High
+ , alertButtons = buttons
+ , alertClosable = True
+ , alertClass = Message
+ , alertMessageRender = renderData
+ , alertCounter = 0
+ , alertBlockDisplay = True
+ , alertName = Just UnusedFilesAlert
+ , alertCombiner = Just $ fullCombiner $ \new _old -> new
+ , alertData = []
+ }
+
brokenRepositoryAlert :: [AlertButton] -> Alert
brokenRepositoryAlert = errorAlert "Serious problems have been detected with your repository. This needs your immediate attention!"
@@ -298,7 +317,7 @@ pairRequestAcknowledgedAlert who button = baseActivityAlert
, alertPriority = High
, alertName = Just $ PairAlert who
, alertCombiner = Just $ dataCombiner $ \_old new -> new
- , alertButtons = maybe [] (:[]) button
+ , alertButtons = maybeToList button
}
xmppNeededAlert :: AlertButton -> Alert
diff --git a/Assistant/DaemonStatus.hs b/Assistant/DaemonStatus.hs
index ef1e065949..eb842b7847 100644
--- a/Assistant/DaemonStatus.hs
+++ b/Assistant/DaemonStatus.hs
@@ -55,11 +55,11 @@ calcSyncRemotes = do
let good r = Remote.uuid r `elem` alive
let syncable = filter good rs
let syncdata = filter (not . remoteAnnexIgnore . Remote.gitconfig) $
- filter (not . isXMPPRemote) syncable
+ filter (not . Remote.isXMPPRemote) syncable
return $ \dstatus -> dstatus
{ syncRemotes = syncable
- , syncGitRemotes = filter Remote.syncableRemote syncable
+ , syncGitRemotes = filter Remote.gitSyncableRemote syncable
, syncDataRemotes = syncdata
, syncingToCloudRemote = any iscloud syncdata
}
@@ -257,11 +257,5 @@ alertDuring alert a = do
i <- addAlert $ alert { alertClass = Activity }
removeAlert i `after` a
-{- Remotes using the XMPP transport have urls like xmpp::user@host -}
-isXMPPRemote :: Remote -> Bool
-isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
- where
- r = Remote.repo remote
-
getXMPPClientID :: Remote -> ClientID
getXMPPClientID r = T.pack $ drop (length "xmpp::") (Git.repoLocation (Remote.repo r))
diff --git a/Assistant/Drop.hs b/Assistant/Drop.hs
index d9d8123972..efd74fdb3e 100644
--- a/Assistant/Drop.hs
+++ b/Assistant/Drop.hs
@@ -5,108 +5,21 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Assistant.Drop where
+module Assistant.Drop (
+ handleDrops,
+ handleDropsFrom,
+) where
import Assistant.Common
import Assistant.DaemonStatus
+import Annex.Drop (handleDropsFrom, Reason)
import Logs.Location
-import Logs.Trust
-import Types.Remote (uuid)
-import qualified Remote
-import qualified Command.Drop
-import Command
-import Annex.Wanted
-import Annex.Exception
-import Config
-import Annex.Content.Direct
-
-import qualified Data.Set as S
-
-type Reason = String
+import CmdLine.Action
{- Drop from local and/or remote when allowed by the preferred content and
- numcopies settings. -}
handleDrops :: Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
-handleDrops _ _ _ Nothing _ = noop
handleDrops reason fromhere key f knownpresentremote = do
syncrs <- syncDataRemotes <$> getDaemonStatus
locs <- liftAnnex $ loggedLocations key
- handleDropsFrom locs syncrs reason fromhere key f knownpresentremote
-
-{- The UUIDs are ones where the content is believed to be present.
- - The Remote list can include other remotes that do not have the content;
- - only ones that match the UUIDs will be dropped from.
- - If allowed to drop fromhere, that drop will be tried first.
- -
- - In direct mode, all associated files are checked, and only if all
- - of them are unwanted are they dropped.
- -}
-handleDropsFrom :: [UUID] -> [Remote] -> Reason -> Bool -> Key -> AssociatedFile -> Maybe Remote -> Assistant ()
-handleDropsFrom _ _ _ _ _ Nothing _ = noop
-handleDropsFrom locs rs reason fromhere key (Just afile) knownpresentremote = do
- fs <- liftAnnex $ ifM isDirect
- ( do
- l <- associatedFilesRelative key
- if null l
- then return [afile]
- else return l
- , return [afile]
- )
- n <- getcopies fs
- if fromhere && checkcopies n Nothing
- then go fs rs =<< dropl fs n
- else go fs rs n
- where
- getcopies fs = liftAnnex $ do
- (untrusted, have) <- trustPartition UnTrusted locs
- numcopies <- maximum <$> mapM (getNumCopies <=< numCopies) fs
- return (length have, numcopies, S.fromList untrusted)
-
- {- Check that we have enough copies still to drop the content.
- - When the remote being dropped from is untrusted, it was not
- - counted as a copy, so having only numcopies suffices. Otherwise,
- - we need more than numcopies to safely drop. -}
- checkcopies (have, numcopies, _untrusted) Nothing = have > numcopies
- checkcopies (have, numcopies, untrusted) (Just u)
- | S.member u untrusted = have >= numcopies
- | otherwise = have > numcopies
-
- decrcopies (have, numcopies, untrusted) Nothing =
- (have - 1, numcopies, untrusted)
- decrcopies v@(_have, _numcopies, untrusted) (Just u)
- | S.member u untrusted = v
- | otherwise = decrcopies v Nothing
-
- go _ [] _ = noop
- go fs (r:rest) n
- | uuid r `S.notMember` slocs = go fs rest n
- | checkcopies n (Just $ Remote.uuid r) =
- dropr fs r n >>= go fs rest
- | otherwise = noop
-
- checkdrop fs n@(have, numcopies, _untrusted) u a =
- ifM (liftAnnex $ allM (wantDrop True u . Just) fs)
- ( ifM (liftAnnex $ safely $ doCommand $ a (Just numcopies))
- ( do
- debug
- [ "dropped"
- , afile
- , "(from " ++ maybe "here" show u ++ ")"
- , "(copies now " ++ show (have - 1) ++ ")"
- , ": " ++ reason
- ]
- return $ decrcopies n u
- , return n
- )
- , return n
- )
-
- dropl fs n = checkdrop fs n Nothing $ \numcopies ->
- Command.Drop.startLocal (Just afile) numcopies key knownpresentremote
-
- dropr fs r n = checkdrop fs n (Just $ Remote.uuid r) $ \numcopies ->
- Command.Drop.startRemote (Just afile) numcopies key r
-
- safely a = either (const False) id <$> tryAnnex a
-
- slocs = S.fromList locs
+ liftAnnex $ handleDropsFrom locs syncrs reason fromhere key f knownpresentremote callCommandAction
diff --git a/Assistant/Sync.hs b/Assistant/Sync.hs
index adbe413508..fc95419ab8 100644
--- a/Assistant/Sync.hs
+++ b/Assistant/Sync.hs
@@ -71,7 +71,7 @@ reconnectRemotes notifypushes rs = void $ do
mapM_ signal $ filter (`notElem` failedrs) rs'
where
gitremotes = filter (notspecialremote . Remote.repo) rs
- (xmppremotes, nonxmppremotes) = partition isXMPPRemote rs
+ (xmppremotes, nonxmppremotes) = partition Remote.isXMPPRemote rs
notspecialremote r
| Git.repoIsUrl r = True
| Git.repoIsLocal r = True
@@ -133,7 +133,7 @@ pushToRemotes' now notifypushes remotes = do
<$> gitRepo
<*> inRepo Git.Branch.current
<*> getUUID
- let (xmppremotes, normalremotes) = partition isXMPPRemote remotes
+ let (xmppremotes, normalremotes) = partition Remote.isXMPPRemote remotes
ret <- go True branch g u normalremotes
unless (null xmppremotes) $ do
shas <- liftAnnex $ map fst <$>
@@ -206,7 +206,7 @@ syncAction rs a
return failed
where
visibleremotes = filter (not . Remote.readonly) $
- filter (not . isXMPPRemote) rs
+ filter (not . Remote.isXMPPRemote) rs
{- Manually pull from remotes and merge their branches. Returns any
- remotes that it failed to pull from, and a Bool indicating
@@ -220,7 +220,7 @@ syncAction rs a
manualPull :: Maybe Git.Ref -> [Remote] -> Assistant ([Remote], Bool)
manualPull currentbranch remotes = do
g <- liftAnnex gitRepo
- let (xmppremotes, normalremotes) = partition isXMPPRemote remotes
+ let (xmppremotes, normalremotes) = partition Remote.isXMPPRemote remotes
failed <- liftIO $ forM normalremotes $ \r ->
ifM (Git.Command.runBool [Param "fetch", Param $ Remote.name r] g)
( return Nothing
diff --git a/Assistant/Threads/Committer.hs b/Assistant/Threads/Committer.hs
index 2ddaade2fc..e8d17b13f9 100644
--- a/Assistant/Threads/Committer.hs
+++ b/Assistant/Threads/Committer.hs
@@ -464,7 +464,7 @@ checkChangeContent change@(Change { changeInfo = i }) =
Nothing -> noop
Just k -> whenM (scanComplete <$> getDaemonStatus) $ do
present <- liftAnnex $ inAnnex k
- if present
+ void $ if present
then queueTransfers "new file created" Next k (Just f) Upload
else queueTransfers "new or renamed file wanted" Next k (Just f) Download
handleDrops "file renamed" present k (Just f) Nothing
diff --git a/Assistant/Threads/ConfigMonitor.hs b/Assistant/Threads/ConfigMonitor.hs
index c180c4da92..a92c7d7859 100644
--- a/Assistant/Threads/ConfigMonitor.hs
+++ b/Assistant/Threads/ConfigMonitor.hs
@@ -17,6 +17,7 @@ import Logs.UUID
import Logs.Trust
import Logs.PreferredContent
import Logs.Group
+import Logs.NumCopies
import Remote.List (remoteListRefresh)
import qualified Git.LsTree as LsTree
import Git.FilePath
@@ -59,6 +60,7 @@ configFilesActions =
, (remoteLog, void $ liftAnnex remoteListRefresh)
, (trustLog, void $ liftAnnex trustMapLoad)
, (groupLog, void $ liftAnnex groupMapLoad)
+ , (numcopiesLog, void $ liftAnnex globalNumCopiesLoad)
, (scheduleLog, void updateScheduleLog)
-- Preferred content settings depend on most of the other configs,
-- so will be reloaded whenever any configs change.
diff --git a/Assistant/Threads/SanityChecker.hs b/Assistant/Threads/SanityChecker.hs
index 8aa691cdc9..925fdbce6d 100644
--- a/Assistant/Threads/SanityChecker.hs
+++ b/Assistant/Threads/SanityChecker.hs
@@ -5,6 +5,8 @@
- Licensed under the GNU GPL version 3 or higher.
-}
+{-# LANGUAGE CPP #-}
+
module Assistant.Threads.SanityChecker (
sanityCheckerStartupThread,
sanityCheckerDailyThread,
@@ -15,7 +17,10 @@ import Assistant.Common
import Assistant.DaemonStatus
import Assistant.Alert
import Assistant.Repair
+import Assistant.Drop
import Assistant.Ssh
+import Assistant.TransferQueue
+import Assistant.Types.UrlRenderer
import qualified Annex.Branch
import qualified Git.LsFiles
import qualified Git.Command
@@ -27,10 +32,20 @@ import Utility.Batch
import Utility.NotificationBroadcaster
import Config
import Utility.HumanTime
+import Utility.Tense
import Git.Repair
import Git.Index
+import Assistant.Unused
+import Logs.Unused
+import Logs.Transfer
+import Config.Files
+import qualified Annex
+#ifdef WITH_WEBAPP
+import Assistant.WebApp.Types
+#endif
import Data.Time.Clock.POSIX
+import qualified Data.Text as T
{- This thread runs once at startup, and most other threads wait for it
- to finish. (However, the webapp thread does not, to prevent the UI
@@ -78,8 +93,8 @@ sanityCheckerHourlyThread = namedThread "SanityCheckerHourly" $ forever $ do
hourlyCheck
{- This thread wakes up daily to make sure the tree is in good shape. -}
-sanityCheckerDailyThread :: NamedThread
-sanityCheckerDailyThread = namedThread "SanityCheckerDaily" $ forever $ do
+sanityCheckerDailyThread :: UrlRenderer -> NamedThread
+sanityCheckerDailyThread urlrenderer = namedThread "SanityCheckerDaily" $ forever $ do
waitForNextCheck
debug ["starting sanity check"]
@@ -90,7 +105,8 @@ sanityCheckerDailyThread = namedThread "SanityCheckerDaily" $ forever $ do
modifyDaemonStatus_ $ \s -> s { sanityCheckRunning = True }
now <- liftIO getPOSIXTime -- before check started
- r <- either showerr return =<< (tryIO . batch) <~> dailyCheck
+ r <- either showerr return
+ =<< (tryIO . batch) <~> dailyCheck urlrenderer
modifyDaemonStatus_ $ \s -> s
{ sanityCheckRunning = False
@@ -119,9 +135,10 @@ waitForNextCheck = do
{- It's important to stay out of the Annex monad as much as possible while
- running potentially expensive parts of this check, since remaining in it
- will block the watcher. -}
-dailyCheck :: Assistant Bool
-dailyCheck = do
+dailyCheck :: UrlRenderer -> Assistant Bool
+dailyCheck urlrenderer = do
g <- liftAnnex gitRepo
+ batchmaker <- liftIO getBatchCommandMaker
-- Find old unstaged symlinks, and add them to git.
(unstaged, cleanup) <- liftIO $ Git.LsFiles.notInRepo False ["."] g
@@ -140,12 +157,29 @@ dailyCheck = do
- to have a lot of small objects and they should not be a
- significant size. -}
when (Git.Config.getMaybe "gc.auto" g == Just "0") $
- liftIO $ void $ Git.Command.runBool
+ liftIO $ void $ Git.Command.runBatch batchmaker
[ Param "-c", Param "gc.auto=670000"
, Param "gc"
, Param "--auto"
] g
+ {- Check if the unused files found last time have been dealt with. -}
+ checkOldUnused urlrenderer
+
+ {- Run git-annex unused once per day. This is run as a separate
+ - process to stay out of the annex monad and so it can run as a
+ - batch job. -}
+ program <- liftIO readProgramFile
+ let (program', params') = batchmaker (program, [Param "unused"])
+ void $ liftIO $ boolSystem program' params'
+ {- Invalidate unused keys cache, and queue transfers of all unused
+ - keys, or if no transfers are called for, drop them. -}
+ unused <- liftAnnex unusedKeys'
+ void $ liftAnnex $ setUnusedKeys unused
+ forM_ unused $ \k -> do
+ unlessM (queueTransfers "unused" Later k Nothing Upload) $
+ handleDrops "unused" True k Nothing Nothing
+
return True
where
toonew timestamp now = now < (realToFrac (timestamp + slop) :: POSIXTime)
@@ -159,7 +193,8 @@ dailyCheck = do
insanity $ "found unstaged symlink: " ++ file
hourlyCheck :: Assistant ()
-hourlyCheck = checkLogSize 0
+hourlyCheck = do
+ checkLogSize 0
{- Rotate logs until log file size is < 1 mb. -}
checkLogSize :: Int -> Assistant ()
@@ -184,3 +219,23 @@ oneHour = 60 * 60
oneDay :: Int
oneDay = 24 * oneHour
+{- If annex.expireunused is set, find any keys that have lingered unused
+ - for the specified duration, and remove them.
+ -
+ - Otherwise, check to see if unused keys are piling up, and let the user
+ - know. -}
+checkOldUnused :: UrlRenderer -> Assistant ()
+checkOldUnused urlrenderer = go =<< annexExpireUnused <$> liftAnnex Annex.getGitConfig
+ where
+ go (Just Nothing) = noop
+ go (Just (Just expireunused)) = expireUnused (Just expireunused)
+ go Nothing = maybe noop prompt =<< describeUnusedWhenBig
+
+ prompt msg =
+#ifdef WITH_WEBAPP
+ do
+ button <- mkAlertButton True (T.pack "Configure") urlrenderer ConfigUnusedR
+ void $ addAlert $ unusedFilesAlert [button] $ T.unpack $ renderTense Present msg
+#else
+ debug [show $ renderTense Past msg]
+#endif
diff --git a/Assistant/Threads/TransferScanner.hs b/Assistant/Threads/TransferScanner.hs
index ba302d6bb9..6df9b1e183 100644
--- a/Assistant/Threads/TransferScanner.hs
+++ b/Assistant/Threads/TransferScanner.hs
@@ -29,6 +29,7 @@ import qualified Git.LsFiles as LsFiles
import qualified Backend
import Annex.Content
import Annex.Wanted
+import CmdLine.Action
import qualified Data.Set as S
@@ -156,16 +157,16 @@ expensiveScan urlrenderer rs = unless onlyweb $ batch <~> do
syncrs <- syncDataRemotes <$> getDaemonStatus
locs <- liftAnnex $ loggedLocations key
present <- liftAnnex $ inAnnex key
- handleDropsFrom locs syncrs
+ liftAnnex $ handleDropsFrom locs syncrs
"expensive scan found too many copies of object"
- present key (Just f) Nothing
+ present key (Just f) Nothing callCommandAction
liftAnnex $ do
let slocs = S.fromList locs
let use a = return $ mapMaybe (a key slocs) syncrs
ts <- if present
- then filterM (wantSend True (Just f) . Remote.uuid . fst)
+ then filterM (wantSend True (Just key) (Just f) . Remote.uuid . fst)
=<< use (genTransfer Upload False)
- else ifM (wantGet True $ Just f)
+ else ifM (wantGet True (Just key) (Just f))
( use (genTransfer Download True) , return [] )
let unwanted' = S.difference unwanted slocs
return (unwanted', ts)
diff --git a/Assistant/Threads/WebApp.hs b/Assistant/Threads/WebApp.hs
index a7f9cc5b2a..d2c2afd475 100644
--- a/Assistant/Threads/WebApp.hs
+++ b/Assistant/Threads/WebApp.hs
@@ -27,6 +27,7 @@ import Assistant.WebApp.Configurators.IA
import Assistant.WebApp.Configurators.WebDAV
import Assistant.WebApp.Configurators.XMPP
import Assistant.WebApp.Configurators.Preferences
+import Assistant.WebApp.Configurators.Unused
import Assistant.WebApp.Configurators.Edit
import Assistant.WebApp.Configurators.Delete
import Assistant.WebApp.Configurators.Fsck
diff --git a/Assistant/Threads/XMPPClient.hs b/Assistant/Threads/XMPPClient.hs
index 8eb4699390..ab4de9257f 100644
--- a/Assistant/Threads/XMPPClient.hs
+++ b/Assistant/Threads/XMPPClient.hs
@@ -322,7 +322,7 @@ pairMsgReceived urlrenderer PairReq theiruuid selfjid theirjid
| baseJID selfjid == baseJID theirjid = autoaccept
| otherwise = do
knownjids <- mapMaybe (parseJID . getXMPPClientID)
- . filter isXMPPRemote . syncRemotes <$> getDaemonStatus
+ . filter Remote.isXMPPRemote . syncRemotes <$> getDaemonStatus
um <- liftAnnex uuidMap
if elem (baseJID theirjid) knownjids && M.member theiruuid um
then autoaccept
diff --git a/Assistant/TransferQueue.hs b/Assistant/TransferQueue.hs
index 98fb2f06cb..93c982224b 100644
--- a/Assistant/TransferQueue.hs
+++ b/Assistant/TransferQueue.hs
@@ -1,6 +1,6 @@
{- git-annex assistant pending transfer queue
-
- - Copyright 2012 Joey Hess
+ - Copyright 2012-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -51,14 +51,17 @@ stubInfo f r = stubTransferInfo
{- Adds transfers to queue for some of the known remotes.
- Honors preferred content settings, only transferring wanted files. -}
-queueTransfers :: Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
+queueTransfers :: Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant Bool
queueTransfers = queueTransfersMatching (const True)
{- Adds transfers to queue for some of the known remotes, that match a
- condition. Honors preferred content settings. -}
-queueTransfersMatching :: (UUID -> Bool) -> Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant ()
+queueTransfersMatching :: (UUID -> Bool) -> Reason -> Schedule -> Key -> AssociatedFile -> Direction -> Assistant Bool
queueTransfersMatching matching reason schedule k f direction
- | direction == Download = whenM (liftAnnex $ wantGet True f) go
+ | direction == Download = ifM (liftAnnex $ wantGet True (Just k) f)
+ ( go
+ , return False
+ )
| otherwise = go
where
go = do
@@ -67,9 +70,13 @@ queueTransfersMatching matching reason schedule k f direction
=<< syncDataRemotes <$> getDaemonStatus
let matchingrs = filter (matching . Remote.uuid) rs
if null matchingrs
- then defer
- else forM_ matchingrs $ \r ->
- enqueue reason schedule (gentransfer r) (stubInfo f r)
+ then do
+ defer
+ return False
+ else do
+ forM_ matchingrs $ \r ->
+ enqueue reason schedule (gentransfer r) (stubInfo f r)
+ return True
selectremotes rs
{- Queue downloads from all remotes that
- have the key. The list of remotes is ordered with
@@ -82,7 +89,7 @@ queueTransfersMatching matching reason schedule k f direction
- already have it. -}
| otherwise = do
s <- locs
- filterM (wantSend True f . Remote.uuid) $
+ filterM (wantSend True (Just k) f . Remote.uuid) $
filter (\r -> not (inset s r || Remote.readonly r)) rs
where
locs = S.fromList <$> Remote.keyLocations k
diff --git a/Assistant/TransferSlots.hs b/Assistant/TransferSlots.hs
index cb5d61a396..de96cdf852 100644
--- a/Assistant/TransferSlots.hs
+++ b/Assistant/TransferSlots.hs
@@ -103,8 +103,8 @@ runTransferThread' program batchmaker d run = go
{- By the time this is called, the daemonstatus's currentTransfers map should
- already have been updated to include the transfer. -}
genTransfer :: Transfer -> TransferInfo -> TransferGenerator
-genTransfer t info = case (transferRemote info, associatedFile info) of
- (Just remote, Just file)
+genTransfer t info = case transferRemote info of
+ Just remote
| Git.repoIsLocalUnknown (Remote.repo remote) -> do
-- optimisation for removable drives not plugged in
liftAnnex $ recordFailedTransfer t info
@@ -114,7 +114,7 @@ genTransfer t info = case (transferRemote info, associatedFile info) of
( do
debug [ "Transferring:" , describeTransfer t info ]
notifyTransfer
- return $ Just (t, info, go remote file)
+ return $ Just (t, info, go remote)
, do
debug [ "Skipping unnecessary transfer:",
describeTransfer t info ]
@@ -149,10 +149,12 @@ genTransfer t info = case (transferRemote info, associatedFile info) of
- usual cleanup. However, first check if something else is
- running the transfer, to avoid removing active transfers.
-}
- go remote file transferrer = ifM (liftIO $ performTransfer transferrer t $ associatedFile info)
+ go remote transferrer = ifM (liftIO $ performTransfer transferrer t $ associatedFile info)
( do
- void $ addAlert $ makeAlertFiller True $
- transferFileAlert direction True file
+ maybe noop
+ (void . addAlert . makeAlertFiller True
+ . transferFileAlert direction True)
+ (associatedFile info)
unless isdownload $
handleDrops
("object uploaded to " ++ show remote)
@@ -188,11 +190,11 @@ genTransfer t info = case (transferRemote info, associatedFile info) of
shouldTransfer :: Transfer -> TransferInfo -> Annex Bool
shouldTransfer t info
| transferDirection t == Download =
- (not <$> inAnnex key) <&&> wantGet True file
+ (not <$> inAnnex key) <&&> wantGet True (Just key) file
| transferDirection t == Upload = case transferRemote info of
Nothing -> return False
Just r -> notinremote r
- <&&> wantSend True file (Remote.uuid r)
+ <&&> wantSend True (Just key) file (Remote.uuid r)
| otherwise = return False
where
key = transferKey t
@@ -216,7 +218,7 @@ finishedTransfer t (Just info)
| transferDirection t == Download =
whenM (liftAnnex $ inAnnex $ transferKey t) $ do
dodrops False
- queueTransfersMatching (/= transferUUID t)
+ void $ queueTransfersMatching (/= transferUUID t)
"newly received object"
Later (transferKey t) (associatedFile info) Upload
| otherwise = dodrops True
diff --git a/Assistant/Types/Alert.hs b/Assistant/Types/Alert.hs
index e6fbe86d39..19fe55e6e2 100644
--- a/Assistant/Types/Alert.hs
+++ b/Assistant/Types/Alert.hs
@@ -32,6 +32,7 @@ data AlertName
| SyncAlert
| NotFsckedAlert
| UpgradeAlert
+ | UnusedFilesAlert
deriving (Eq)
{- The first alert is the new alert, the second is an old alert.
diff --git a/Assistant/Unused.hs b/Assistant/Unused.hs
new file mode 100644
index 0000000000..3ad98c12e2
--- /dev/null
+++ b/Assistant/Unused.hs
@@ -0,0 +1,86 @@
+{- git-annex assistant unused files
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE OverloadedStrings #-}
+
+module Assistant.Unused where
+
+import qualified Data.Map as M
+
+import Assistant.Common
+import qualified Git
+import Types.Key
+import Logs.Unused
+import Logs.Location
+import Annex.Content
+import Utility.DataUnits
+import Utility.DiskFree
+import Utility.HumanTime
+import Utility.Tense
+
+import Data.Time.Clock.POSIX
+import qualified Data.Text as T
+
+describeUnused :: Assistant (Maybe TenseText)
+describeUnused = describeUnused' False
+
+describeUnusedWhenBig :: Assistant (Maybe TenseText)
+describeUnusedWhenBig = describeUnused' True
+
+{- This uses heuristics: 1000 unused keys, or more unused keys
+ - than the remaining free disk space, or more than 1/10th the total
+ - disk space being unused keys all suggest a problem. -}
+describeUnused' :: Bool -> Assistant (Maybe TenseText)
+describeUnused' whenbig = liftAnnex $ go =<< readUnusedLog ""
+ where
+ go m = do
+ let num = M.size m
+ let diskused = foldl' sumkeysize 0 (M.keys m)
+ df <- forpath getDiskFree
+ disksize <- forpath getDiskSize
+ return $ if num == 0
+ then Nothing
+ else if not whenbig || moreused df diskused || tenthused disksize diskused
+ then Just $ tenseWords
+ [ UnTensed $ T.pack $ roughSize storageUnits False diskused
+ , Tensed "are" "were"
+ , "taken up by unused files"
+ ]
+ else if num > 1000
+ then Just $ tenseWords
+ [ UnTensed $ T.pack $ show num ++ " unused files"
+ , Tensed "exist" "existed"
+ ]
+ else Nothing
+
+ moreused Nothing _ = False
+ moreused (Just df) used = df <= used
+
+ tenthused Nothing _ = False
+ tenthused (Just disksize) used = used >= disksize `div` 10
+
+ sumkeysize s k = s + fromMaybe 0 (keySize k)
+
+ forpath a = inRepo $ liftIO . a . Git.repoPath
+
+{- With a duration, expires all unused files that are older.
+ - With Nothing, expires *all* unused files. -}
+expireUnused :: Maybe Duration -> Assistant ()
+expireUnused duration = do
+ m <- liftAnnex $ readUnusedLog ""
+ now <- liftIO getPOSIXTime
+ let oldkeys = M.keys $ M.filter (tooold now) m
+ forM_ oldkeys $ \k -> do
+ debug ["removing old unused key", key2file k]
+ liftAnnex $ do
+ removeAnnex k
+ logStatus k InfoMissing
+ where
+ boundry = durationToPOSIXTime <$> duration
+ tooold now (_, mt) = case boundry of
+ Nothing -> True
+ Just b -> maybe False (\t -> now - t >= b) mt
diff --git a/Assistant/Upgrade.hs b/Assistant/Upgrade.hs
index fd71897cad..aaf6a8478b 100644
--- a/Assistant/Upgrade.hs
+++ b/Assistant/Upgrade.hs
@@ -276,7 +276,6 @@ deleteFromManifest dir = do
removeEmptyRecursive :: FilePath -> IO ()
removeEmptyRecursive dir = do
- print ("remove", dir)
mapM_ removeEmptyRecursive =<< dirContents dir
void $ tryIO $ removeDirectory dir
diff --git a/Assistant/WebApp/Configurators/Delete.hs b/Assistant/WebApp/Configurators/Delete.hs
index c29e4a681a..8d72853d2e 100644
--- a/Assistant/WebApp/Configurators/Delete.hs
+++ b/Assistant/WebApp/Configurators/Delete.hs
@@ -96,12 +96,11 @@ deleteCurrentRepository = dangerPage $ do
rs <- syncRemotes <$> getDaemonStatus
mapM_ (\r -> changeSyncable (Just r) False) rs
- {- Make all directories writable, so all annexed
- - content can be deleted. -}
+ {- Make all directories writable and files writable
+ - so all annexed content can be deleted. -}
liftIO $ do
- recurseDir SystemFS dir >>=
- filterM doesDirectoryExist >>=
- mapM_ allowWrite
+ recurseDir SystemFS dir
+ >>= mapM_ (void . tryIO . allowWrite)
removeDirectoryRecursive dir
redirect ShutdownConfirmedR
diff --git a/Assistant/WebApp/Configurators/Edit.hs b/Assistant/WebApp/Configurators/Edit.hs
index 59824de79c..279fe02a4c 100644
--- a/Assistant/WebApp/Configurators/Edit.hs
+++ b/Assistant/WebApp/Configurators/Edit.hs
@@ -264,6 +264,7 @@ getUpgradeRepositoryR r = go =<< liftAnnex (repoIdRemote r)
liftAnnex $ setConfig
(remoteConfig (Remote.repo rmt) "ignore")
(Git.Config.boolConfig False)
- liftAssistant $ syncRemote rmt
liftAnnex $ void Remote.remoteListRefresh
+ liftAssistant updateSyncRemotes
+ liftAssistant $ syncRemote rmt
redirect DashboardR
diff --git a/Assistant/WebApp/Configurators/Local.hs b/Assistant/WebApp/Configurators/Local.hs
index e0cb5ce264..1ab290b1b6 100644
--- a/Assistant/WebApp/Configurators/Local.hs
+++ b/Assistant/WebApp/Configurators/Local.hs
@@ -14,7 +14,7 @@ import Assistant.WebApp.Gpg
import Assistant.WebApp.MakeRemote
import Assistant.Sync
import Assistant.Restart
-import Init
+import Annex.Init
import qualified Git
import qualified Git.Construct
import qualified Git.Config
diff --git a/Assistant/WebApp/Configurators/Preferences.hs b/Assistant/WebApp/Configurators/Preferences.hs
index 385f187113..d4783e7422 100644
--- a/Assistant/WebApp/Configurators/Preferences.hs
+++ b/Assistant/WebApp/Configurators/Preferences.hs
@@ -17,6 +17,7 @@ import qualified Annex
import qualified Git
import Config
import Config.Files
+import Config.NumCopies
import Utility.DataUnits
import Git.Config
import Types.Distribution
@@ -81,7 +82,7 @@ prefsAForm def = PrefsForm
getPrefs :: Annex PrefsForm
getPrefs = PrefsForm
<$> (T.pack . roughSize storageUnits False . annexDiskReserve <$> Annex.getGitConfig)
- <*> (annexNumCopies <$> Annex.getGitConfig)
+ <*> (fromNumCopies <$> getNumCopies)
<*> inAutoStartFile
<*> (annexAutoUpgrade <$> Annex.getGitConfig)
<*> (annexDebug <$> Annex.getGitConfig)
@@ -89,7 +90,8 @@ getPrefs = PrefsForm
storePrefs :: PrefsForm -> Annex ()
storePrefs p = do
setConfig (annexConfig "diskreserve") (T.unpack $ diskReserve p)
- setConfig (annexConfig "numcopies") (show $ numCopies p)
+ setGlobalNumCopies (NumCopies $ numCopies p)
+ unsetConfig (annexConfig "numcopies") -- deprecated
setConfig (annexConfig "autoupgrade") (fromAutoUpgrade $ autoUpgrade p)
unlessM ((==) <$> pure (autoStart p) <*> inAutoStartFile) $ do
here <- fromRepo Git.repoPath
diff --git a/Assistant/WebApp/Configurators/Unused.hs b/Assistant/WebApp/Configurators/Unused.hs
new file mode 100644
index 0000000000..1f2fc87291
--- /dev/null
+++ b/Assistant/WebApp/Configurators/Unused.hs
@@ -0,0 +1,80 @@
+{- git-annex assistant unused file preferences
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
+{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-}
+
+module Assistant.WebApp.Configurators.Unused where
+
+import Assistant.WebApp.Common
+import qualified Annex
+import Utility.HumanTime
+import Assistant.Unused
+import Config
+import Git.Config
+import Logs.Unused
+import Utility.Tense
+
+import qualified Text.Hamlet as Hamlet
+
+data UnusedForm = UnusedForm
+ { enableExpire :: Bool
+ , expireWhen :: Integer
+ }
+
+unusedForm :: UnusedForm -> Hamlet.Html -> MkMForm UnusedForm
+unusedForm def msg = do
+ (enableRes, enableView) <- mreq (selectFieldList enabledisable) ""
+ (Just $ enableExpire def)
+ (whenRes, whenView) <- mreq intField ""
+ (Just $ expireWhen def)
+ let form = do
+ webAppFormAuthToken
+ $(widgetFile "configurators/unused/form")
+ return (UnusedForm <$> enableRes <*> whenRes, form)
+ where
+ enabledisable :: [(Text, Bool)]
+ enabledisable = [("Disable expiry", False), ("Enable expiry", True)]
+
+getConfigUnusedR :: Handler Html
+getConfigUnusedR = postConfigUnusedR
+postConfigUnusedR :: Handler Html
+postConfigUnusedR = page "Unused files" (Just Configuration) $ do
+ current <- liftAnnex getUnused
+ ((res, form), enctype) <- liftH $ runFormPostNoToken $ unusedForm current
+ case res of
+ FormSuccess new -> liftH $ do
+ liftAnnex $ storeUnused new
+ redirect ConfigurationR
+ _ -> do
+ munuseddesc <- liftAssistant describeUnused
+ ts <- liftAnnex $ dateUnusedLog ""
+ mlastchecked <- case ts of
+ Nothing -> pure Nothing
+ Just t -> Just <$> liftIO (durationSince t)
+ $(widgetFile "configurators/unused")
+
+getUnused :: Annex UnusedForm
+getUnused = convert . annexExpireUnused <$> Annex.getGitConfig
+ where
+ convert Nothing = noexpire
+ convert (Just Nothing) = noexpire
+ convert (Just (Just n)) = UnusedForm True $ durationToDays n
+
+ -- The 7 is so that, if they enable expiry, they have to change
+ -- it to get faster than a week.
+ noexpire = UnusedForm False 7
+
+storeUnused :: UnusedForm -> Annex ()
+storeUnused f = setConfig (annexConfig "expireunused") $
+ if not (enableExpire f) || expireWhen f < 0
+ then boolConfig False
+ else fromDuration $ daysToDuration $ expireWhen f
+
+getCleanupUnusedR :: Handler Html
+getCleanupUnusedR = do
+ liftAssistant $ expireUnused Nothing
+ redirect ConfigUnusedR
diff --git a/Assistant/WebApp/Configurators/XMPP.hs b/Assistant/WebApp/Configurators/XMPP.hs
index d0ded0b228..e7ba6c0736 100644
--- a/Assistant/WebApp/Configurators/XMPP.hs
+++ b/Assistant/WebApp/Configurators/XMPP.hs
@@ -161,7 +161,7 @@ buddyListDisplay = do
#ifdef WITH_XMPP
getXMPPRemotes :: Assistant [(JID, Remote)]
-getXMPPRemotes = catMaybes . map pair . filter isXMPPRemote . syncGitRemotes
+getXMPPRemotes = catMaybes . map pair . filter Remote.isXMPPRemote . syncGitRemotes
<$> getDaemonStatus
where
pair r = maybe Nothing (\jid -> Just (jid, r)) $
diff --git a/Assistant/WebApp/RepoList.hs b/Assistant/WebApp/RepoList.hs
index fd341466aa..56a3b9ea43 100644
--- a/Assistant/WebApp/RepoList.hs
+++ b/Assistant/WebApp/RepoList.hs
@@ -164,7 +164,7 @@ repoList reposelector
| Remote.readonly r = False
| onlyCloud reposelector = Git.repoIsUrl (Remote.repo r)
&& Remote.uuid r /= NoUUID
- && not (isXMPPRemote r)
+ && not (Remote.isXMPPRemote r)
| otherwise = True
selectedremote Nothing = False
selectedremote (Just (iscloud, _))
diff --git a/Assistant/WebApp/routes b/Assistant/WebApp/routes
index ac5b12a6fb..43b5dd8773 100644
--- a/Assistant/WebApp/routes
+++ b/Assistant/WebApp/routes
@@ -25,6 +25,7 @@
/config/upgrade/start/#GitAnnexDistribution ConfigStartUpgradeR GET
/config/upgrade/finish ConfigFinishUpgradeR GET
/config/upgrade/automatically ConfigEnableAutomaticUpgradeR GET
+/config/unused ConfigUnusedR GET POST
/config/addrepository AddRepositoryR GET
/config/repository/new NewRepositoryR GET POST
@@ -118,4 +119,6 @@
/repair/#UUID RepairRepositoryR GET POST
/repair/run/#UUID RepairRepositoryRunR GET POST
+/unused/cleanup CleanupUnusedR GET
+
/static StaticR Static getStatic
diff --git a/Build/EvilLinker.hs b/Build/EvilLinker.hs
index c36ec33f3c..c8641f649c 100644
--- a/Build/EvilLinker.hs
+++ b/Build/EvilLinker.hs
@@ -125,8 +125,8 @@ getOutput c ps environ = do
putStrLn $ unwords [c, show ps]
systemenviron <- getEnvironment
let environ' = fromMaybe [] environ ++ systemenviron
- out@(s, ok) <- processTranscript' c ps (Just environ') Nothing
- putStrLn $ unwords [c, "finished", show ok, "output size:", show (length s)]
+ out@(_, ok) <- processTranscript' c ps (Just environ') Nothing
+ putStrLn $ unwords [c, "finished", show ok]
return out
atFile :: FilePath -> String
diff --git a/Build/LinuxMkLibs.hs b/Build/LinuxMkLibs.hs
index 74641d811a..be605c5a58 100644
--- a/Build/LinuxMkLibs.hs
+++ b/Build/LinuxMkLibs.hs
@@ -141,4 +141,4 @@ parseLdd = catMaybes . map (getlib . dropWhile isSpace) . lines
- XXX Debian specific. -}
glibcLibs :: IO [FilePath]
glibcLibs = lines <$> readProcess "sh"
- ["-c", "dpkg -L libc6 libgcc1 | egrep '\\.so|gconv'"]
+ ["-c", "dpkg -L libc6:$(dpkg --print-architecture) libgcc1:$(dpkg --print-architecture) | egrep '\\.so|gconv'"]
diff --git a/Checks.hs b/Checks.hs
index 67aa51a2af..7a9cd1e38f 100644
--- a/Checks.hs
+++ b/Checks.hs
@@ -12,7 +12,7 @@ module Checks where
import Common.Annex
import Types.Command
-import Init
+import Annex.Init
import Config
import Utility.Daemon
import qualified Git
diff --git a/CmdLine.hs b/CmdLine.hs
index 7c28ecec82..a920898dce 100644
--- a/CmdLine.hs
+++ b/CmdLine.hs
@@ -23,7 +23,6 @@ import System.Posix.Signals
import Common.Annex
import qualified Annex
-import qualified Annex.Queue
import qualified Git
import qualified Git.AutoCorrect
import Annex.Content
@@ -41,7 +40,7 @@ dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
Left e -> maybe (throw e) (\a -> a params) (cmdnorepo cmd)
Right g -> do
state <- Annex.new g
- (actions, state') <- Annex.run state $ do
+ Annex.eval state $ do
checkEnvironment
checkfuzzy
forM_ fields $ uncurry Annex.setField
@@ -50,8 +49,9 @@ dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
sequence_ flags
whenM (annexDebug <$> Annex.getGitConfig) $
liftIO enableDebugOutput
- prepCommand cmd params
- tryRun state' cmd $ [startup] ++ actions ++ [shutdown $ cmdnocommit cmd]
+ startup
+ performCommandAction cmd params
+ shutdown $ cmdnocommit cmd
where
err msg = msg ++ "\n\n" ++ usage header allcmds
cmd = Prelude.head cmds
@@ -92,44 +92,19 @@ getOptCmd argv cmd commonoptions = check $
, commandUsage cmd
]
-{- Runs a list of Annex actions. Catches IO errors and continues
- - (but explicitly thrown errors terminate the whole command).
- -}
-tryRun :: Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
-tryRun = tryRun' 0
-tryRun' :: Integer -> Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
-tryRun' errnum _ cmd []
- | errnum > 0 = error $ cmdname cmd ++ ": " ++ show errnum ++ " failed"
- | otherwise = noop
-tryRun' errnum state cmd (a:as) = do
- r <- run
- handle $! r
- where
- run = tryIO $ Annex.run state $ do
- Annex.Queue.flushWhenFull
- a
- handle (Left err) = showerr err >> cont False state
- handle (Right (success, state')) = cont success state'
- cont success s = do
- let errnum' = if success then errnum else errnum + 1
- (tryRun' $! errnum') s cmd as
- showerr err = Annex.eval state $ do
- showErr err
- showEndFail
-
{- Actions to perform each time ran. -}
-startup :: Annex Bool
-startup = liftIO $ do
+startup :: Annex ()
+startup =
#ifndef mingw32_HOST_OS
- void $ installHandler sigINT Default Nothing
+ liftIO $ void $ installHandler sigINT Default Nothing
+#else
+ return ()
#endif
- return True
{- Cleanup actions. -}
-shutdown :: Bool -> Annex Bool
+shutdown :: Bool -> Annex ()
shutdown nocommit = do
saveState nocommit
sequence_ =<< M.elems <$> Annex.getState Annex.cleanup
liftIO reapZombies -- zombies from long-running git processes
sshCleanup -- ssh connection caching
- return True
diff --git a/CmdLine/Action.hs b/CmdLine/Action.hs
new file mode 100644
index 0000000000..247c658bcd
--- /dev/null
+++ b/CmdLine/Action.hs
@@ -0,0 +1,70 @@
+{- git-annex command-line actions
+ -
+ - Copyright 2010-2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE BangPatterns #-}
+
+module CmdLine.Action where
+
+import Common.Annex
+import qualified Annex
+import Types.Command
+import qualified Annex.Queue
+import Annex.Exception
+
+type CommandActionRunner = CommandStart -> CommandCleanup
+
+{- Runs a command, starting with the check stage, and then
+ - the seek stage. Finishes by printing the number of commandActions that
+ - failed. -}
+performCommandAction :: Command -> CmdParams -> Annex ()
+performCommandAction Command { cmdseek = seek, cmdcheck = c, cmdname = name } params = do
+ mapM_ runCheck c
+ Annex.changeState $ \s -> s { Annex.errcounter = 0 }
+ seek params
+ showerrcount =<< Annex.getState Annex.errcounter
+ where
+ showerrcount 0 = noop
+ showerrcount cnt = error $ name ++ ": " ++ show cnt ++ " failed"
+
+{- Runs one of the actions needed to perform a command.
+ - Individual actions can fail without stopping the whole command,
+ - including by throwing IO errors (but other errors terminate the whole
+ - command).
+ -
+ - This should only be run in the seek stage. -}
+commandAction :: CommandActionRunner
+commandAction a = handle =<< tryAnnexIO go
+ where
+ go = do
+ Annex.Queue.flushWhenFull
+ callCommandAction a
+ handle (Right True) = return True
+ handle (Right False) = incerr
+ handle (Left err) = do
+ showErr err
+ showEndFail
+ incerr
+ incerr = do
+ Annex.changeState $ \s ->
+ let ! c = Annex.errcounter s + 1
+ ! s' = s { Annex.errcounter = c }
+ in s'
+ return False
+
+{- Runs a single command action through the start, perform and cleanup
+ - stages, without catching errors. Useful if one command wants to run
+ - part of another command. -}
+callCommandAction :: CommandActionRunner
+callCommandAction = start
+ where
+ start = stage $ maybe skip perform
+ perform = stage $ maybe failure cleanup
+ cleanup = stage $ status
+ stage = (=<<)
+ skip = return True
+ failure = showEndFail >> return False
+ status r = showEndResult r >> return r
diff --git a/GitAnnex.hs b/CmdLine/GitAnnex.hs
similarity index 96%
rename from GitAnnex.hs
rename to CmdLine/GitAnnex.hs
index 4c1649ba14..b25082963b 100644
--- a/GitAnnex.hs
+++ b/CmdLine/GitAnnex.hs
@@ -7,12 +7,11 @@
{-# LANGUAGE CPP, OverloadedStrings #-}
-module GitAnnex where
+module CmdLine.GitAnnex where
import qualified Git.CurrentRepo
import CmdLine
import Command
-import GitAnnex.Options
import qualified Command.Add
import qualified Command.Unannex
@@ -50,6 +49,7 @@ import qualified Command.Info
import qualified Command.Status
import qualified Command.Migrate
import qualified Command.Uninit
+import qualified Command.NumCopies
import qualified Command.Trust
import qualified Command.Untrust
import qualified Command.Semitrust
@@ -117,6 +117,7 @@ cmds = concat
, Command.Unannex.def
, Command.Uninit.def
, Command.PreCommit.def
+ , Command.NumCopies.def
, Command.Trust.def
, Command.Untrust.def
, Command.Semitrust.def
@@ -178,4 +179,4 @@ run args = do
#ifdef WITH_EKG
_ <- forkServer "localhost" 4242
#endif
- dispatch True args cmds options [] header Git.CurrentRepo.get
+ dispatch True args cmds gitAnnexOptions [] header Git.CurrentRepo.get
diff --git a/GitAnnex/Options.hs b/CmdLine/GitAnnex/Options.hs
similarity index 78%
rename from GitAnnex/Options.hs
rename to CmdLine/GitAnnex/Options.hs
index 88fad948aa..fcf5deaf02 100644
--- a/GitAnnex/Options.hs
+++ b/CmdLine/GitAnnex/Options.hs
@@ -5,23 +5,25 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module GitAnnex.Options where
+module CmdLine.GitAnnex.Options where
import System.Console.GetOpt
import Common.Annex
import qualified Git.Config
import Git.Types
-import Command
import Types.TrustLevel
+import Types.NumCopies
+import Types.Messages
import qualified Annex
import qualified Remote
import qualified Limit
import qualified Limit.Wanted
-import qualified Option
+import CmdLine.Option
+import CmdLine.Usage
-options :: [Option]
-options = Option.common ++
+gitAnnexOptions :: [Option]
+gitAnnexOptions = commonOptions ++
[ Option ['N'] ["numcopies"] (ReqArg setnumcopies paramNumber)
"override default number of copies"
, Option [] ["trust"] (trustArg Trusted)
@@ -40,6 +42,10 @@ options = Option.common ++
"match files present in a remote"
, Option ['C'] ["copies"] (ReqArg Limit.addCopies paramNumber)
"skip files with fewer copies"
+ , Option [] ["lackingcopies"] (ReqArg (Limit.addLackingCopies False) paramNumber)
+ "match files that need more copies"
+ , Option [] ["approxlackingcopies"] (ReqArg (Limit.addLackingCopies True) paramNumber)
+ "match files that need more copies (faster)"
, Option ['B'] ["inbackend"] (ReqArg Limit.addInBackend paramName)
"match files using a key-value backend"
, Option [] ["inallgroup"] (ReqArg Limit.addInAllGroup paramGroup)
@@ -58,11 +64,11 @@ options = Option.common ++
"override default User-Agent"
, Option [] ["trust-glacier"] (NoArg (Annex.setFlag "trustglacier"))
"Trust Amazon Glacier inventory"
- ] ++ Option.matcher
+ ] ++ matcherOptions
where
trustArg t = ReqArg (Remote.forceTrust t) paramRemote
setnumcopies v = maybe noop
- (\n -> Annex.changeState $ \s -> s { Annex.forcenumcopies = Just n })
+ (\n -> Annex.changeState $ \s -> s { Annex.forcenumcopies = Just $ NumCopies n })
(readish v)
setuseragent v = Annex.changeState $ \s -> s { Annex.useragent = Just v }
setgitconfig v = inRepo (Git.Config.store v)
@@ -75,13 +81,19 @@ keyOptions =
"operate on all versions of all files"
, Option ['U'] ["unused"] (NoArg (Annex.setFlag "unused"))
"operate on files found by last run of git-annex unused"
+ , Option [] ["key"] (ReqArg (Annex.setField "key") paramKey)
+ "operate on specified key"
]
fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "source remote"
+fromOption = fieldOption ['f'] "from" paramRemote "source remote"
toOption :: Option
-toOption = Option.field ['t'] "to" paramRemote "destination remote"
+toOption = fieldOption ['t'] "to" paramRemote "destination remote"
fromToOptions :: [Option]
fromToOptions = [fromOption, toOption]
+
+jsonOption :: Option
+jsonOption = Option ['j'] ["json"] (NoArg (Annex.setOutput JSONOutput))
+ "enable JSON output"
diff --git a/GitAnnexShell.hs b/CmdLine/GitAnnexShell.hs
similarity index 97%
rename from GitAnnexShell.hs
rename to CmdLine/GitAnnexShell.hs
index b5f6804e77..f490792b07 100644
--- a/GitAnnexShell.hs
+++ b/CmdLine/GitAnnexShell.hs
@@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module GitAnnexShell where
+module CmdLine.GitAnnexShell where
import System.Environment
import System.Console.GetOpt
@@ -16,12 +16,11 @@ import CmdLine
import Command
import Annex.UUID
import Annex (setField)
-import qualified Option
-import Fields
+import CmdLine.GitAnnexShell.Fields
import Utility.UserInfo
import Remote.GCrypt (getGCryptUUID)
import qualified Annex
-import Init
+import Annex.Init
import qualified Command.ConfigList
import qualified Command.InAnnex
@@ -54,7 +53,7 @@ cmds = map adddirparam $ cmds_readonly ++ cmds_notreadonly
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
options :: [OptDescr (Annex ())]
-options = Option.common ++
+options = commonOptions ++
[ Option [] ["uuid"] (ReqArg checkUUID paramUUID) "local repository uuid"
]
where
@@ -104,7 +103,7 @@ builtin cmd dir params = do
Git.Construct.repoAbsPath dir >>= Git.Construct.fromAbsPath
where
addrsyncopts opts seek k = setField "RsyncOptions" opts >> seek k
- newcmd opts c = c { cmdseek = map (addrsyncopts opts) (cmdseek c) }
+ newcmd opts c = c { cmdseek = addrsyncopts opts (cmdseek c) }
external :: [String] -> IO ()
external params = do
diff --git a/Fields.hs b/CmdLine/GitAnnexShell/Fields.hs
similarity index 82%
rename from Fields.hs
rename to CmdLine/GitAnnexShell/Fields.hs
index ffd273be67..4f208773b9 100644
--- a/Fields.hs
+++ b/CmdLine/GitAnnexShell/Fields.hs
@@ -1,14 +1,15 @@
-{- git-annex fields
+{- git-annex-shell fields
-
- Copyright 2012 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
-module Fields where
+module CmdLine.GitAnnexShell.Fields where
import Common.Annex
import qualified Annex
+import Git.FilePath
import Data.Char
@@ -29,7 +30,7 @@ remoteUUID = Field "remoteuuid" $
associatedFile :: Field
associatedFile = Field "associatedfile" $ \f ->
-- is the file a safe relative filename?
- not (isAbsolute f) && not ("../" `isPrefixOf` f)
+ not (absoluteGitPath f) && not ("../" `isPrefixOf` f)
direct :: Field
direct = Field "direct" $ \f -> f == "1"
diff --git a/Option.hs b/CmdLine/Option.hs
similarity index 80%
rename from Option.hs
rename to CmdLine/Option.hs
index 64ba56f6d2..915b06849e 100644
--- a/Option.hs
+++ b/CmdLine/Option.hs
@@ -5,12 +5,12 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Option (
- common,
- matcher,
- flag,
- field,
- name,
+module CmdLine.Option (
+ commonOptions,
+ matcherOptions,
+ flagOption,
+ fieldOption,
+ optionName,
ArgDescr(..),
OptDescr(..),
) where
@@ -21,10 +21,10 @@ import Common.Annex
import qualified Annex
import Types.Messages
import Limit
-import Usage
+import CmdLine.Usage
-common :: [Option]
-common =
+commonOptions :: [Option]
+commonOptions =
[ Option [] ["force"] (NoArg (setforce True))
"allow actions that may lose annexed data"
, Option ['F'] ["fast"] (NoArg (setfast True))
@@ -35,8 +35,6 @@ common =
"avoid verbose output"
, Option ['v'] ["verbose"] (NoArg (Annex.setOutput NormalOutput))
"allow verbose output (default)"
- , Option ['j'] ["json"] (NoArg (Annex.setOutput JSONOutput))
- "enable JSON output"
, Option ['d'] ["debug"] (NoArg setdebug)
"show debug messages"
, Option [] ["no-debug"] (NoArg unsetdebug)
@@ -52,8 +50,8 @@ common =
setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True }
unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False }
-matcher :: [Option]
-matcher =
+matcherOptions :: [Option]
+matcherOptions =
[ longopt "not" "negate next option"
, longopt "and" "both previous and next option must match"
, longopt "or" "either previous or next option must match"
@@ -65,15 +63,15 @@ matcher =
shortopt o = Option o [] $ NoArg $ addToken o
{- An option that sets a flag. -}
-flag :: String -> String -> String -> Option
-flag short opt description =
+flagOption :: String -> String -> String -> Option
+flagOption short opt description =
Option short [opt] (NoArg (Annex.setFlag opt)) description
{- An option that sets a field. -}
-field :: String -> String -> String -> String -> Option
-field short opt paramdesc description =
+fieldOption :: String -> String -> String -> String -> Option
+fieldOption short opt paramdesc description =
Option short [opt] (ReqArg (Annex.setField opt) paramdesc) description
{- The flag or field name used for an option. -}
-name :: Option -> String
-name (Option _ o _ _) = Prelude.head o
+optionName :: Option -> String
+optionName (Option _ o _ _) = Prelude.head o
diff --git a/Seek.hs b/CmdLine/Seek.hs
similarity index 64%
rename from Seek.hs
rename to CmdLine/Seek.hs
index a4e9a2fe53..e95b9f0059 100644
--- a/Seek.hs
+++ b/CmdLine/Seek.hs
@@ -4,14 +4,12 @@
- the values a user passes to a command, and prepare actions operating
- on them.
-
- - Copyright 2010-2013 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
-module Seek where
-
-import System.PosixCompat.Files
+module CmdLine.Seek where
import Common.Annex
import Types.Command
@@ -22,24 +20,15 @@ import qualified Git
import qualified Git.Command
import qualified Git.LsFiles as LsFiles
import qualified Limit
-import qualified Option
-import Config
+import CmdLine.Option
+import CmdLine.Action
import Logs.Location
import Logs.Unused
import Annex.CatFile
-seekHelper :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> [FilePath] -> Annex [FilePath]
-seekHelper a params = do
- ll <- inRepo $ \g ->
- runSegmentPaths (\fs -> Git.Command.leaveZombie <$> a fs g) params
- {- Show warnings only for files/directories that do not exist. -}
- forM_ (map fst $ filter (null . snd) $ zip params ll) $ \p ->
- unlessM (isJust <$> liftIO (catchMaybeIO $ getSymbolicLinkStatus p)) $
- fileNotFound p
- return $ concat ll
-
withFilesInGit :: (FilePath -> CommandStart) -> CommandSeek
-withFilesInGit a params = prepFiltered a $ seekHelper LsFiles.inRepo params
+withFilesInGit a params = seekActions $ prepFiltered a $
+ seekHelper LsFiles.inRepo params
withFilesNotInGit :: (FilePath -> CommandStart) -> CommandSeek
withFilesNotInGit a params = do
@@ -47,7 +36,8 @@ withFilesNotInGit a params = do
files <- filter (not . dotfile) <$>
seekunless (null ps && not (null params)) ps
dotfiles <- seekunless (null dotps) dotps
- prepFiltered a $ return $ concat $ segmentPaths params (files++dotfiles)
+ seekActions $ prepFiltered a $
+ return $ concat $ segmentPaths params (files++dotfiles)
where
(dotps, ps) = partition dotfile params
seekunless True _ = return []
@@ -57,7 +47,8 @@ withFilesNotInGit a params = do
liftIO $ Git.Command.leaveZombie <$> LsFiles.notInRepo force l g
withPathContents :: ((FilePath, FilePath) -> CommandStart) -> CommandSeek
-withPathContents a params = map a . concat <$> liftIO (mapM get params)
+withPathContents a params = seekActions $
+ map a . concat <$> liftIO (mapM get params)
where
get p = ifM (isDirectory <$> getFileStatus p)
( map (\f -> (f, makeRelative (parentDir p) f))
@@ -66,20 +57,20 @@ withPathContents a params = map a . concat <$> liftIO (mapM get params)
)
withWords :: ([String] -> CommandStart) -> CommandSeek
-withWords a params = return [a params]
+withWords a params = seekActions $ return [a params]
withStrings :: (String -> CommandStart) -> CommandSeek
-withStrings a params = return $ map a params
+withStrings a params = seekActions $ return $ map a params
withPairs :: ((String, String) -> CommandStart) -> CommandSeek
-withPairs a params = return $ map a $ pairs [] params
+withPairs a params = seekActions $ return $ map a $ pairs [] params
where
pairs c [] = reverse c
pairs c (x:y:xs) = pairs ((x,y):c) xs
pairs _ _ = error "expected pairs"
withFilesToBeCommitted :: (String -> CommandStart) -> CommandSeek
-withFilesToBeCommitted a params = prepFiltered a $
+withFilesToBeCommitted a params = seekActions $ prepFiltered a $
seekHelper LsFiles.stagedNotDeleted params
withFilesUnlocked :: (FilePath -> CommandStart) -> CommandSeek
@@ -94,7 +85,8 @@ withFilesUnlockedToBeCommitted = withFilesUnlocked' LsFiles.typeChangedStaged
- not some other sort of symlink.
-}
withFilesUnlocked' :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> (FilePath -> CommandStart) -> CommandSeek
-withFilesUnlocked' typechanged a params = prepFiltered a unlockedfiles
+withFilesUnlocked' typechanged a params = seekActions $
+ prepFiltered a unlockedfiles
where
check f = liftIO (notSymlink f) <&&>
(isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f)
@@ -102,32 +94,25 @@ withFilesUnlocked' typechanged a params = prepFiltered a unlockedfiles
{- Finds files that may be modified. -}
withFilesMaybeModified :: (FilePath -> CommandStart) -> CommandSeek
-withFilesMaybeModified a params =
+withFilesMaybeModified a params = seekActions $
prepFiltered a $ seekHelper LsFiles.modified params
withKeys :: (Key -> CommandStart) -> CommandSeek
-withKeys a params = return $ map (a . parse) params
+withKeys a params = seekActions $ return $ map (a . parse) params
where
parse p = fromMaybe (error "bad key") $ file2key p
-withValue :: Annex v -> (v -> CommandSeek) -> CommandSeek
-withValue v a params = do
- r <- v
- a r params
-
-{- Modifies a seek action using the value of a field option, which is fed into
- - a conversion function, and then is passed into the seek action.
- - This ensures that the conversion function only runs once.
+{- Gets the value of a field options, which is fed into
+ - a conversion function.
-}
-withField :: Option -> (Maybe String -> Annex a) -> (a -> CommandSeek) -> CommandSeek
-withField option converter = withValue $
- converter <=< Annex.getField $ Option.name option
+getOptionField :: Option -> (Maybe String -> Annex a) -> Annex a
+getOptionField option converter = converter <=< Annex.getField $ optionName option
-withFlag :: Option -> (Bool -> CommandSeek) -> CommandSeek
-withFlag option = withValue $ Annex.getFlag (Option.name option)
+getOptionFlag :: Option -> Annex Bool
+getOptionFlag option = Annex.getFlag (optionName option)
withNothing :: CommandStart -> CommandSeek
-withNothing a [] = return [a]
+withNothing a [] = seekActions $ return [a]
withNothing _ _ = error "This command takes no parameters."
{- If --all is specified, or in a bare repo, runs an action on all
@@ -136,6 +121,8 @@ withNothing _ _ = error "This command takes no parameters."
- If --unused is specified, runs an action on all keys found by
- the last git annex unused scan.
-
+ - If --key is specified, operates only on that key.
+ -
- Otherwise, fall back to a regular CommandSeek action on
- whatever params were passed. -}
withKeyOptions :: (Key -> CommandStart) -> CommandSeek -> CommandSeek
@@ -143,36 +130,51 @@ withKeyOptions keyop fallbackop params = do
bare <- fromRepo Git.repoIsLocalBare
allkeys <- Annex.getFlag "all"
unused <- Annex.getFlag "unused"
+ specifickey <- Annex.getField "key"
auto <- Annex.getState Annex.auto
- case (allkeys || bare , unused, auto ) of
- (True , False , False) -> go loggedKeys
- (False , True , False) -> go unusedKeys
- (True , True , _ )
- | bare && not allkeys -> go unusedKeys
- | otherwise -> error "Cannot use --all with --unused."
- (False , False , _ ) -> fallbackop params
- (_ , _ , True )
- | bare -> error "Cannot use --auto in a bare repository."
- | otherwise -> error "Cannot use --auto with --all or --unused."
+ when (auto && bare) $
+ error "Cannot use --auto in a bare repository"
+ case (allkeys, unused, null params, specifickey) of
+ (False , False , True , Nothing)
+ | bare -> go auto loggedKeys
+ | otherwise -> fallbackop params
+ (False , False , _ , Nothing) -> fallbackop params
+ (True , False , True , Nothing) -> go auto loggedKeys
+ (False , True , True , Nothing) -> go auto unusedKeys'
+ (False , False , True , Just ks) -> case file2key ks of
+ Nothing -> error "Invalid key"
+ Just k -> go auto $ return [k]
+ _ -> error "Can only specify one of file names, --all, --unused, or --key"
where
- go a = do
- unless (null params) $
- error "Cannot mix --all or --unused with file names."
- map keyop <$> a
+ go True _ = error "Cannot use --auto with --all or --unused or --key"
+ go False a = do
+ matcher <- Limit.getMatcher
+ seekActions $ map (process matcher) <$> a
+ process matcher k = ifM (matcher $ MatchingKey k)
+ ( keyop k , return Nothing)
prepFiltered :: (FilePath -> CommandStart) -> Annex [FilePath] -> Annex [CommandStart]
prepFiltered a fs = do
matcher <- Limit.getMatcher
map (process matcher) <$> fs
where
- process matcher f = ifM (matcher $ FileInfo f f)
+ process matcher f = ifM (matcher $ MatchingFile $ FileInfo f f)
( a f , return Nothing )
+seekActions :: Annex [CommandStart] -> Annex ()
+seekActions gen = do
+ as <- gen
+ mapM_ commandAction as
+
+seekHelper :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> [FilePath] -> Annex [FilePath]
+seekHelper a params = do
+ ll <- inRepo $ \g ->
+ runSegmentPaths (\fs -> Git.Command.leaveZombie <$> a fs g) params
+ {- Show warnings only for files/directories that do not exist. -}
+ forM_ (map fst $ filter (null . snd) $ zip params ll) $ \p ->
+ unlessM (isJust <$> liftIO (catchMaybeIO $ getSymbolicLinkStatus p)) $
+ fileNotFound p
+ return $ concat ll
+
notSymlink :: FilePath -> IO Bool
notSymlink f = liftIO $ not . isSymbolicLink <$> getSymbolicLinkStatus f
-
-whenNotDirect :: CommandSeek -> CommandSeek
-whenNotDirect a params = ifM isDirect ( return [] , a params )
-
-whenDirect :: CommandSeek -> CommandSeek
-whenDirect a params = ifM isDirect ( a params, return [] )
diff --git a/Usage.hs b/CmdLine/Usage.hs
similarity index 98%
rename from Usage.hs
rename to CmdLine/Usage.hs
index 9a48a09086..64b512144d 100644
--- a/Usage.hs
+++ b/CmdLine/Usage.hs
@@ -5,7 +5,7 @@
- Licensed under the GNU GPL version 3 or higher.
-}
-module Usage where
+module CmdLine.Usage where
import Common.Annex
diff --git a/Command.hs b/Command.hs
index b6484749ec..83d67bffd9 100644
--- a/Command.hs
+++ b/Command.hs
@@ -1,10 +1,12 @@
{- git-annex command infrastructure
-
- - Copyright 2010-2011 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
+{-# LANGUAGE BangPatterns #-}
+
module Command (
command,
noRepo,
@@ -14,13 +16,9 @@ module Command (
next,
stop,
stopUnless,
- prepCommand,
- doCommand,
whenAnnexed,
ifAnnexed,
isBareRepo,
- numCopies,
- numCopiesCheck,
checkAuto,
module ReExported
) where
@@ -29,18 +27,17 @@ import Common.Annex
import qualified Backend
import qualified Annex
import qualified Git
-import qualified Remote
import Types.Command as ReExported
import Types.Option as ReExported
-import Seek as ReExported
+import CmdLine.Seek as ReExported
import Checks as ReExported
-import Usage as ReExported
-import Logs.Trust
-import Config
-import Annex.CheckAttr
+import CmdLine.Usage as ReExported
+import CmdLine.Action as ReExported
+import CmdLine.Option as ReExported
+import CmdLine.GitAnnex.Options as ReExported
{- Generates a normal command -}
-command :: String -> String -> [CommandSeek] -> CommandSection -> String -> Command
+command :: String -> String -> CommandSeek -> CommandSection -> String -> Command
command = Command [] Nothing commonChecks False False
{- Indicates that a command doesn't need to commit any changes to
@@ -74,25 +71,6 @@ stop = return Nothing
stopUnless :: Annex Bool -> Annex (Maybe a) -> Annex (Maybe a)
stopUnless c a = ifM c ( a , stop )
-{- Prepares to run a command via the check and seek stages, returning a
- - list of actions to perform to run the command. -}
-prepCommand :: Command -> [String] -> Annex [CommandCleanup]
-prepCommand Command { cmdseek = seek, cmdcheck = c } params = do
- mapM_ runCheck c
- map doCommand . concat <$> mapM (\s -> s params) seek
-
-{- Runs a command through the start, perform and cleanup stages -}
-doCommand :: CommandStart -> CommandCleanup
-doCommand = start
- where
- start = stage $ maybe skip perform
- perform = stage $ maybe failure cleanup
- cleanup = stage $ status
- stage = (=<<)
- skip = return True
- failure = showEndFail >> return False
- status r = showEndResult r >> return r
-
{- Modifies an action to only act on files that are already annexed,
- and passes the key and backend on to it. -}
whenAnnexed :: (FilePath -> (Key, Backend) -> Annex (Maybe a)) -> FilePath -> Annex (Maybe a)
@@ -104,20 +82,6 @@ ifAnnexed file yes no = maybe no yes =<< Backend.lookupFile file
isBareRepo :: Annex Bool
isBareRepo = fromRepo Git.repoIsLocalBare
-numCopies :: FilePath -> Annex (Maybe Int)
-numCopies file = do
- forced <- Annex.getState Annex.forcenumcopies
- case forced of
- Just n -> return $ Just n
- Nothing -> readish <$> checkAttr "annex.numcopies" file
-
-numCopiesCheck :: FilePath -> Key -> (Int -> Int -> v) -> Annex v
-numCopiesCheck file key vs = do
- numcopiesattr <- numCopies file
- needed <- getNumCopies numcopiesattr
- have <- trustExclude UnTrusted =<< Remote.keyLocations key
- return $ length have `vs` needed
-
checkAuto :: Annex Bool -> Annex Bool
checkAuto checker = ifM (Annex.getState Annex.auto)
( checker , return True )
diff --git a/Command/Add.hs b/Command/Add.hs
index c5035ba1fd..d1dcb6025d 100644
--- a/Command/Add.hs
+++ b/Command/Add.hs
@@ -9,8 +9,6 @@
module Command.Add where
-import System.PosixCompat.Files
-
import Common.Annex
import Annex.Exception
import Command
@@ -41,18 +39,18 @@ def = [notBareRepo $ command "add" paramPaths seek SectionCommon
{- Add acts on both files not checked into git yet, and unlocked files.
-
- In direct mode, it acts on any files that have changed. -}
-seek :: [CommandSeek]
-seek =
- [ go withFilesNotInGit
- , whenNotDirect $ go withFilesUnlocked
- , whenDirect $ go withFilesMaybeModified
- ]
- where
- go a = withValue largeFilesMatcher $ \matcher ->
- a $ \file -> ifM (checkFileMatcher matcher file <||> Annex.getState Annex.force)
- ( start file
- , stop
- )
+seek :: CommandSeek
+seek ps = do
+ matcher <- largeFilesMatcher
+ let go a = flip a ps $ \file -> ifM (checkFileMatcher matcher file <||> Annex.getState Annex.force)
+ ( start file
+ , stop
+ )
+ go withFilesNotInGit
+ ifM isDirect
+ ( go withFilesMaybeModified
+ , go withFilesUnlocked
+ )
{- The add subcommand annexes a file, generating a key for it using a
- backend, and then moving it into the annex directory and setting up
diff --git a/Command/AddUnused.hs b/Command/AddUnused.hs
index 1a178e8d47..91427e8191 100644
--- a/Command/AddUnused.hs
+++ b/Command/AddUnused.hs
@@ -18,8 +18,8 @@ def :: [Command]
def = [notDirect $ command "addunused" (paramRepeating paramNumRange)
seek SectionMaintenance "add back unused files"]
-seek :: [CommandSeek]
-seek = [withUnusedMaps start]
+seek :: CommandSeek
+seek = withUnusedMaps start
start :: UnusedMaps -> Int -> CommandStart
start = startUnused "addunused" perform
diff --git a/Command/AddUrl.hs b/Command/AddUrl.hs
index 7f3607b816..82b04f07b4 100644
--- a/Command/AddUrl.hs
+++ b/Command/AddUrl.hs
@@ -21,7 +21,6 @@ import qualified Annex.Url as Url
import qualified Backend.URL
import Annex.Content
import Logs.Web
-import qualified Option
import Types.Key
import Types.KeySource
import Config
@@ -39,19 +38,20 @@ def = [notBareRepo $ withOptions [fileOption, pathdepthOption, relaxedOption] $
SectionCommon "add urls to annex"]
fileOption :: Option
-fileOption = Option.field [] "file" paramFile "specify what file the url is added to"
+fileOption = fieldOption [] "file" paramFile "specify what file the url is added to"
pathdepthOption :: Option
-pathdepthOption = Option.field [] "pathdepth" paramNumber "path components to use in filename"
+pathdepthOption = fieldOption [] "pathdepth" paramNumber "path components to use in filename"
relaxedOption :: Option
-relaxedOption = Option.flag [] "relaxed" "skip size check"
+relaxedOption = flagOption [] "relaxed" "skip size check"
-seek :: [CommandSeek]
-seek = [withField fileOption return $ \f ->
- withFlag relaxedOption $ \relaxed ->
- withField pathdepthOption (return . maybe Nothing readish) $ \d ->
- withStrings $ start relaxed f d]
+seek :: CommandSeek
+seek ps = do
+ f <- getOptionField fileOption return
+ relaxed <- getOptionFlag relaxedOption
+ d <- getOptionField pathdepthOption (return . maybe Nothing readish)
+ withStrings (start relaxed f d) ps
start :: Bool -> Maybe FilePath -> Maybe Int -> String -> CommandStart
start relaxed optfile pathdepth s = go $ fromMaybe bad $ parseURI s
diff --git a/Command/Assistant.hs b/Command/Assistant.hs
index cef4392dc6..7a05cdfbae 100644
--- a/Command/Assistant.hs
+++ b/Command/Assistant.hs
@@ -9,9 +9,8 @@ module Command.Assistant where
import Common.Annex
import Command
-import qualified Option
import qualified Command.Watch
-import Init
+import Annex.Init
import Config.Files
import qualified Build.SysConfig
import Utility.HumanTime
@@ -32,17 +31,18 @@ options =
]
autoStartOption :: Option
-autoStartOption = Option.flag [] "autostart" "start in known repositories"
+autoStartOption = flagOption [] "autostart" "start in known repositories"
startDelayOption :: Option
-startDelayOption = Option.field [] "startdelay" paramNumber "delay before running startup scan"
+startDelayOption = fieldOption [] "startdelay" paramNumber "delay before running startup scan"
-seek :: [CommandSeek]
-seek = [withFlag Command.Watch.stopOption $ \stopdaemon ->
- withFlag Command.Watch.foregroundOption $ \foreground ->
- withFlag autoStartOption $ \autostart ->
- withField startDelayOption (pure . maybe Nothing parseDuration) $ \startdelay ->
- withNothing $ start foreground stopdaemon autostart startdelay]
+seek :: CommandSeek
+seek ps = do
+ stopdaemon <- getOptionFlag Command.Watch.stopOption
+ foreground <- getOptionFlag Command.Watch.foregroundOption
+ autostart <- getOptionFlag autoStartOption
+ startdelay <- getOptionField startDelayOption (pure . maybe Nothing parseDuration)
+ withNothing (start foreground stopdaemon autostart startdelay) ps
start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start foreground stopdaemon autostart startdelay
diff --git a/Command/Commit.hs b/Command/Commit.hs
index 6f3f9df285..f5f13d248e 100644
--- a/Command/Commit.hs
+++ b/Command/Commit.hs
@@ -16,8 +16,8 @@ def :: [Command]
def = [command "commit" paramNothing seek
SectionPlumbing "commits any staged changes to the git-annex branch"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = next $ next $ do
diff --git a/Command/ConfigList.hs b/Command/ConfigList.hs
index c42480200b..58b7388645 100644
--- a/Command/ConfigList.hs
+++ b/Command/ConfigList.hs
@@ -17,8 +17,8 @@ def :: [Command]
def = [noCommit $ command "configlist" paramNothing seek
SectionPlumbing "outputs relevant git configuration"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
diff --git a/Command/Copy.hs b/Command/Copy.hs
index 9fd97334ad..29606061d2 100644
--- a/Command/Copy.hs
+++ b/Command/Copy.hs
@@ -9,22 +9,23 @@ module Command.Copy where
import Common.Annex
import Command
-import GitAnnex.Options
import qualified Command.Move
import qualified Remote
import Annex.Wanted
+import Config.NumCopies
def :: [Command]
def = [withOptions Command.Move.moveOptions $ command "copy" paramPaths seek
SectionCommon "copy content of files to/from another repository"]
-seek :: [CommandSeek]
-seek =
- [ withField toOption Remote.byNameWithUUID $ \to ->
- withField fromOption Remote.byNameWithUUID $ \from ->
- withKeyOptions (Command.Move.startKey to from False) $
- withFilesInGit $ whenAnnexed $ start to from
- ]
+seek :: CommandSeek
+seek ps = do
+ to <- getOptionField toOption Remote.byNameWithUUID
+ from <- getOptionField fromOption Remote.byNameWithUUID
+ withKeyOptions
+ (Command.Move.startKey to from False)
+ (withFilesInGit $ whenAnnexed $ start to from)
+ ps
{- A copy is just a move that does not delete the source file.
- However, --auto mode avoids unnecessary copies, and avoids getting or
@@ -35,5 +36,5 @@ start to from file (key, backend) = stopUnless shouldCopy $
where
shouldCopy = checkAuto (check <||> numCopiesCheck file key (<))
check = case to of
- Nothing -> wantGet False (Just file)
- Just r -> wantSend False (Just file) (Remote.uuid r)
+ Nothing -> wantGet False (Just key) (Just file)
+ Just r -> wantSend False (Just key) (Just file) (Remote.uuid r)
diff --git a/Command/Dead.hs b/Command/Dead.hs
index 180f2fda90..13aa74bffa 100644
--- a/Command/Dead.hs
+++ b/Command/Dead.hs
@@ -19,8 +19,8 @@ def :: [Command]
def = [command "dead" (paramRepeating paramRemote) seek
SectionSetup "hide a lost repository"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start ws = do
diff --git a/Command/Describe.hs b/Command/Describe.hs
index 18851b1726..601b3fcc98 100644
--- a/Command/Describe.hs
+++ b/Command/Describe.hs
@@ -16,8 +16,8 @@ def :: [Command]
def = [command "describe" (paramPair paramRemote paramDesc) seek
SectionSetup "change description of a repository"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start (name:description) = do
diff --git a/Command/Direct.hs b/Command/Direct.hs
index c35bbdaea8..47f622a81a 100644
--- a/Command/Direct.hs
+++ b/Command/Direct.hs
@@ -23,8 +23,8 @@ def = [notBareRepo $ noDaemonRunning $
command "direct" paramNothing seek
SectionSetup "switch repository to direct mode"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = ifM isDirect ( stop , next perform )
diff --git a/Command/Drop.hs b/Command/Drop.hs
index 4c7128603d..d29195b050 100644
--- a/Command/Drop.hs
+++ b/Command/Drop.hs
@@ -14,26 +14,25 @@ import qualified Annex
import Annex.UUID
import Logs.Location
import Logs.Trust
+import Config.NumCopies
import Annex.Content
-import Config
-import qualified Option
import Annex.Wanted
-import Types.Key
def :: [Command]
-def = [withOptions [fromOption] $ command "drop" paramPaths seek
+def = [withOptions [dropFromOption] $ command "drop" paramPaths seek
SectionCommon "indicate content of files not currently wanted"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "drop content from a remote"
+dropFromOption :: Option
+dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
-seek :: [CommandSeek]
-seek = [withField fromOption Remote.byNameWithUUID $ \from ->
- withFilesInGit $ whenAnnexed $ start from]
+seek :: CommandSeek
+seek ps = do
+ from <- getOptionField dropFromOption Remote.byNameWithUUID
+ withFilesInGit (whenAnnexed $ start from) ps
start :: Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart
start from file (key, _) = checkDropAuto from file key $ \numcopies ->
- stopUnless (checkAuto $ wantDrop False (Remote.uuid <$> from) (Just file)) $
+ stopUnless (checkAuto $ wantDrop False (Remote.uuid <$> from) (Just key) (Just file)) $
case from of
Nothing -> startLocal (Just file) numcopies key Nothing
Just remote -> do
@@ -42,17 +41,17 @@ start from file (key, _) = checkDropAuto from file key $ \numcopies ->
then startLocal (Just file) numcopies key Nothing
else startRemote (Just file) numcopies key remote
-startLocal :: AssociatedFile -> Maybe Int -> Key -> Maybe Remote -> CommandStart
+startLocal :: AssociatedFile -> NumCopies -> Key -> Maybe Remote -> CommandStart
startLocal afile numcopies key knownpresentremote = stopUnless (inAnnex key) $ do
- showStart "drop" (fromMaybe (key2file key) afile)
+ showStart' "drop" key afile
next $ performLocal key numcopies knownpresentremote
-startRemote :: AssociatedFile -> Maybe Int -> Key -> Remote -> CommandStart
+startRemote :: AssociatedFile -> NumCopies -> Key -> Remote -> CommandStart
startRemote afile numcopies key remote = do
- showStart ("drop " ++ Remote.name remote) (fromMaybe (key2file key) afile)
+ showStart' ("drop " ++ Remote.name remote) key afile
next $ performRemote key numcopies remote
-performLocal :: Key -> Maybe Int -> Maybe Remote -> CommandPerform
+performLocal :: Key -> NumCopies -> Maybe Remote -> CommandPerform
performLocal key numcopies knownpresentremote = lockContent key $ do
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
let trusteduuids' = case knownpresentremote of
@@ -64,7 +63,7 @@ performLocal key numcopies knownpresentremote = lockContent key $ do
removeAnnex key
next $ cleanupLocal key
-performRemote :: Key -> Maybe Int -> Remote -> CommandPerform
+performRemote :: Key -> NumCopies -> Remote -> CommandPerform
performRemote key numcopies remote = lockContent key $ do
-- Filter the remote it's being dropped from out of the lists of
-- places assumed to have the key, and places to check.
@@ -97,23 +96,21 @@ cleanupRemote key remote ok = do
{- Checks specified remotes to verify that enough copies of a key exist to
- allow it to be safely removed (with no data loss). Can be provided with
- some locations where the key is known/assumed to be present. -}
-canDropKey :: Key -> Maybe Int -> [UUID] -> [Remote] -> [UUID] -> Annex Bool
-canDropKey key numcopiesM have check skip = do
+canDropKey :: Key -> NumCopies -> [UUID] -> [Remote] -> [UUID] -> Annex Bool
+canDropKey key numcopies have check skip = do
force <- Annex.getState Annex.force
- if force || numcopiesM == Just 0
+ if force || numcopies == NumCopies 0
then return True
- else do
- need <- getNumCopies numcopiesM
- findCopies key need skip have check
+ else findCopies key numcopies skip have check
-findCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
+findCopies :: Key -> NumCopies -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
findCopies key need skip = helper [] []
where
helper bad missing have []
- | length have >= need = return True
+ | NumCopies (length have) >= need = return True
| otherwise = notEnoughCopies key need have (skip++missing) bad
helper bad missing have (r:rs)
- | length have >= need = return True
+ | NumCopies (length have) >= need = return True
| otherwise = do
let u = Remote.uuid r
let duplicate = u `elem` have
@@ -124,12 +121,12 @@ findCopies key need skip = helper [] []
(False, Right False) -> helper bad (u:missing) have rs
_ -> helper bad missing have rs
-notEnoughCopies :: Key -> Int -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
+notEnoughCopies :: Key -> NumCopies -> [UUID] -> [UUID] -> [Remote] -> Annex Bool
notEnoughCopies key need have skip bad = do
unsafe
showLongNote $
"Could only verify the existence of " ++
- show (length have) ++ " out of " ++ show need ++
+ show (length have) ++ " out of " ++ show (fromNumCopies need) ++
" necessary copies"
Remote.showTriedRemotes bad
Remote.showLocations key (have++skip)
@@ -138,25 +135,21 @@ notEnoughCopies key need have skip bad = do
return False
where
unsafe = showNote "unsafe"
- hint = showLongNote "(Use --force to override this check, or adjust annex.numcopies.)"
+ hint = showLongNote "(Use --force to override this check, or adjust numcopies.)"
{- In auto mode, only runs the action if there are enough
- - copies on other semitrusted repositories.
- -
- - Passes any numcopies attribute of the file on to the action as an
- - optimisation. -}
-checkDropAuto :: Maybe Remote -> FilePath -> Key -> (Maybe Int -> CommandStart) -> CommandStart
+ - copies on other semitrusted repositories. -}
+checkDropAuto :: Maybe Remote -> FilePath -> Key -> (NumCopies -> CommandStart) -> CommandStart
checkDropAuto mremote file key a = do
- numcopiesattr <- numCopies file
- Annex.getState Annex.auto >>= auto numcopiesattr
+ numcopies <- getFileNumCopies file
+ Annex.getState Annex.auto >>= auto numcopies
where
- auto numcopiesattr False = a numcopiesattr
- auto numcopiesattr True = do
- needed <- getNumCopies numcopiesattr
+ auto numcopies False = a numcopies
+ auto numcopies True = do
locs <- Remote.keyLocations key
uuid <- getUUID
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
- if length locs' >= needed
- then a numcopiesattr
+ if NumCopies (length locs') >= numcopies
+ then a numcopies
else stop
diff --git a/Command/DropKey.hs b/Command/DropKey.hs
index 6249195840..125e6ded40 100644
--- a/Command/DropKey.hs
+++ b/Command/DropKey.hs
@@ -12,20 +12,19 @@ import Command
import qualified Annex
import Logs.Location
import Annex.Content
-import Types.Key
def :: [Command]
def = [noCommit $ command "dropkey" (paramRepeating paramKey) seek
SectionPlumbing "drops annexed content for specified keys"]
-seek :: [CommandSeek]
-seek = [withKeys start]
+seek :: CommandSeek
+seek = withKeys start
start :: Key -> CommandStart
start key = stopUnless (inAnnex key) $ do
unlessM (Annex.getState Annex.force) $
error "dropkey can cause data loss; use --force if you're sure you want to do this"
- showStart "dropkey" (key2file key)
+ showStart' "dropkey" key Nothing
next $ perform key
perform :: Key -> CommandPerform
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index bf2635e00f..a3409ab1b7 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -13,28 +13,30 @@ import qualified Annex
import qualified Command.Drop
import qualified Remote
import qualified Git
-import qualified Option
import Command.Unused (withUnusedMaps, UnusedMaps(..), startUnused)
+import Config.NumCopies
def :: [Command]
-def = [withOptions [Command.Drop.fromOption] $
+def = [withOptions [Command.Drop.dropFromOption] $
command "dropunused" (paramRepeating paramNumRange)
seek SectionMaintenance "drop unused file content"]
-seek :: [CommandSeek]
-seek = [withUnusedMaps start]
+seek :: CommandSeek
+seek ps = do
+ numcopies <- getNumCopies
+ withUnusedMaps (start numcopies) ps
-start :: UnusedMaps -> Int -> CommandStart
-start = startUnused "dropunused" perform (performOther gitAnnexBadLocation) (performOther gitAnnexTmpLocation)
+start :: NumCopies -> UnusedMaps -> Int -> CommandStart
+start numcopies = startUnused "dropunused" (perform numcopies) (performOther gitAnnexBadLocation) (performOther gitAnnexTmpLocation)
-perform :: Key -> CommandPerform
-perform key = maybe droplocal dropremote =<< Remote.byNameWithUUID =<< from
+perform :: NumCopies -> Key -> CommandPerform
+perform numcopies key = maybe droplocal dropremote =<< Remote.byNameWithUUID =<< from
where
dropremote r = do
showAction $ "from " ++ Remote.name r
- Command.Drop.performRemote key Nothing r
- droplocal = Command.Drop.performLocal key Nothing Nothing
- from = Annex.getField $ Option.name Command.Drop.fromOption
+ Command.Drop.performRemote key numcopies r
+ droplocal = Command.Drop.performLocal key numcopies Nothing
+ from = Annex.getField $ optionName Command.Drop.dropFromOption
performOther :: (Key -> Git.Repo -> FilePath) -> Key -> CommandPerform
performOther filespec key = do
diff --git a/Command/EnableRemote.hs b/Command/EnableRemote.hs
index f6a1b819c8..a00046d5a5 100644
--- a/Command/EnableRemote.hs
+++ b/Command/EnableRemote.hs
@@ -20,8 +20,8 @@ def = [command "enableremote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "enables use of an existing special remote"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start [] = unknownNameError "Specify the name of the special remote to enable."
@@ -40,10 +40,10 @@ start (name:ws) = go =<< InitRemote.findExisting name
unknownNameError :: String -> Annex a
unknownNameError prefix = do
names <- InitRemote.remoteNames
- error $ prefix ++
+ error $ prefix ++ "\n" ++
if null names
- then ""
- else " Known special remotes: " ++ unwords names
+ then "(No special remotes are currently known; perhaps use initremote instead?)"
+ else "Known special remotes: " ++ unwords names
perform :: RemoteType -> UUID -> R.RemoteConfig -> CommandPerform
perform t u c = do
diff --git a/Command/ExamineKey.hs b/Command/ExamineKey.hs
index 7dfdadd3df..dd2bec5071 100644
--- a/Command/ExamineKey.hs
+++ b/Command/ExamineKey.hs
@@ -10,16 +10,18 @@ module Command.ExamineKey where
import Common.Annex
import Command
import qualified Utility.Format
-import Command.Find (formatOption, withFormat, showFormatted, keyVars)
+import Command.Find (formatOption, getFormat, showFormatted, keyVars)
import Types.Key
def :: [Command]
-def = [noCommit $ noMessages $ withOptions [formatOption] $
+def = [noCommit $ noMessages $ withOptions [formatOption, jsonOption] $
command "examinekey" (paramRepeating paramKey) seek
SectionPlumbing "prints information from a key"]
-seek :: [CommandSeek]
-seek = [withFormat $ \f -> withKeys $ start f]
+seek :: CommandSeek
+seek ps = do
+ format <- getFormat
+ withKeys (start format) ps
start :: Maybe Utility.Format.Format -> Key -> CommandStart
start format key = do
diff --git a/Command/Find.hs b/Command/Find.hs
index 0591e657e0..c6a32a9449 100644
--- a/Command/Find.hs
+++ b/Command/Find.hs
@@ -17,26 +17,27 @@ import qualified Annex
import qualified Utility.Format
import Utility.DataUnits
import Types.Key
-import qualified Option
def :: [Command]
-def = [noCommit $ noMessages $ withOptions [formatOption, print0Option] $
+def = [noCommit $ noMessages $ withOptions [formatOption, print0Option, jsonOption] $
command "find" paramPaths seek SectionQuery "lists available files"]
formatOption :: Option
-formatOption = Option.field [] "format" paramFormat "control format of output"
+formatOption = fieldOption [] "format" paramFormat "control format of output"
-withFormat :: (Maybe Utility.Format.Format -> CommandSeek) -> CommandSeek
-withFormat = withField formatOption $ return . fmap Utility.Format.gen
+getFormat :: Annex (Maybe Utility.Format.Format)
+getFormat = getOptionField formatOption $ return . fmap Utility.Format.gen
print0Option :: Option
-print0Option = Option.Option [] ["print0"] (Option.NoArg set)
+print0Option = Option [] ["print0"] (NoArg set)
"terminate output with null"
where
- set = Annex.setField (Option.name formatOption) "${file}\0"
+ set = Annex.setField (optionName formatOption) "${file}\0"
-seek :: [CommandSeek]
-seek = [withFormat $ \f -> withFilesInGit $ whenAnnexed $ start f]
+seek :: CommandSeek
+seek ps = do
+ format <- getFormat
+ withFilesInGit (whenAnnexed $ start format) ps
start :: Maybe Utility.Format.Format -> FilePath -> (Key, Backend) -> CommandStart
start format file (key, _) = do
diff --git a/Command/Fix.hs b/Command/Fix.hs
index a63a10f8f9..f730226e30 100644
--- a/Command/Fix.hs
+++ b/Command/Fix.hs
@@ -9,8 +9,6 @@
module Command.Fix where
-import System.PosixCompat.Files
-
import Common.Annex
import Command
import qualified Annex.Queue
@@ -24,8 +22,8 @@ def :: [Command]
def = [notDirect $ noCommit $ command "fix" paramPaths seek
SectionMaintenance "fix up symlinks to point to annexed content"]
-seek :: [CommandSeek]
-seek = [withFilesInGit $ whenAnnexed start]
+seek :: CommandSeek
+seek = withFilesInGit $ whenAnnexed start
{- Fixes the symlink to an annexed file. -}
start :: FilePath -> (Key, Backend) -> CommandStart
diff --git a/Command/Forget.hs b/Command/Forget.hs
index 74bd68ad1d..dbcce6cc36 100644
--- a/Command/Forget.hs
+++ b/Command/Forget.hs
@@ -12,7 +12,6 @@ import Command
import qualified Annex.Branch as Branch
import Logs.Transitions
import qualified Annex
-import qualified Option
import Data.Time.Clock.POSIX
@@ -24,11 +23,12 @@ forgetOptions :: [Option]
forgetOptions = [dropDeadOption]
dropDeadOption :: Option
-dropDeadOption = Option.flag [] "drop-dead" "drop references to dead repositories"
+dropDeadOption = flagOption [] "drop-dead" "drop references to dead repositories"
-seek :: [CommandSeek]
-seek = [withFlag dropDeadOption $ \dropdead ->
- withNothing $ start dropdead]
+seek :: CommandSeek
+seek ps = do
+ dropdead <- getOptionFlag dropDeadOption
+ withNothing (start dropdead) ps
start :: Bool -> CommandStart
start dropdead = do
diff --git a/Command/FromKey.hs b/Command/FromKey.hs
index c3d2daafe2..7eb62fa4e0 100644
--- a/Command/FromKey.hs
+++ b/Command/FromKey.hs
@@ -7,8 +7,6 @@
module Command.FromKey where
-import System.PosixCompat.Files
-
import Common.Annex
import Command
import qualified Annex.Queue
@@ -20,8 +18,8 @@ def = [notDirect $ notBareRepo $
command "fromkey" (paramPair paramKey paramPath) seek
SectionPlumbing "adds a file using a specific key"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start (keyname:file:[]) = do
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index 2ab47b5627..dfe1a9ab64 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -9,8 +9,6 @@
module Command.Fsck where
-import System.PosixCompat.Files
-
import Common.Annex
import Command
import qualified Annex
@@ -25,15 +23,14 @@ import Annex.Perms
import Annex.Link
import Logs.Location
import Logs.Trust
+import Config.NumCopies
import Annex.UUID
import Utility.DataUnits
import Utility.FileMode
import Config
-import qualified Option
import Types.Key
import Utility.HumanTime
import Git.FilePath
-import GitAnnex.Options hiding (fromOption)
#ifndef mingw32_HOST_OS
import System.Posix.Process (getProcessID)
@@ -49,41 +46,42 @@ def :: [Command]
def = [withOptions fsckOptions $ command "fsck" paramPaths seek
SectionMaintenance "check for problems"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "check remote"
+fsckFromOption :: Option
+fsckFromOption = fieldOption ['f'] "from" paramRemote "check remote"
startIncrementalOption :: Option
-startIncrementalOption = Option.flag ['S'] "incremental" "start an incremental fsck"
+startIncrementalOption = flagOption ['S'] "incremental" "start an incremental fsck"
moreIncrementalOption :: Option
-moreIncrementalOption = Option.flag ['m'] "more" "continue an incremental fsck"
+moreIncrementalOption = flagOption ['m'] "more" "continue an incremental fsck"
incrementalScheduleOption :: Option
-incrementalScheduleOption = Option.field [] "incremental-schedule" paramTime
+incrementalScheduleOption = fieldOption [] "incremental-schedule" paramTime
"schedule incremental fscking"
fsckOptions :: [Option]
fsckOptions =
- [ fromOption
+ [ fsckFromOption
, startIncrementalOption
, moreIncrementalOption
, incrementalScheduleOption
] ++ keyOptions
-seek :: [CommandSeek]
-seek =
- [ withField fromOption Remote.byNameWithUUID $ \from ->
- withIncremental $ \i ->
- withKeyOptions (startKey i) $
- withFilesInGit $ whenAnnexed $ start from i
- ]
+seek :: CommandSeek
+seek ps = do
+ from <- getOptionField fsckFromOption Remote.byNameWithUUID
+ i <- getIncremental
+ withKeyOptions
+ (startKey i)
+ (withFilesInGit $ whenAnnexed $ start from i)
+ ps
-withIncremental :: (Incremental -> CommandSeek) -> CommandSeek
-withIncremental = withValue $ do
+getIncremental :: Annex Incremental
+getIncremental = do
i <- maybe (return False) (checkschedule . parseDuration)
- =<< Annex.getField (Option.name incrementalScheduleOption)
- starti <- Annex.getFlag (Option.name startIncrementalOption)
- morei <- Annex.getFlag (Option.name moreIncrementalOption)
+ =<< Annex.getField (optionName incrementalScheduleOption)
+ starti <- Annex.getFlag (optionName startIncrementalOption)
+ morei <- Annex.getFlag (optionName moreIncrementalOption)
case (i, starti, morei) of
(False, False, False) -> return NonIncremental
(False, True, _) -> startIncremental
@@ -110,14 +108,14 @@ withIncremental = withValue $ do
start :: Maybe Remote -> Incremental -> FilePath -> (Key, Backend) -> CommandStart
start from inc file (key, backend) = do
- numcopies <- numCopies file
+ numcopies <- getFileNumCopies file
case from of
Nothing -> go $ perform key file backend numcopies
Just r -> go $ performRemote key file backend numcopies r
where
go = runFsck inc file key
-perform :: Key -> FilePath -> Backend -> Maybe Int -> Annex Bool
+perform :: Key -> FilePath -> Backend -> NumCopies -> Annex Bool
perform key file backend numcopies = check
-- order matters
[ fixLink key file
@@ -131,7 +129,7 @@ perform key file backend numcopies = check
{- To fsck a remote, the content is retrieved to a tmp file,
- and checked locally. -}
-performRemote :: Key -> FilePath -> Backend -> Maybe Int -> Remote -> Annex Bool
+performRemote :: Key -> FilePath -> Backend -> NumCopies -> Remote -> Annex Bool
performRemote key file backend numcopies remote =
dispatch =<< Remote.hasKey remote key
where
@@ -367,27 +365,26 @@ checkBackendOr' bad backend key file postcheck =
, return True
)
-checkKeyNumCopies :: Key -> FilePath -> Maybe Int -> Annex Bool
+checkKeyNumCopies :: Key -> FilePath -> NumCopies -> Annex Bool
checkKeyNumCopies key file numcopies = do
- needed <- getNumCopies numcopies
(untrustedlocations, safelocations) <- trustPartition UnTrusted =<< Remote.keyLocations key
- let present = length safelocations
- if present < needed
+ let present = NumCopies (length safelocations)
+ if present < numcopies
then do
ppuuids <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
- warning $ missingNote file present needed ppuuids
+ warning $ missingNote file present numcopies ppuuids
return False
else return True
-missingNote :: String -> Int -> Int -> String -> String
-missingNote file 0 _ [] =
+missingNote :: String -> NumCopies -> NumCopies -> String -> String
+missingNote file (NumCopies 0) _ [] =
"** No known copies exist of " ++ file
-missingNote file 0 _ untrusted =
+missingNote file (NumCopies 0) _ untrusted =
"Only these untrusted locations may have copies of " ++ file ++
"\n" ++ untrusted ++
"Back it up to trusted locations with git-annex copy."
missingNote file present needed [] =
- "Only " ++ show present ++ " of " ++ show needed ++
+ "Only " ++ show (fromNumCopies present) ++ " of " ++ show (fromNumCopies needed) ++
" trustworthy copies exist of " ++ file ++
"\nBack it up with git-annex copy."
missingNote file present needed untrusted =
@@ -481,10 +478,9 @@ recordStartTime = do
createAnnexDirectory $ parentDir f
liftIO $ do
nukeFile f
- h <- openFile f WriteMode
- t <- modificationTime <$> getFileStatus f
- hPutStr h $ showTime $ realToFrac t
- hClose h
+ withFile f WriteMode $ \h -> do
+ t <- modificationTime <$> getFileStatus f
+ hPutStr h $ showTime $ realToFrac t
where
showTime :: POSIXTime -> String
showTime = show
diff --git a/Command/FuzzTest.hs b/Command/FuzzTest.hs
index 34e74b4334..08103edc87 100644
--- a/Command/FuzzTest.hs
+++ b/Command/FuzzTest.hs
@@ -25,8 +25,8 @@ def :: [Command]
def = [ notBareRepo $ command "fuzztest" paramNothing seek SectionPlumbing
"generates fuzz test files"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
@@ -146,13 +146,6 @@ genFuzzFile = do
genFuzzDir :: IO FuzzDir
genFuzzDir = mkFuzzDir <$> (getStdRandom (randomR (1,16)) :: IO Int)
-localFile :: FilePath -> Bool
-localFile f
- | isAbsolute f = False
- | ".." `isInfixOf` f = False
- | ".git" `isPrefixOf` f = False
- | otherwise = True
-
data TimeStampedFuzzAction
= Started UTCTime FuzzAction
| Finished UTCTime Bool
diff --git a/Command/GCryptSetup.hs b/Command/GCryptSetup.hs
index bdd770f159..2448467fdd 100644
--- a/Command/GCryptSetup.hs
+++ b/Command/GCryptSetup.hs
@@ -18,8 +18,8 @@ def = [dontCheck repoExists $ noCommit $
command "gcryptsetup" paramValue seek
SectionPlumbing "sets up gcrypt repository"]
-seek :: [CommandSeek]
-seek = [withStrings start]
+seek :: CommandSeek
+seek = withStrings start
start :: String -> CommandStart
start gcryptid = next $ next $ do
diff --git a/Command/Get.hs b/Command/Get.hs
index 9adf79393c..f436b15b56 100644
--- a/Command/Get.hs
+++ b/Command/Get.hs
@@ -12,10 +12,9 @@ import Command
import qualified Remote
import Annex.Content
import Logs.Transfer
+import Config.NumCopies
import Annex.Wanted
-import GitAnnex.Options
import qualified Command.Move
-import Types.Key
def :: [Command]
def = [withOptions getOptions $ command "get" paramPaths seek
@@ -24,17 +23,18 @@ def = [withOptions getOptions $ command "get" paramPaths seek
getOptions :: [Option]
getOptions = fromOption : keyOptions
-seek :: [CommandSeek]
-seek =
- [ withField fromOption Remote.byNameWithUUID $ \from ->
- withKeyOptions (startKeys from) $
- withFilesInGit $ whenAnnexed $ start from
- ]
+seek :: CommandSeek
+seek ps = do
+ from <- getOptionField fromOption Remote.byNameWithUUID
+ withKeyOptions
+ (startKeys from)
+ (withFilesInGit $ whenAnnexed $ start from)
+ ps
start :: Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart
start from file (key, _) = start' expensivecheck from key (Just file)
where
- expensivecheck = checkAuto (numCopiesCheck file key (<) <||> wantGet False (Just file))
+ expensivecheck = checkAuto (numCopiesCheck file key (<) <||> wantGet False (Just key) (Just file))
startKeys :: Maybe Remote -> Key -> CommandStart
startKeys from key = start' (return True) from key Nothing
@@ -49,7 +49,7 @@ start' expensivecheck from key afile = stopUnless (not <$> inAnnex key) $
go $ Command.Move.fromPerform src False key afile
where
go a = do
- showStart "get" (fromMaybe (key2file key) afile)
+ showStart' "get" key afile
next a
perform :: Key -> AssociatedFile -> CommandPerform
@@ -59,7 +59,11 @@ perform key afile = stopUnless (getViaTmp key $ getKeyFile key afile) $
{- Try to find a copy of the file in one of the remotes,
- and copy it to here. -}
getKeyFile :: Key -> AssociatedFile -> FilePath -> Annex Bool
-getKeyFile key afile dest = dispatch =<< Remote.keyPossibilities key
+getKeyFile key afile dest = getKeyFile' key afile dest
+ =<< Remote.keyPossibilities key
+
+getKeyFile' :: Key -> AssociatedFile -> FilePath -> [Remote] -> Annex Bool
+getKeyFile' key afile dest = dispatch
where
dispatch [] = do
showNote "not available"
diff --git a/Command/Group.hs b/Command/Group.hs
index 4c0bf4899a..b0dbc14653 100644
--- a/Command/Group.hs
+++ b/Command/Group.hs
@@ -19,8 +19,8 @@ def :: [Command]
def = [command "group" (paramPair paramRemote paramDesc) seek
SectionSetup "add a repository to a group"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start (name:g:[]) = do
diff --git a/Command/Help.hs b/Command/Help.hs
index 71e767663b..7998ed7965 100644
--- a/Command/Help.hs
+++ b/Command/Help.hs
@@ -18,7 +18,6 @@ import qualified Command.Copy
import qualified Command.Sync
import qualified Command.Whereis
import qualified Command.Fsck
-import GitAnnex.Options
import System.Console.GetOpt
@@ -26,8 +25,8 @@ def :: [Command]
def = [noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "help" paramNothing seek SectionQuery "display help"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start params = do
@@ -42,7 +41,7 @@ start' ["options"] = showCommonOptions
start' _ = showGeneralHelp
showCommonOptions :: IO ()
-showCommonOptions = putStrLn $ usageInfo "Common options:" options
+showCommonOptions = putStrLn $ usageInfo "Common options:" gitAnnexOptions
showGeneralHelp :: IO ()
showGeneralHelp = putStrLn $ unlines
diff --git a/Command/Import.hs b/Command/Import.hs
index dcf2b0fa0b..db3601a1b3 100644
--- a/Command/Import.hs
+++ b/Command/Import.hs
@@ -7,13 +7,10 @@
module Command.Import where
-import System.PosixCompat.Files
-
import Common.Annex
import Command
import qualified Annex
import qualified Command.Add
-import qualified Option
import Utility.CopyFile
import Backend
import Remote
@@ -32,16 +29,16 @@ opts =
]
duplicateOption :: Option
-duplicateOption = Option.flag [] "duplicate" "do not delete source files"
+duplicateOption = flagOption [] "duplicate" "do not delete source files"
deduplicateOption :: Option
-deduplicateOption = Option.flag [] "deduplicate" "delete source files whose content was imported before"
+deduplicateOption = flagOption [] "deduplicate" "delete source files whose content was imported before"
cleanDuplicatesOption :: Option
-cleanDuplicatesOption = Option.flag [] "clean-duplicates" "delete duplicate source files (import nothing)"
+cleanDuplicatesOption = flagOption [] "clean-duplicates" "delete duplicate source files (import nothing)"
skipDuplicatesOption :: Option
-skipDuplicatesOption = Option.flag [] "skip-duplicates" "import only new files"
+skipDuplicatesOption = flagOption [] "skip-duplicates" "import only new files"
data DuplicateMode = Default | Duplicate | DeDuplicate | CleanDuplicates | SkipDuplicates
deriving (Eq)
@@ -53,7 +50,7 @@ getDuplicateMode = gen
<*> getflag cleanDuplicatesOption
<*> getflag skipDuplicatesOption
where
- getflag = Annex.getFlag . Option.name
+ getflag = Annex.getFlag . optionName
gen False False False False = Default
gen True False False False = Duplicate
gen False True False False = DeDuplicate
@@ -61,8 +58,10 @@ getDuplicateMode = gen
gen False False False True = SkipDuplicates
gen _ _ _ _ = error "bad combination of --duplicate, --deduplicate, --clean-duplicates, --skip-duplicates"
-seek :: [CommandSeek]
-seek = [withValue getDuplicateMode $ \mode -> withPathContents $ start mode]
+seek :: CommandSeek
+seek ps = do
+ mode <- getDuplicateMode
+ withPathContents (start mode) ps
start :: DuplicateMode -> (FilePath, FilePath) -> CommandStart
start mode (srcfile, destfile) =
diff --git a/Command/ImportFeed.hs b/Command/ImportFeed.hs
index d16362205a..dfa89b3446 100644
--- a/Command/ImportFeed.hs
+++ b/Command/ImportFeed.hs
@@ -21,7 +21,6 @@ import qualified Annex
import Command
import qualified Annex.Url as Url
import Logs.Web
-import qualified Option
import qualified Utility.Format
import Utility.Tmp
import Command.AddUrl (addUrlFile, relaxedOption)
@@ -39,13 +38,14 @@ def = [notBareRepo $ withOptions [templateOption, relaxedOption] $
SectionCommon "import files from podcast feeds"]
templateOption :: Option
-templateOption = Option.field [] "template" paramFormat "template for filenames"
+templateOption = fieldOption [] "template" paramFormat "template for filenames"
-seek :: [CommandSeek]
-seek = [withField templateOption return $ \tmpl ->
- withFlag relaxedOption $ \relaxed ->
- withValue (getCache tmpl) $ \cache ->
- withStrings $ start relaxed cache]
+seek :: CommandSeek
+seek ps = do
+ tmpl <- getOptionField templateOption return
+ relaxed <- getOptionFlag relaxedOption
+ cache <- getCache tmpl
+ withStrings (start relaxed cache) ps
start :: Bool -> Cache -> URLString -> CommandStart
start relaxed cache url = do
diff --git a/Command/InAnnex.hs b/Command/InAnnex.hs
index 4410d722d0..11cbdb73dd 100644
--- a/Command/InAnnex.hs
+++ b/Command/InAnnex.hs
@@ -15,8 +15,8 @@ def :: [Command]
def = [noCommit $ command "inannex" (paramRepeating paramKey) seek
SectionPlumbing "checks if keys are present in the annex"]
-seek :: [CommandSeek]
-seek = [withKeys start]
+seek :: CommandSeek
+seek = withKeys start
start :: Key -> CommandStart
start key = inAnnexSafe key >>= dispatch
diff --git a/Command/Indirect.hs b/Command/Indirect.hs
index a8669fe505..c0dd57959b 100644
--- a/Command/Indirect.hs
+++ b/Command/Indirect.hs
@@ -7,7 +7,6 @@
module Command.Indirect where
-import System.PosixCompat.Files
import Control.Exception.Extensible
import Common.Annex
@@ -23,7 +22,7 @@ import Annex.Content
import Annex.Content.Direct
import Annex.CatFile
import Annex.Exception
-import Init
+import Annex.Init
import qualified Command.Add
def :: [Command]
@@ -31,8 +30,8 @@ def = [notBareRepo $ noDaemonRunning $
command "indirect" paramNothing seek
SectionSetup "switch repository to indirect mode"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = ifM isDirect
diff --git a/Command/Info.hs b/Command/Info.hs
index d465f2d841..98cc49efa9 100644
--- a/Command/Info.hs
+++ b/Command/Info.hs
@@ -14,7 +14,6 @@ import qualified Data.Map as M
import Text.JSON
import Data.Tuple
import Data.Ord
-import System.PosixCompat.Files
import Common.Annex
import qualified Remote
@@ -28,6 +27,7 @@ import Annex.Content
import Types.Key
import Logs.UUID
import Logs.Trust
+import Config.NumCopies
import Remote
import Config
import Utility.Percentage
@@ -70,11 +70,12 @@ data StatInfo = StatInfo
type StatState = StateT StatInfo Annex
def :: [Command]
-def = [noCommit $ command "info" paramPaths seek
- SectionQuery "shows general information about the annex"]
+def = [noCommit $ withOptions [jsonOption] $
+ command "info" paramPaths seek SectionQuery
+ "shows general information about the annex"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [FilePath] -> CommandStart
start [] = do
@@ -310,7 +311,7 @@ getLocalStatInfo dir = do
where
initial = (emptyKeyData, emptyKeyData, emptyNumCopiesStats)
update matcher fast key file vs@(presentdata, referenceddata, numcopiesstats) =
- ifM (matcher $ FileInfo file file)
+ ifM (matcher $ MatchingFile $ FileInfo file file)
( do
!presentdata' <- ifM (inAnnex key)
( return $ addKey key presentdata
diff --git a/Command/Init.hs b/Command/Init.hs
index 3db9a6be3e..e8d9af1674 100644
--- a/Command/Init.hs
+++ b/Command/Init.hs
@@ -9,14 +9,14 @@ module Command.Init where
import Common.Annex
import Command
-import Init
+import Annex.Init
def :: [Command]
def = [dontCheck repoExists $
command "init" paramDesc seek SectionSetup "initialize git-annex"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start ws = do
diff --git a/Command/InitRemote.hs b/Command/InitRemote.hs
index 5a240f8003..79fbcf39c5 100644
--- a/Command/InitRemote.hs
+++ b/Command/InitRemote.hs
@@ -24,8 +24,8 @@ def = [command "initremote"
(paramPair paramName $ paramOptional $ paramRepeating paramKeyValue)
seek SectionSetup "creates a special (non-git) remote"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start [] = error "Specify a name for the remote."
diff --git a/Command/List.hs b/Command/List.hs
index 12c27c0228..ba62513338 100644
--- a/Command/List.hs
+++ b/Command/List.hs
@@ -20,7 +20,6 @@ import Remote
import Logs.Trust
import Logs.UUID
import Annex.UUID
-import qualified Option
import qualified Annex
import Git.Types (RemoteName)
@@ -29,16 +28,16 @@ def = [noCommit $ withOptions [allrepos] $ command "list" paramPaths seek
SectionQuery "show which remotes contain files"]
allrepos :: Option
-allrepos = Option.flag [] "allrepos" "show all repositories, not only remotes"
+allrepos = flagOption [] "allrepos" "show all repositories, not only remotes"
-seek :: [CommandSeek]
-seek =
- [ withValue getList $ withNothing . startHeader
- , withValue getList $ withFilesInGit . whenAnnexed . start
- ]
+seek :: CommandSeek
+seek ps = do
+ list <- getList
+ printHeader list
+ withFilesInGit (whenAnnexed $ start list) ps
getList :: Annex [(UUID, RemoteName, TrustLevel)]
-getList = ifM (Annex.getFlag $ Option.name allrepos)
+getList = ifM (Annex.getFlag $ optionName allrepos)
( nubBy ((==) `on` fst3) <$> ((++) <$> getRemotes <*> getAll)
, getRemotes
)
@@ -58,10 +57,8 @@ getList = ifM (Annex.getFlag $ Option.name allrepos)
return $ sortBy (comparing snd3) $
filter (\t -> thd3 t /= DeadTrusted) rs3
-startHeader :: [(UUID, RemoteName, TrustLevel)] -> CommandStart
-startHeader l = do
- liftIO $ putStrLn $ header $ map (\(_, n, t) -> (n, t)) l
- stop
+printHeader :: [(UUID, RemoteName, TrustLevel)] -> Annex ()
+printHeader l = liftIO $ putStrLn $ header $ map (\(_, n, t) -> (n, t)) l
start :: [(UUID, RemoteName, TrustLevel)] -> FilePath -> (Key, Backend) -> CommandStart
start l file (key, _) = do
diff --git a/Command/Lock.hs b/Command/Lock.hs
index bceba4a919..e6733dcb1b 100644
--- a/Command/Lock.hs
+++ b/Command/Lock.hs
@@ -16,8 +16,10 @@ def :: [Command]
def = [notDirect $ command "lock" paramPaths seek SectionCommon
"undo unlock command"]
-seek :: [CommandSeek]
-seek = [withFilesUnlocked start, withFilesUnlockedToBeCommitted start]
+seek :: CommandSeek
+seek ps = do
+ withFilesUnlocked start ps
+ withFilesUnlockedToBeCommitted start ps
start :: FilePath -> CommandStart
start file = do
diff --git a/Command/Log.hs b/Command/Log.hs
index f3a5becb8a..1dd5aa51ab 100644
--- a/Command/Log.hs
+++ b/Command/Log.hs
@@ -24,7 +24,6 @@ import qualified Annex.Branch
import qualified Git
import Git.Command
import qualified Remote
-import qualified Option
import qualified Annex
data RefChange = RefChange
@@ -44,25 +43,26 @@ options = passthruOptions ++ [gourceOption]
passthruOptions :: [Option]
passthruOptions = map odate ["since", "after", "until", "before"] ++
- [ Option.field ['n'] "max-count" paramNumber
+ [ fieldOption ['n'] "max-count" paramNumber
"limit number of logs displayed"
]
where
- odate n = Option.field [] n paramDate $ "show log " ++ n ++ " date"
+ odate n = fieldOption [] n paramDate $ "show log " ++ n ++ " date"
gourceOption :: Option
-gourceOption = Option.flag [] "gource" "format output for gource"
+gourceOption = flagOption [] "gource" "format output for gource"
-seek :: [CommandSeek]
-seek = [withValue Remote.uuidDescriptions $ \m ->
- withValue (liftIO getCurrentTimeZone) $ \zone ->
- withValue (concat <$> mapM getoption passthruOptions) $ \os ->
- withFlag gourceOption $ \gource ->
- withFilesInGit $ whenAnnexed $ start m zone os gource]
+seek :: CommandSeek
+seek ps = do
+ m <- Remote.uuidDescriptions
+ zone <- liftIO getCurrentTimeZone
+ os <- concat <$> mapM getoption passthruOptions
+ gource <- getOptionFlag gourceOption
+ withFilesInGit (whenAnnexed $ start m zone os gource) ps
where
getoption o = maybe [] (use o) <$>
- Annex.getField (Option.name o)
- use o v = [Param ("--" ++ Option.name o), Param v]
+ Annex.getField (optionName o)
+ use o v = [Param ("--" ++ optionName o), Param v]
start :: M.Map UUID String -> TimeZone -> [CommandParam] -> Bool ->
FilePath -> (Key, Backend) -> CommandStart
diff --git a/Command/LookupKey.hs b/Command/LookupKey.hs
index aa83266cb1..814c5d2d77 100644
--- a/Command/LookupKey.hs
+++ b/Command/LookupKey.hs
@@ -17,8 +17,8 @@ def = [notBareRepo $ noCommit $ noMessages $
command "lookupkey" (paramRepeating paramFile) seek
SectionPlumbing "looks up key used for file"]
-seek :: [CommandSeek]
-seek = [withStrings start]
+seek :: CommandSeek
+seek = withStrings start
start :: String -> CommandStart
start file = do
diff --git a/Command/Map.hs b/Command/Map.hs
index 575e321228..9b80d2035d 100644
--- a/Command/Map.hs
+++ b/Command/Map.hs
@@ -31,8 +31,8 @@ def = [dontCheck repoExists $
command "map" paramNothing seek SectionQuery
"generate map of repositories"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
diff --git a/Command/Merge.hs b/Command/Merge.hs
index 31db7a99f9..51a8b9c527 100644
--- a/Command/Merge.hs
+++ b/Command/Merge.hs
@@ -17,11 +17,10 @@ def :: [Command]
def = [command "merge" paramNothing seek SectionMaintenance
"automatically merge changes from remotes"]
-seek :: [CommandSeek]
-seek =
- [ withNothing mergeBranch
- , withNothing mergeSynced
- ]
+seek :: CommandSeek
+seek ps = do
+ withNothing mergeBranch ps
+ withNothing mergeSynced ps
mergeBranch :: CommandStart
mergeBranch = do
diff --git a/Command/Migrate.hs b/Command/Migrate.hs
index 0fdf0e8176..c14c07bddb 100644
--- a/Command/Migrate.hs
+++ b/Command/Migrate.hs
@@ -22,8 +22,8 @@ def = [notDirect $
command "migrate" paramPaths seek
SectionUtility "switch data to different backend"]
-seek :: [CommandSeek]
-seek = [withFilesInGit $ whenAnnexed start]
+seek :: CommandSeek
+seek = withFilesInGit $ whenAnnexed start
start :: FilePath -> (Key, Backend) -> CommandStart
start file (key, oldbackend) = do
diff --git a/Command/Mirror.hs b/Command/Mirror.hs
index fb829bcb02..4a7a8dd991 100644
--- a/Command/Mirror.hs
+++ b/Command/Mirror.hs
@@ -9,34 +9,33 @@ module Command.Mirror where
import Common.Annex
import Command
-import GitAnnex.Options
import qualified Command.Move
import qualified Command.Drop
import qualified Command.Get
import qualified Remote
import Annex.Content
import qualified Annex
+import Config.NumCopies
def :: [Command]
def = [withOptions (fromToOptions ++ keyOptions) $
command "mirror" paramPaths seek
SectionCommon "mirror content of files to/from another repository"]
-seek :: [CommandSeek]
-seek =
- [ withField toOption Remote.byNameWithUUID $ \to ->
- withField fromOption Remote.byNameWithUUID $ \from ->
- withKeyOptions (startKey Nothing to from Nothing) $
- withFilesInGit $ whenAnnexed $ start to from
- ]
+seek :: CommandSeek
+seek ps = do
+ to <- getOptionField toOption Remote.byNameWithUUID
+ from <- getOptionField fromOption Remote.byNameWithUUID
+ withKeyOptions
+ (startKey to from Nothing)
+ (withFilesInGit $ whenAnnexed $ start to from)
+ ps
start :: Maybe Remote -> Maybe Remote -> FilePath -> (Key, Backend) -> CommandStart
-start to from file (key, _backend) = do
- numcopies <- numCopies file
- startKey numcopies to from (Just file) key
+start to from file (key, _backend) = startKey to from (Just file) key
-startKey :: Maybe Int -> Maybe Remote -> Maybe Remote -> Maybe FilePath -> Key -> CommandStart
-startKey numcopies to from afile key = do
+startKey :: Maybe Remote -> Maybe Remote -> Maybe FilePath -> Key -> CommandStart
+startKey to from afile key = do
noAuto
case (from, to) of
(Nothing, Nothing) -> error "specify either --from or --to"
@@ -48,7 +47,9 @@ startKey numcopies to from afile key = do
error "--auto is not supported for mirror"
mirrorto r = ifM (inAnnex key)
( Command.Move.toStart r False afile key
- , Command.Drop.startRemote afile numcopies key r
+ , do
+ numcopies <- getnumcopies
+ Command.Drop.startRemote afile numcopies key r
)
mirrorfrom r = do
haskey <- Remote.hasKey r key
@@ -56,6 +57,9 @@ startKey numcopies to from afile key = do
Left _ -> stop
Right True -> Command.Get.start' (return True) Nothing key afile
Right False -> ifM (inAnnex key)
- ( Command.Drop.startLocal afile numcopies key Nothing
+ ( do
+ numcopies <- getnumcopies
+ Command.Drop.startLocal afile numcopies key Nothing
, stop
)
+ getnumcopies = maybe getNumCopies getFileNumCopies afile
diff --git a/Command/Move.hs b/Command/Move.hs
index 7d11b5abd5..af3623da0c 100644
--- a/Command/Move.hs
+++ b/Command/Move.hs
@@ -16,8 +16,6 @@ import qualified Remote
import Annex.UUID
import Logs.Presence
import Logs.Transfer
-import GitAnnex.Options
-import Types.Key
def :: [Command]
def = [withOptions moveOptions $ command "move" paramPaths seek
@@ -26,13 +24,14 @@ def = [withOptions moveOptions $ command "move" paramPaths seek
moveOptions :: [Option]
moveOptions = fromToOptions ++ keyOptions
-seek :: [CommandSeek]
-seek =
- [ withField toOption Remote.byNameWithUUID $ \to ->
- withField fromOption Remote.byNameWithUUID $ \from ->
- withKeyOptions (startKey to from True) $
- withFilesInGit $ whenAnnexed $ start to from True
- ]
+seek :: CommandSeek
+seek ps = do
+ to <- getOptionField toOption Remote.byNameWithUUID
+ from <- getOptionField fromOption Remote.byNameWithUUID
+ withKeyOptions
+ (startKey to from True)
+ (withFilesInGit $ whenAnnexed $ start to from True)
+ ps
start :: Maybe Remote -> Maybe Remote -> Bool -> FilePath -> (Key, Backend) -> CommandStart
start to from move file (key, _) = start' to from move (Just file) key
@@ -53,17 +52,14 @@ start' to from move afile key = do
"--auto is not supported for move"
showMoveAction :: Bool -> Key -> AssociatedFile -> Annex ()
-showMoveAction True _ (Just file) = showStart "move" file
-showMoveAction False _ (Just file) = showStart "copy" file
-showMoveAction True key Nothing = showStart "move" (key2file key)
-showMoveAction False key Nothing = showStart "copy" (key2file key)
+showMoveAction move = showStart' (if move then "move" else "copy")
{- Moves (or copies) the content of an annexed file to a remote.
-
- If the remote already has the content, it is still removed from
- the current repository.
-
- - Note that unlike drop, this does not honor annex.numcopies.
+ - Note that unlike drop, this does not honor numcopies.
- A file's content can be moved even if there are insufficient copies to
- allow it to be dropped.
-}
diff --git a/Command/NumCopies.hs b/Command/NumCopies.hs
new file mode 100644
index 0000000000..b7323ae357
--- /dev/null
+++ b/Command/NumCopies.hs
@@ -0,0 +1,56 @@
+{- git-annex command
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Command.NumCopies where
+
+import Common.Annex
+import qualified Annex
+import Command
+import Config.NumCopies
+import Types.Messages
+
+def :: [Command]
+def = [command "numcopies" paramNumber seek
+ SectionSetup "configure desired number of copies"]
+
+seek :: CommandSeek
+seek = withWords start
+
+start :: [String] -> CommandStart
+start [] = startGet
+start [s] = do
+ case readish s of
+ Nothing -> error $ "Bad number: " ++ s
+ Just n
+ | n > 0 -> startSet n
+ | n == 0 -> ifM (Annex.getState Annex.force)
+ ( startSet n
+ , error "Setting numcopies to 0 is very unsafe. You will lose data! If you really want to do that, specify --force."
+ )
+ | otherwise -> error "Number cannot be negative!"
+start _ = error "Specify a single number."
+
+startGet :: CommandStart
+startGet = next $ next $ do
+ Annex.setOutput QuietOutput
+ v <- getGlobalNumCopies
+ case v of
+ Just n -> liftIO $ putStrLn $ show $ fromNumCopies n
+ Nothing -> do
+ liftIO $ putStrLn $ "global numcopies is not set"
+ old <- deprecatedNumCopies
+ case old of
+ Nothing -> liftIO $ putStrLn "(default is 1)"
+ Just n -> liftIO $ putStrLn $ "(deprecated git config annex.numcopies is set to " ++ show (fromNumCopies n) ++ " locally)"
+ return True
+
+startSet :: Int -> CommandStart
+startSet n = do
+ showStart "numcopies" (show n)
+ next $ next $ do
+ setGlobalNumCopies $ NumCopies n
+ return True
diff --git a/Command/PreCommit.hs b/Command/PreCommit.hs
index eed2f491c6..388d065c0f 100644
--- a/Command/PreCommit.hs
+++ b/Command/PreCommit.hs
@@ -9,6 +9,7 @@ module Command.PreCommit where
import Common.Annex
import Command
+import Config
import qualified Command.Add
import qualified Command.Fix
import Annex.Direct
@@ -17,19 +18,20 @@ def :: [Command]
def = [command "pre-commit" paramPaths seek SectionPlumbing
"run by git pre-commit hook"]
-seek :: [CommandSeek]
-seek =
- -- fix symlinks to files being committed
- [ whenNotDirect $ withFilesToBeCommitted $ whenAnnexed Command.Fix.start
- -- inject unlocked files into the annex
- , whenNotDirect $ withFilesUnlockedToBeCommitted startIndirect
+seek :: CommandSeek
+seek ps = ifM isDirect
-- update direct mode mappings for committed files
- , whenDirect $ withWords startDirect
- ]
+ ( withWords startDirect ps
+ , do
+ -- fix symlinks to files being committed
+ withFilesToBeCommitted (whenAnnexed Command.Fix.start) ps
+ -- inject unlocked files into the annex
+ withFilesUnlockedToBeCommitted startIndirect ps
+ )
startIndirect :: FilePath -> CommandStart
startIndirect file = next $ do
- unlessM (doCommand $ Command.Add.start file) $
+ unlessM (callCommandAction $ Command.Add.start file) $
error $ "failed to add " ++ file ++ "; canceling commit"
next $ return True
diff --git a/Command/ReKey.hs b/Command/ReKey.hs
index 7448ba97e6..805300f9f8 100644
--- a/Command/ReKey.hs
+++ b/Command/ReKey.hs
@@ -22,8 +22,8 @@ def = [notDirect $ command "rekey"
(paramOptional $ paramRepeating $ paramPair paramPath paramKey)
seek SectionPlumbing "change keys used for files"]
-seek :: [CommandSeek]
-seek = [withPairs start]
+seek :: CommandSeek
+seek = withPairs start
start :: (FilePath, String) -> CommandStart
start (file, keyname) = ifAnnexed file go stop
diff --git a/Command/RecvKey.hs b/Command/RecvKey.hs
index 3b2a8c496a..1794596c57 100644
--- a/Command/RecvKey.hs
+++ b/Command/RecvKey.hs
@@ -7,8 +7,6 @@
module Command.RecvKey where
-import System.PosixCompat.Files
-
import Common.Annex
import Command
import CmdLine
@@ -17,7 +15,7 @@ import Annex
import Utility.Rsync
import Logs.Transfer
import Command.SendKey (fieldTransfer)
-import qualified Fields
+import qualified CmdLine.GitAnnexShell.Fields as Fields
import qualified Types.Key
import qualified Types.Backend
import qualified Backend
@@ -26,8 +24,8 @@ def :: [Command]
def = [noCommit $ command "recvkey" paramKey seek
SectionPlumbing "runs rsync in server mode to receive content"]
-seek :: [CommandSeek]
-seek = [withKeys start]
+seek :: CommandSeek
+seek = withKeys start
start :: Key -> CommandStart
start key = ifM (inAnnex key)
diff --git a/Command/Reinject.hs b/Command/Reinject.hs
index c49af00601..1609c60974 100644
--- a/Command/Reinject.hs
+++ b/Command/Reinject.hs
@@ -17,8 +17,8 @@ def :: [Command]
def = [command "reinject" (paramPair "SRC" "DEST") seek
SectionUtility "sets content of annexed file"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [FilePath] -> CommandStart
start (src:dest:[])
diff --git a/Command/Repair.hs b/Command/Repair.hs
index 0f02a3ab32..c873176851 100644
--- a/Command/Repair.hs
+++ b/Command/Repair.hs
@@ -20,8 +20,8 @@ def :: [Command]
def = [noCommit $ dontCheck repoExists $
command "repair" paramNothing seek SectionMaintenance "recover broken git repository"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = next $ next $ runRepair =<< Annex.getState Annex.force
diff --git a/Command/RmUrl.hs b/Command/RmUrl.hs
index d3ded38a39..3f304b76ed 100644
--- a/Command/RmUrl.hs
+++ b/Command/RmUrl.hs
@@ -16,8 +16,8 @@ def = [notBareRepo $
command "rmurl" (paramPair paramFile paramUrl) seek
SectionCommon "record file is not available at url"]
-seek :: [CommandSeek]
-seek = [withPairs start]
+seek :: CommandSeek
+seek = withPairs start
start :: (FilePath, String) -> CommandStart
start (file, url) = flip whenAnnexed file $ \_ (key, _) -> do
diff --git a/Command/Schedule.hs b/Command/Schedule.hs
index db654f2911..a088dbef8b 100644
--- a/Command/Schedule.hs
+++ b/Command/Schedule.hs
@@ -21,8 +21,8 @@ def :: [Command]
def = [command "schedule" (paramPair paramRemote (paramOptional paramExpression)) seek
SectionSetup "get or set scheduled jobs"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start = parse
diff --git a/Command/Semitrust.hs b/Command/Semitrust.hs
index e205636726..26ce6961bb 100644
--- a/Command/Semitrust.hs
+++ b/Command/Semitrust.hs
@@ -16,8 +16,8 @@ def :: [Command]
def = [command "semitrust" (paramRepeating paramRemote) seek
SectionSetup "return repository to default trust level"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start ws = do
diff --git a/Command/SendKey.hs b/Command/SendKey.hs
index 24b1821c3f..2215b16b2c 100644
--- a/Command/SendKey.hs
+++ b/Command/SendKey.hs
@@ -13,15 +13,15 @@ import Annex.Content
import Annex
import Utility.Rsync
import Logs.Transfer
-import qualified Fields
+import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered
def :: [Command]
def = [noCommit $ command "sendkey" paramKey seek
SectionPlumbing "runs rsync in server mode to send content"]
-seek :: [CommandSeek]
-seek = [withKeys start]
+seek :: CommandSeek
+seek = withKeys start
start :: Key -> CommandStart
start key = do
diff --git a/Command/Status.hs b/Command/Status.hs
index 5dc6259947..cd6c259838 100644
--- a/Command/Status.hs
+++ b/Command/Status.hs
@@ -17,14 +17,12 @@ import qualified Git.Ref
import qualified Git
def :: [Command]
-def = [notBareRepo $ noCommit $ noMessages $
+def = [notBareRepo $ noCommit $ noMessages $ withOptions [jsonOption] $
command "status" paramPaths seek SectionCommon
"show the working tree status"]
-seek :: [CommandSeek]
-seek =
- [ withWords start
- ]
+seek :: CommandSeek
+seek = withWords start
start :: [FilePath] -> CommandStart
start [] = do
@@ -32,11 +30,11 @@ start [] = do
-- given the path to the top of the repository.
cwd <- liftIO getCurrentDirectory
top <- fromRepo Git.repoPath
- next $ perform [relPathDirToFile cwd top]
-start locs = next $ perform locs
+ start' [relPathDirToFile cwd top]
+start locs = start' locs
-perform :: [FilePath] -> CommandPerform
-perform locs = do
+start' :: [FilePath] -> CommandStart
+start' locs = do
(l, cleanup) <- inRepo $ LsFiles.modifiedOthers locs
getstatus <- ifM isDirect
( return statusDirect
@@ -44,7 +42,7 @@ perform locs = do
)
forM_ l $ \f -> maybe noop (showFileStatus f) =<< getstatus f
void $ liftIO cleanup
- next $ return True
+ stop
data Status
= NewFile
@@ -57,7 +55,10 @@ showStatus DeletedFile = "D"
showStatus ModifiedFile = "M"
showFileStatus :: FilePath -> Status -> Annex ()
-showFileStatus f s = liftIO $ putStrLn $ showStatus s ++ " " ++ f
+showFileStatus f s = unlessM (showFullJSON [("status", ss), ("file", f)]) $
+ liftIO $ putStrLn $ ss ++ " " ++ f
+ where
+ ss = showStatus s
statusDirect :: FilePath -> Annex (Maybe Status)
statusDirect f = checkstatus =<< liftIO (catchMaybeIO $ getFileStatus f)
diff --git a/Command/Sync.hs b/Command/Sync.hs
index 38a6a5c6a6..331f5d03ff 100644
--- a/Command/Sync.hs
+++ b/Command/Sync.hs
@@ -1,7 +1,7 @@
{- git-annex command
-
- Copyright 2011 Joachim Breitner
- - Copyright 2011,2012 Joey Hess
+ - Copyright 2011-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -10,10 +10,11 @@ module Command.Sync where
import Common.Annex
import Command
-import qualified Remote
import qualified Annex
import qualified Annex.Branch
import qualified Annex.Queue
+import qualified Remote
+import qualified Types.Remote as Remote
import Annex.Direct
import Annex.CatFile
import Annex.Link
@@ -30,16 +31,29 @@ import Types.Key
import Config
import Annex.ReplaceFile
import Git.FileMode
+import Annex.Wanted
+import Annex.Content
+import Command.Get (getKeyFile')
+import qualified Command.Move
+import Logs.Location
+import Annex.Drop
+import Annex.UUID
import qualified Data.Set as S
import Data.Hash.MD5
import Control.Concurrent.MVar
def :: [Command]
-def = [command "sync" (paramOptional (paramRepeating paramRemote))
- [seek] SectionCommon "synchronize local repository with remotes"]
+def = [withOptions syncOptions $
+ command "sync" (paramOptional (paramRepeating paramRemote))
+ seek SectionCommon "synchronize local repository with remotes"]
+
+syncOptions :: [Option]
+syncOptions = [ contentOption ]
+
+contentOption :: Option
+contentOption = flagOption [] "content" "also transfer file contents"
--- syncing involves several operations, any of which can independently fail
seek :: CommandSeek
seek rs = do
prepMerge
@@ -60,17 +74,36 @@ seek rs = do
let withbranch a = a =<< getbranch
remotes <- syncRemotes rs
- return $ concat
+ let gitremotes = filter Remote.gitSyncableRemote remotes
+ let dataremotes = filter (not . remoteAnnexIgnore . Remote.gitconfig) remotes
+
+ -- Syncing involves many actions, any of which can independently
+ -- fail, without preventing the others from running.
+ seekActions $ return $ concat
[ [ commit ]
, [ withbranch mergeLocal ]
- , [ withbranch (pullRemote remote) | remote <- remotes ]
- , [ mergeAnnex ]
- , [ withbranch pushLocal ]
- , [ withbranch (pushRemote remote) | remote <- remotes ]
+ , map (withbranch . pullRemote) gitremotes
+ , [ mergeAnnex ]
+ ]
+ whenM (Annex.getFlag $ optionName contentOption) $
+ whenM (seekSyncContent dataremotes) $ do
+ -- Transferring content can take a while,
+ -- and other changes can be pushed to the git-annex
+ -- branch on the remotes in the meantime, so pull
+ -- and merge again to avoid our push overwriting
+ -- those changes.
+ seekActions $ return $ concat
+ [ map (withbranch . pullRemote) gitremotes
+ , [ commitAnnex, mergeAnnex ]
+ ]
+ seekActions $ return $ concat
+ [ [ withbranch pushLocal ]
+ , map (withbranch . pushRemote) gitremotes
]
{- Merging may delete the current directory, so go to the top
- - of the repo. -}
+ - of the repo. This also means that sync always acts on all files in the
+ - repository, not just on a subdirectory. -}
prepMerge :: Annex ()
prepMerge = liftIO . setCurrentDirectory =<< fromRepo Git.repoPath
@@ -83,21 +116,17 @@ remoteBranch remote = Git.Ref.underBase $ "refs/remotes/" ++ Remote.name remote
syncRemotes :: [String] -> Annex [Remote]
syncRemotes rs = ifM (Annex.getState Annex.fast) ( nub <$> pickfast , wanted )
where
- pickfast = (++) <$> listed <*> (good =<< fastest <$> available)
+ pickfast = (++) <$> listed <*> (filterM good =<< fastest <$> available)
wanted
- | null rs = good =<< concat . Remote.byCost <$> available
+ | null rs = filterM good =<< concat . Remote.byCost <$> available
| otherwise = listed
- listed = do
- l <- catMaybes <$> mapM (Remote.byName . Just) rs
- let s = filter (not . Remote.syncableRemote) l
- unless (null s) $
- error $ "cannot sync special remotes: " ++
- unwords (map Types.Remote.name s)
- return l
- available = filter Remote.syncableRemote
- . filter (remoteAnnexSync . Types.Remote.gitconfig)
+ listed = catMaybes <$> mapM (Remote.byName . Just) rs
+ available = filter (remoteAnnexSync . Types.Remote.gitconfig)
+ . filter (not . Remote.isXMPPRemote)
<$> Remote.remoteList
- good = filterM $ Remote.Git.repoAvail . Types.Remote.repo
+ good r
+ | Remote.gitSyncableRemote r = Remote.Git.repoAvail $ Types.Remote.repo r
+ | otherwise = return True
fastest = fromMaybe [] . headMaybe . Remote.byCost
commit :: CommandStart
@@ -129,7 +158,7 @@ commitStaged commitmessage = go =<< inRepo Git.Branch.currentUnsafe
go (Just branch) = do
parent <- inRepo $ Git.Ref.sha branch
void $ inRepo $ Git.Branch.commit False commitmessage branch
- (maybe [] (:[]) parent)
+ (maybeToList parent)
return True
mergeLocal :: Maybe Git.Ref -> CommandStart
@@ -265,6 +294,11 @@ pushBranch remote branch g = tryIO (directpush g) `after` syncpush g
, show $ Git.Ref.base $ syncBranch b
]
+commitAnnex :: CommandStart
+commitAnnex = do
+ Annex.Branch.commit "update"
+ stop
+
mergeAnnex :: CommandStart
mergeAnnex = do
void Annex.Branch.forceUpdate
@@ -358,14 +392,10 @@ resolveMerge' u
-- Our side is annexed, other side is not.
(Just keyUs, Nothing) -> do
ifM isDirect
- -- Move newly added non-annexed object
- -- out of direct mode merge directory.
( do
removeoldfile keyUs
makelink keyUs
- d <- fromRepo gitAnnexMergeDir
- liftIO $ rename (d > file) file
- -- cleaup tree after git merge
+ movefromdirectmerge file
, do
unstageoldfile
makelink keyUs
@@ -399,6 +429,31 @@ resolveMerge' u
getKey select = case select (LsFiles.unmergedSha u) of
Nothing -> return Nothing
Just sha -> catKey sha symLinkMode
+
+ {- Move something out of the direct mode merge directory and into
+ - the git work tree.
+ -
+ - On a filesystem not supporting symlinks, this is complicated
+ - because a directory may contain annex links, but just
+ - moving them into the work tree will not let git know they are
+ - symlinks.
+ -
+ - Also, if the content of the file is available, make it available
+ - in direct mode.
+ -}
+ movefromdirectmerge item = do
+ d <- fromRepo gitAnnexMergeDir
+ liftIO $ rename (d > item) item
+ mapM_ setuplink =<< liftIO (dirContentsRecursive item)
+ setuplink f = do
+ v <- getAnnexLinkTarget f
+ case v of
+ Nothing -> noop
+ Just target -> do
+ unlessM (coreSymlinks <$> Annex.getGitConfig) $
+ addAnnexLink target f
+ maybe noop (flip toDirect f)
+ (fileKey (takeFileName target))
{- git-merge moves conflicting files away to files
- named something like f~HEAD or f~branch, but the
@@ -464,3 +519,68 @@ newer remote b = do
( inRepo $ Git.Branch.changed r b
, return True
)
+
+{- If it's preferred content, and we don't have it, get it from one of the
+ - listed remotes (preferring the cheaper earlier ones).
+ -
+ - Send it to each remote that doesn't have it, and for which it's
+ - preferred content.
+ -
+ - Drop it locally if it's not preferred content (honoring numcopies).
+ -
+ - Drop it from each remote that has it, where it's not preferred content
+ - (honoring numcopies).
+ -
+ - If any file movements were generated, returns true.
+ -}
+seekSyncContent :: [Remote] -> Annex Bool
+seekSyncContent rs = do
+ mvar <- liftIO $ newEmptyMVar
+ mapM_ (go mvar) =<< seekHelper LsFiles.inRepo []
+ liftIO $ not <$> isEmptyMVar mvar
+ where
+ go mvar f = ifAnnexed f
+ (\v -> void (liftIO (tryPutMVar mvar ())) >> syncFile rs f v)
+ noop
+
+syncFile :: [Remote] -> FilePath -> (Key, Backend) -> Annex ()
+syncFile rs f (k, _) = do
+ locs <- loggedLocations k
+ let (have, lack) = partition (\r -> Remote.uuid r `elem` locs) rs
+
+ got <- anyM id =<< handleget have
+ putrs <- catMaybes . snd . unzip <$> (sequence =<< handleput lack)
+
+ u <- getUUID
+ let locs' = concat [if got then [u] else [], putrs, locs]
+
+ -- Using callCommandAction rather than commandAction for drops,
+ -- because a failure to drop does not mean the sync failed.
+ handleDropsFrom locs' rs "unwanted" True k (Just f)
+ Nothing callCommandAction
+ where
+ wantget have = allM id
+ [ pure (not $ null have)
+ , not <$> inAnnex k
+ , wantGet True (Just k) (Just f)
+ ]
+ handleget have = ifM (wantget have)
+ ( return [ get have ]
+ , return []
+ )
+ get have = commandAction $ do
+ showStart "get" f
+ next $ next $ getViaTmp k $ \dest -> getKeyFile' k (Just f) dest have
+
+ wantput r
+ | Remote.readonly r || remoteAnnexReadOnly (Types.Remote.gitconfig r) = return False
+ | otherwise = wantSend True (Just k) (Just f) (Remote.uuid r)
+ handleput lack = ifM (inAnnex k)
+ ( map put <$> (filterM wantput lack)
+ , return []
+ )
+ put dest = do
+ ok <- commandAction $ do
+ showStart "copy" f
+ next $ Command.Move.toPerform dest False k (Just f)
+ return (ok, if ok then Just (Remote.uuid dest) else Nothing)
diff --git a/Command/Test.hs b/Command/Test.hs
index be480eeb71..ee72201423 100644
--- a/Command/Test.hs
+++ b/Command/Test.hs
@@ -16,8 +16,8 @@ def = [ noRepo startIO $ dontCheck repoExists $
command "test" paramNothing seek SectionPlumbing
"run built-in test suite"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
{- We don't actually run the test suite here because of a dependency loop.
- The main program notices when the command is test and runs it; this
@@ -34,5 +34,4 @@ start ps = do
stop
startIO :: CmdParams -> IO ()
-startIO [] = warningIO "git-annex was built without its test suite; not testing"
-startIO _ = error "Cannot specify any additional parameters when running test"
+startIO _ = warningIO "git-annex was built without its test suite; not testing"
diff --git a/Command/TransferInfo.hs b/Command/TransferInfo.hs
index 93f6c7077a..8ab577a81b 100644
--- a/Command/TransferInfo.hs
+++ b/Command/TransferInfo.hs
@@ -12,15 +12,15 @@ import Command
import Annex.Content
import Logs.Transfer
import Types.Key
-import qualified Fields
+import qualified CmdLine.GitAnnexShell.Fields as Fields
import Utility.Metered
def :: [Command]
def = [noCommit $ command "transferinfo" paramKey seek SectionPlumbing
"updates sender on number of bytes of content received"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
{- Security:
-
diff --git a/Command/TransferKey.hs b/Command/TransferKey.hs
index 41a207080a..b6b2374678 100644
--- a/Command/TransferKey.hs
+++ b/Command/TransferKey.hs
@@ -14,8 +14,6 @@ import Logs.Location
import Logs.Transfer
import qualified Remote
import Types.Remote
-import GitAnnex.Options
-import qualified Option
def :: [Command]
def = [withOptions transferKeyOptions $
@@ -26,13 +24,14 @@ transferKeyOptions :: [Option]
transferKeyOptions = fileOption : fromToOptions
fileOption :: Option
-fileOption = Option.field [] "file" paramFile "the associated file"
+fileOption = fieldOption [] "file" paramFile "the associated file"
-seek :: [CommandSeek]
-seek = [withField toOption Remote.byNameWithUUID $ \to ->
- withField fromOption Remote.byNameWithUUID $ \from ->
- withField fileOption return $ \file ->
- withKeys $ start to from file]
+seek :: CommandSeek
+seek ps = do
+ to <- getOptionField toOption Remote.byNameWithUUID
+ from <- getOptionField fromOption Remote.byNameWithUUID
+ file <- getOptionField fileOption return
+ withKeys (start to from file) ps
start :: Maybe Remote -> Maybe Remote -> AssociatedFile -> Key -> CommandStart
start to from file key =
diff --git a/Command/TransferKeys.hs b/Command/TransferKeys.hs
index 6d8db4ef2a..b426286092 100644
--- a/Command/TransferKeys.hs
+++ b/Command/TransferKeys.hs
@@ -25,8 +25,8 @@ def :: [Command]
def = [command "transferkeys" paramNothing seek
SectionPlumbing "transfers keys"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = withHandles $ \(readh, writeh) -> do
@@ -106,34 +106,34 @@ readResponse h = fromMaybe False . deserialize <$> hGetLine h
fieldSep :: String
fieldSep = "\0"
-class Serialized a where
+class TCSerialized a where
serialize :: a -> String
deserialize :: String -> Maybe a
-instance Serialized Bool where
+instance TCSerialized Bool where
serialize True = "1"
serialize False = "0"
deserialize "1" = Just True
deserialize "0" = Just False
deserialize _ = Nothing
-instance Serialized Direction where
+instance TCSerialized Direction where
serialize Upload = "u"
serialize Download = "d"
deserialize "u" = Just Upload
deserialize "d" = Just Download
deserialize _ = Nothing
-instance Serialized AssociatedFile where
+instance TCSerialized AssociatedFile where
serialize (Just f) = f
serialize Nothing = ""
deserialize "" = Just Nothing
deserialize f = Just $ Just f
-instance Serialized UUID where
+instance TCSerialized UUID where
serialize = fromUUID
deserialize = Just . toUUID
-instance Serialized Key where
+instance TCSerialized Key where
serialize = key2file
deserialize = file2key
diff --git a/Command/Trust.hs b/Command/Trust.hs
index 26993ef771..3898af347a 100644
--- a/Command/Trust.hs
+++ b/Command/Trust.hs
@@ -16,8 +16,8 @@ def :: [Command]
def = [command "trust" (paramRepeating paramRemote) seek
SectionSetup "trust a repository"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start ws = do
diff --git a/Command/Unannex.hs b/Command/Unannex.hs
index 5e3c4279aa..1f29784308 100644
--- a/Command/Unannex.hs
+++ b/Command/Unannex.hs
@@ -23,8 +23,8 @@ def :: [Command]
def = [command "unannex" paramPaths seek SectionUtility
"undo accidential add command"]
-seek :: [CommandSeek]
-seek = [withFilesInGit $ whenAnnexed start]
+seek :: CommandSeek
+seek = withFilesInGit $ whenAnnexed start
start :: FilePath -> (Key, Backend) -> CommandStart
start file (key, _) = stopUnless (inAnnex key) $ do
diff --git a/Command/Ungroup.hs b/Command/Ungroup.hs
index a6557f21d3..a88e3f7c8e 100644
--- a/Command/Ungroup.hs
+++ b/Command/Ungroup.hs
@@ -19,8 +19,8 @@ def :: [Command]
def = [command "ungroup" (paramPair paramRemote paramDesc) seek
SectionSetup "remove a repository from a group"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start (name:g:[]) = do
diff --git a/Command/Uninit.hs b/Command/Uninit.hs
index 3fbe6758a4..3bf6dbe005 100644
--- a/Command/Uninit.hs
+++ b/Command/Uninit.hs
@@ -12,9 +12,9 @@ import Command
import qualified Git
import qualified Git.Command
import qualified Command.Unannex
-import Init
import qualified Annex.Branch
import Annex.Content
+import Annex.Init
def :: [Command]
def = [addCheck check $ command "uninit" paramPaths seek
@@ -34,12 +34,11 @@ check = do
revhead = inRepo $ Git.Command.pipeReadStrict
[Params "rev-parse --abbrev-ref HEAD"]
-seek :: [CommandSeek]
-seek =
- [ withFilesNotInGit $ whenAnnexed startCheckIncomplete
- , withFilesInGit $ whenAnnexed Command.Unannex.start
- , withNothing start
- ]
+seek :: CommandSeek
+seek ps = do
+ withFilesNotInGit (whenAnnexed startCheckIncomplete) ps
+ withFilesInGit (whenAnnexed Command.Unannex.start) ps
+ finish
{- git annex symlinks that are not checked into git could be left by an
- interrupted add. -}
@@ -50,8 +49,8 @@ startCheckIncomplete file _ = error $ unlines
, "Not continuing with uninit; either delete or git annex add the file and retry."
]
-start :: CommandStart
-start = next $ next $ do
+finish :: Annex ()
+finish = do
annexdir <- fromRepo gitAnnexDir
annexobjectdir <- fromRepo gitAnnexObjectDir
leftovers <- removeUnannexed =<< getKeysPresent
diff --git a/Command/Unlock.hs b/Command/Unlock.hs
index 1eba26ff72..9f2c257fbc 100644
--- a/Command/Unlock.hs
+++ b/Command/Unlock.hs
@@ -20,8 +20,8 @@ def =
where
c n = notDirect . command n paramPaths seek SectionCommon
-seek :: [CommandSeek]
-seek = [withFilesInGit $ whenAnnexed start]
+seek :: CommandSeek
+seek = withFilesInGit $ whenAnnexed start
{- The unlock subcommand replaces the symlink with a copy of the file's
- content. -}
diff --git a/Command/Untrust.hs b/Command/Untrust.hs
index f18637838e..cde1eee930 100644
--- a/Command/Untrust.hs
+++ b/Command/Untrust.hs
@@ -16,8 +16,8 @@ def :: [Command]
def = [command "untrust" (paramRepeating paramRemote) seek
SectionSetup "do not trust a repository"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start ws = do
diff --git a/Command/Unused.hs b/Command/Unused.hs
index 1e5cdc1632..312c26adf4 100644
--- a/Command/Unused.hs
+++ b/Command/Unused.hs
@@ -33,25 +33,24 @@ import qualified Git.DiffTree as DiffTree
import qualified Backend
import qualified Remote
import qualified Annex.Branch
-import qualified Option
import Annex.CatFile
import Types.Key
import Git.FilePath
def :: [Command]
-def = [withOptions [fromOption] $ command "unused" paramNothing seek
+def = [withOptions [unusedFromOption] $ command "unused" paramNothing seek
SectionMaintenance "look for unused file content"]
-fromOption :: Option
-fromOption = Option.field ['f'] "from" paramRemote "remote to check for unused content"
+unusedFromOption :: Option
+unusedFromOption = fieldOption ['f'] "from" paramRemote "remote to check for unused content"
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
{- Finds unused content in the annex. -}
start :: CommandStart
start = do
- from <- Annex.getField $ Option.name fromOption
+ from <- Annex.getField $ optionName unusedFromOption
let (name, action) = case from of
Nothing -> (".", checkUnused)
Just "." -> (".", checkUnused)
@@ -92,7 +91,7 @@ check file msg a c = do
l <- a
let unusedlist = number c l
unless (null l) $ showLongNote $ msg unusedlist
- writeUnusedLog file unusedlist
+ updateUnusedLog file $ M.fromList unusedlist
return $ c + length l
number :: Int -> [a] -> [(Int, a)]
@@ -326,19 +325,21 @@ data UnusedMaps = UnusedMaps
, unusedTmpMap :: UnusedMap
}
-{- Read unused logs once, and pass the maps to each start action. -}
withUnusedMaps :: (UnusedMaps -> Int -> CommandStart) -> CommandSeek
withUnusedMaps a params = do
- unused <- readUnusedLog ""
- unusedbad <- readUnusedLog "bad"
- unusedtmp <- readUnusedLog "tmp"
+ unused <- readUnusedMap ""
+ unusedbad <- readUnusedMap "bad"
+ unusedtmp <- readUnusedMap "tmp"
let m = unused `M.union` unusedbad `M.union` unusedtmp
- return $ map (a $ UnusedMaps unused unusedbad unusedtmp) $
+ let unusedmaps = UnusedMaps unused unusedbad unusedtmp
+ seekActions $ return $ map (a unusedmaps) $
concatMap (unusedSpec m) params
unusedSpec :: UnusedMap -> String -> [Int]
unusedSpec m spec
- | spec == "all" = [fst (M.findMin m)..fst (M.findMax m)]
+ | spec == "all" = if M.null m
+ then []
+ else [fst (M.findMin m)..fst (M.findMax m)]
| "-" `isInfixOf` spec = range $ separate (== '-') spec
| otherwise = maybe badspec (: []) (readish spec)
where
@@ -347,8 +348,8 @@ unusedSpec m spec
_ -> badspec
badspec = error $ "Expected number or range, not \"" ++ spec ++ "\""
-{- Start action for unused content. Finds the number in the maps, and
- - calls either of 3 actions, depending on the type of unused file. -}
+{- Seek action for unused content. Finds the number in the maps, and
+ - calls one of 3 actions, depending on the type of unused file. -}
startUnused :: String
-> (Key -> CommandPerform)
-> (Key -> CommandPerform)
diff --git a/Command/Upgrade.hs b/Command/Upgrade.hs
index de34278dde..80876290a4 100644
--- a/Command/Upgrade.hs
+++ b/Command/Upgrade.hs
@@ -16,8 +16,8 @@ def = [dontCheck repoExists $ -- because an old version may not seem to exist
command "upgrade" paramNothing seek
SectionMaintenance "upgrade repository layout"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
diff --git a/Command/Version.hs b/Command/Version.hs
index 0326b9edeb..526b752f04 100644
--- a/Command/Version.hs
+++ b/Command/Version.hs
@@ -21,8 +21,8 @@ def :: [Command]
def = [noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "version" paramNothing seek SectionQuery "show version info"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
diff --git a/Command/Vicfg.hs b/Command/Vicfg.hs
index 22c641408a..7608959c24 100644
--- a/Command/Vicfg.hs
+++ b/Command/Vicfg.hs
@@ -30,8 +30,8 @@ def :: [Command]
def = [command "vicfg" paramNothing seek
SectionSetup "edit git-annex's configuration"]
-seek :: [CommandSeek]
-seek = [withNothing start]
+seek :: CommandSeek
+seek = withNothing start
start :: CommandStart
start = do
diff --git a/Command/Wanted.hs b/Command/Wanted.hs
index 9ea0c211fd..bae450d265 100644
--- a/Command/Wanted.hs
+++ b/Command/Wanted.hs
@@ -20,8 +20,8 @@ def :: [Command]
def = [command "wanted" (paramPair paramRemote (paramOptional paramExpression)) seek
SectionSetup "get or set preferred content expression"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start = parse
diff --git a/Command/Watch.hs b/Command/Watch.hs
index a33fc633c0..79079337c7 100644
--- a/Command/Watch.hs
+++ b/Command/Watch.hs
@@ -10,23 +10,23 @@ module Command.Watch where
import Common.Annex
import Assistant
import Command
-import Option
import Utility.HumanTime
def :: [Command]
def = [notBareRepo $ withOptions [foregroundOption, stopOption] $
command "watch" paramNothing seek SectionCommon "watch for changes"]
-seek :: [CommandSeek]
-seek = [withFlag stopOption $ \stopdaemon ->
- withFlag foregroundOption $ \foreground ->
- withNothing $ start False foreground stopdaemon Nothing]
+seek :: CommandSeek
+seek ps = do
+ stopdaemon <- getOptionFlag stopOption
+ foreground <- getOptionFlag foregroundOption
+ withNothing (start False foreground stopdaemon Nothing) ps
foregroundOption :: Option
-foregroundOption = Option.flag [] "foreground" "do not daemonize"
+foregroundOption = flagOption [] "foreground" "do not daemonize"
stopOption :: Option
-stopOption = Option.flag [] "stop" "stop daemon"
+stopOption = flagOption [] "stop" "stop daemon"
start :: Bool -> Bool -> Bool -> Maybe Duration -> CommandStart
start assistant foreground stopdaemon startdelay = do
diff --git a/Command/WebApp.hs b/Command/WebApp.hs
index a009be15de..d5f43432c4 100644
--- a/Command/WebApp.hs
+++ b/Command/WebApp.hs
@@ -23,13 +23,12 @@ import Utility.Daemon (checkDaemon)
#ifdef __ANDROID__
import Utility.Env
#endif
-import Init
+import Annex.Init
import qualified Git
import qualified Git.Config
import qualified Git.CurrentRepo
import qualified Annex
import Config.Files
-import qualified Option
import Upgrade
import Annex.Version
@@ -45,12 +44,13 @@ def = [ withOptions [listenOption] $
command "webapp" paramNothing seek SectionCommon "launch webapp"]
listenOption :: Option
-listenOption = Option.field [] "listen" paramAddress
+listenOption = fieldOption [] "listen" paramAddress
"accept connections to this address"
-seek :: [CommandSeek]
-seek = [withField listenOption return $ \listenhost ->
- withNothing $ start listenhost]
+seek :: CommandSeek
+seek ps = do
+ listenhost <- getOptionField listenOption return
+ withNothing (start listenhost) ps
start :: Maybe HostName -> CommandStart
start = start' True
@@ -107,7 +107,7 @@ startNoRepo _ = do
(d:_) -> do
setCurrentDirectory d
state <- Annex.new =<< Git.CurrentRepo.get
- void $ Annex.eval state $ doCommand $
+ void $ Annex.eval state $ callCommandAction $
start' False listenhost
{- Run the webapp without a repository, which prompts the user, makes one,
diff --git a/Command/Whereis.hs b/Command/Whereis.hs
index 7086bf645e..387ffebc95 100644
--- a/Command/Whereis.hs
+++ b/Command/Whereis.hs
@@ -15,16 +15,27 @@ import Remote
import Logs.Trust
def :: [Command]
-def = [noCommit $ command "whereis" paramPaths seek
- SectionQuery "lists repositories that have file content"]
+def = [noCommit $ withOptions (jsonOption : keyOptions) $
+ command "whereis" paramPaths seek SectionQuery
+ "lists repositories that have file content"]
-seek :: [CommandSeek]
-seek = [withValue (remoteMap id) $ \m ->
- withFilesInGit $ whenAnnexed $ start m]
+seek :: CommandSeek
+seek ps = do
+ m <- remoteMap id
+ withKeyOptions
+ (startKeys m)
+ (withFilesInGit $ whenAnnexed $ start m)
+ ps
start :: M.Map UUID Remote -> FilePath -> (Key, Backend) -> CommandStart
-start remotemap file (key, _) = do
- showStart "whereis" file
+start remotemap file (key, _) = start' remotemap key (Just file)
+
+startKeys :: M.Map UUID Remote -> Key -> CommandStart
+startKeys remotemap key = start' remotemap key Nothing
+
+start' :: M.Map UUID Remote -> Key -> AssociatedFile -> CommandStart
+start' remotemap key afile = do
+ showStart' "whereis" key afile
next $ perform remotemap key
perform :: M.Map UUID Remote -> Key -> CommandPerform
diff --git a/Command/XMPPGit.hs b/Command/XMPPGit.hs
index 796e8b4edd..47c2d7ff24 100644
--- a/Command/XMPPGit.hs
+++ b/Command/XMPPGit.hs
@@ -16,8 +16,8 @@ def = [noCommit $ noRepo startNoRepo $ dontCheck repoExists $
command "xmppgit" paramNothing seek
SectionPlumbing "git to XMPP relay"]
-seek :: [CommandSeek]
-seek = [withWords start]
+seek :: CommandSeek
+seek = withWords start
start :: [String] -> CommandStart
start _ = do
diff --git a/Common.hs b/Common.hs
index a6203b9a69..6612c9c544 100644
--- a/Common.hs
+++ b/Common.hs
@@ -15,7 +15,6 @@ import Data.String.Utils as X hiding (join)
import System.FilePath as X
import System.Directory as X
import System.IO as X hiding (FilePath)
-import System.PosixCompat.Files as X
#ifndef mingw32_HOST_OS
import System.Posix.IO as X
#endif
@@ -31,5 +30,6 @@ import Utility.Monad as X
import Utility.Data as X
import Utility.Applicative as X
import Utility.FileSystemEncoding as X
+import Utility.PosixFiles as X
import Utility.PartialPrelude as X
diff --git a/Config.hs b/Config.hs
index 5003c1ce09..376a3a488c 100644
--- a/Config.hs
+++ b/Config.hs
@@ -69,10 +69,6 @@ setRemoteCost r c = setConfig (remoteConfig r "cost") (show c)
setRemoteAvailability :: Git.Repo -> Availability -> Annex ()
setRemoteAvailability r c = setConfig (remoteConfig r "availability") (show c)
-getNumCopies :: Maybe Int -> Annex Int
-getNumCopies (Just v) = return v
-getNumCopies Nothing = annexNumCopies <$> Annex.getGitConfig
-
isDirect :: Annex Bool
isDirect = annexDirect <$> Annex.getGitConfig
diff --git a/Config/NumCopies.hs b/Config/NumCopies.hs
new file mode 100644
index 0000000000..26d81b8a4c
--- /dev/null
+++ b/Config/NumCopies.hs
@@ -0,0 +1,80 @@
+{- git-annex numcopies configuration
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Config.NumCopies (
+ module Types.NumCopies,
+ module Logs.NumCopies,
+ getFileNumCopies,
+ getGlobalFileNumCopies,
+ getNumCopies,
+ numCopiesCheck,
+ deprecatedNumCopies,
+ defaultNumCopies
+) where
+
+import Common.Annex
+import qualified Annex
+import Types.NumCopies
+import Logs.NumCopies
+import Logs.Trust
+import Annex.CheckAttr
+import qualified Remote
+
+defaultNumCopies :: NumCopies
+defaultNumCopies = NumCopies 1
+
+fromSources :: [Annex (Maybe NumCopies)] -> Annex NumCopies
+fromSources = fromMaybe defaultNumCopies <$$> getM id
+
+{- The git config annex.numcopies is deprecated. -}
+deprecatedNumCopies :: Annex (Maybe NumCopies)
+deprecatedNumCopies = annexNumCopies <$> Annex.getGitConfig
+
+{- Value forced on the command line by --numcopies. -}
+getForcedNumCopies :: Annex (Maybe NumCopies)
+getForcedNumCopies = Annex.getState Annex.forcenumcopies
+
+{- Numcopies value from any of the non-.gitattributes configuration
+ - sources. -}
+getNumCopies :: Annex NumCopies
+getNumCopies = fromSources
+ [ getForcedNumCopies
+ , getGlobalNumCopies
+ , deprecatedNumCopies
+ ]
+
+{- Numcopies value for a file, from any configuration source, including the
+ - deprecated git config. -}
+getFileNumCopies :: FilePath -> Annex NumCopies
+getFileNumCopies f = fromSources
+ [ getForcedNumCopies
+ , getFileNumCopies' f
+ , deprecatedNumCopies
+ ]
+
+{- This is the globally visible numcopies value for a file. So it does
+ - not include local configuration in the git config or command line
+ - options. -}
+getGlobalFileNumCopies :: FilePath -> Annex NumCopies
+getGlobalFileNumCopies f = fromSources
+ [ getFileNumCopies' f
+ ]
+
+getFileNumCopies' :: FilePath -> Annex (Maybe NumCopies)
+getFileNumCopies' file = maybe getGlobalNumCopies (return . Just) =<< getattr
+ where
+ getattr = (NumCopies <$$> readish)
+ <$> checkAttr "annex.numcopies" file
+
+{- Checks if numcopies are satisfied for a file by running a comparison
+ - between the number of (not untrusted) copies that are
+ - belived to exist, and the configured value. -}
+numCopiesCheck :: FilePath -> Key -> (Int -> Int -> v) -> Annex v
+numCopiesCheck file key vs = do
+ NumCopies needed <- getFileNumCopies file
+ have <- trustExclude UnTrusted =<< Remote.keyLocations key
+ return $ length have `vs` needed
diff --git a/Creds.hs b/Creds.hs
index 7c300dd07a..3bd87a522a 100644
--- a/Creds.hs
+++ b/Creds.hs
@@ -51,7 +51,7 @@ setRemoteCredPair' c storage creds
return c
storeconfig key (Just cipher) = do
- s <- liftIO $ encrypt [] cipher
+ s <- liftIO $ encrypt (getGpgEncParams c) cipher
(feedBytes $ L.pack $ encodeCredPair creds)
(readBytes $ return . L.unpack)
return $ M.insert key (toB64 s) c
diff --git a/Crypto.hs b/Crypto.hs
index 371bbcaf1e..f3a9e3957e 100644
--- a/Crypto.hs
+++ b/Crypto.hs
@@ -196,15 +196,21 @@ prop_HmacSha1WithCipher_sane = known_good == macWithCipher' HmacSha1 "foo" "bar"
class LensGpgEncParams a where getGpgEncParams :: a -> [CommandParam]
{- Extract the GnuPG options from a pair of a Remote Config and a Remote
- - Git Config. If the remote is configured to use public-key encryption,
- - look up the recipient keys and add them to the option list. -}
+ - Git Config. -}
instance LensGpgEncParams (RemoteConfig, RemoteGitConfig) where
- getGpgEncParams (c,gc) = map Param (remoteAnnexGnupgOptions gc) ++ recipients
+ getGpgEncParams (c,gc) = map Param (remoteAnnexGnupgOptions gc) ++ getGpgEncParams c
where
- recipients = case M.lookup "encryption" c of
- Just "pubkey" -> Gpg.pkEncTo $ maybe [] (split ",") $
- M.lookup "cipherkeys" c
- _ -> []
+
+{- Extract the GnuPG options from a Remote Config, ignoring any
+ - git config settings. (Which is ok if the remote is just being set up
+ - and so doesn't have any.)
+ -
+ - If the remote is configured to use public-key encryption,
+ - look up the recipient keys and add them to the option list.-}
+instance LensGpgEncParams RemoteConfig where
+ getGpgEncParams c = case M.lookup "encryption" c of
+ Just "pubkey" -> Gpg.pkEncTo $ maybe [] (split ",") $ M.lookup "cipherkeys" c
+ _ -> []
{- Extract the GnuPG options from a Remote. -}
instance LensGpgEncParams (RemoteA a) where
diff --git a/Git/Command.hs b/Git/Command.hs
index 4c338ba250..034c4ecb55 100644
--- a/Git/Command.hs
+++ b/Git/Command.hs
@@ -18,6 +18,7 @@ import qualified Utility.CoProcess as CoProcess
#ifdef mingw32_HOST_OS
import Git.FilePath
#endif
+import Utility.Batch
{- Constructs a git command line operating on the specified repo. -}
gitCommandLine :: [CommandParam] -> Repo -> [CommandParam]
@@ -31,7 +32,7 @@ gitCommandLine params r@(Repo { location = l@(Local _ _ ) }) =
#ifdef mingw32_HOST_OS
-- despite running on windows, msysgit wants a unix-formatted path
gitpath s
- | isAbsolute s = "/" ++ dropDrive (toInternalGitPath s)
+ | absoluteGitPath s = "/" ++ dropDrive (toInternalGitPath s)
| otherwise = s
#else
gitpath = id
@@ -41,9 +42,13 @@ gitCommandLine _ repo = assertLocal repo $ error "internal"
{- Runs git in the specified repo. -}
runBool :: [CommandParam] -> Repo -> IO Bool
runBool params repo = assertLocal repo $
- boolSystemEnv "git"
- (gitCommandLine params repo)
- (gitEnv repo)
+ boolSystemEnv "git" (gitCommandLine params repo) (gitEnv repo)
+
+{- Runs git in batch mode. -}
+runBatch :: BatchCommandMaker -> [CommandParam] -> Repo -> IO Bool
+runBatch batchmaker params repo = assertLocal repo $ do
+ let (cmd, params') = batchmaker ("git", gitCommandLine params repo)
+ boolSystemEnv cmd params' (gitEnv repo)
{- Runs git in the specified repo, throwing an error if it fails. -}
run :: [CommandParam] -> Repo -> IO ()
diff --git a/Git/Construct.hs b/Git/Construct.hs
index 71a13f49f9..eed2b99300 100644
--- a/Git/Construct.hs
+++ b/Git/Construct.hs
@@ -33,6 +33,7 @@ import Common
import Git.Types
import Git
import Git.Remote
+import Git.FilePath
import qualified Git.Url as Url
import Utility.UserInfo
@@ -57,7 +58,7 @@ fromPath dir = fromAbsPath =<< absPath dir
- specified. -}
fromAbsPath :: FilePath -> IO Repo
fromAbsPath dir
- | isAbsolute dir = ifM (doesDirectoryExist dir') ( ret dir' , hunt )
+ | absoluteGitPath dir = ifM (doesDirectoryExist dir') ( ret dir' , hunt )
| otherwise =
error $ "internal error, " ++ dir ++ " is not absolute"
where
diff --git a/Git/FilePath.hs b/Git/FilePath.hs
index 4189244fc6..42eb0812e3 100644
--- a/Git/FilePath.hs
+++ b/Git/FilePath.hs
@@ -20,12 +20,15 @@ module Git.FilePath (
asTopFilePath,
InternalGitPath,
toInternalGitPath,
- fromInternalGitPath
+ fromInternalGitPath,
+ absoluteGitPath
) where
import Common
import Git
+import qualified System.FilePath.Posix
+
{- A FilePath, relative to the top of the git repository. -}
newtype TopFilePath = TopFilePath { getTopFilePath :: FilePath }
deriving (Show)
@@ -48,8 +51,7 @@ asTopFilePath file = TopFilePath file
- it internally.
-
- On Windows, git uses '/' to separate paths stored in the repository,
- - despite Windows using '\'. Also, git on windows dislikes paths starting
- - with "./" or ".\".
+ - despite Windows using '\'.
-
-}
type InternalGitPath = String
@@ -58,11 +60,7 @@ toInternalGitPath :: FilePath -> InternalGitPath
#ifndef mingw32_HOST_OS
toInternalGitPath = id
#else
-toInternalGitPath p =
- let p' = replace "\\" "/" p
- in if "./" `isPrefixOf` p'
- then dropWhile (== '/') (drop 1 p')
- else p'
+toInternalGitPath = replace "\\" "/"
#endif
fromInternalGitPath :: InternalGitPath -> FilePath
@@ -71,3 +69,10 @@ fromInternalGitPath = id
#else
fromInternalGitPath = replace "/" "\\"
#endif
+
+{- isAbsolute on Windows does not think "/foo" or "\foo" is absolute,
+ - so try posix paths.
+ -}
+absoluteGitPath :: FilePath -> Bool
+absoluteGitPath p = isAbsolute p ||
+ System.FilePath.Posix.isAbsolute (toInternalGitPath p)
diff --git a/Git/Fsck.hs b/Git/Fsck.hs
index a49978d44a..23d3a35580 100644
--- a/Git/Fsck.hs
+++ b/Git/Fsck.hs
@@ -20,7 +20,7 @@ import Git
import Git.Command
import Git.Sha
import Utility.Batch
-import qualified Git.BuildVersion
+import qualified Git.Version
import qualified Data.Set as S
@@ -40,12 +40,14 @@ data FsckResults = FsckFoundMissing MissingObjects | FsckFailed
-}
findBroken :: Bool -> Repo -> IO FsckResults
findBroken batchmode r = do
- let (command, params) = ("git", fsckParams r)
+ supportsNoDangling <- (>= Git.Version.normalize "1.7.10")
+ <$> Git.Version.installed
+ let (command, params) = ("git", fsckParams supportsNoDangling r)
(command', params') <- if batchmode
then toBatchCommand (command, params)
else return (command, params)
(output, fsckok) <- processTranscript command' (toCommand params') Nothing
- let objs = findShas output
+ let objs = findShas supportsNoDangling output
badobjs <- findMissing objs r
if S.null badobjs && not fsckok
then return FsckFailed
@@ -75,21 +77,18 @@ isMissing s r = either (const True) (const False) <$> tryIO dump
, Param (show s)
] r
-findShas :: String -> [Sha]
-findShas = catMaybes . map extractSha . concat . map words . filter wanted . lines
+findShas :: Bool -> String -> [Sha]
+findShas supportsNoDangling = catMaybes . map extractSha . concat . map words . filter wanted . lines
where
wanted l
| supportsNoDangling = True
| otherwise = not ("dangling " `isPrefixOf` l)
-fsckParams :: Repo -> [CommandParam]
-fsckParams = gitCommandLine $ map Param $ catMaybes
+fsckParams :: Bool -> Repo -> [CommandParam]
+fsckParams supportsNoDangling = gitCommandLine $ map Param $ catMaybes
[ Just "fsck"
, if supportsNoDangling
then Just "--no-dangling"
else Nothing
, Just "--no-reflogs"
]
-
-supportsNoDangling :: Bool
-supportsNoDangling = not $ Git.BuildVersion.older "1.7.10"
diff --git a/Git/Ref.hs b/Git/Ref.hs
index 09472930f4..88717ce471 100644
--- a/Git/Ref.hs
+++ b/Git/Ref.hs
@@ -11,6 +11,7 @@ import Common
import Git
import Git.Command
import Git.Sha
+import Git.Types
import Data.Char (chr)
@@ -51,6 +52,10 @@ underBase dir r = Ref $ dir ++ "/" ++ show (base r)
fileRef :: FilePath -> Ref
fileRef f = Ref $ ":./" ++ f
+{- Converts a Ref to refer to the content of the Ref on a given date. -}
+dateRef :: Ref -> RefDate -> Ref
+dateRef (Ref r) (RefDate d) = Ref $ r ++ "@" ++ d
+
{- A Ref that can be used to refer to a file in the repository as it
- appears in a given Ref. -}
fileFromRef :: Ref -> FilePath -> Ref
diff --git a/Git/Types.hs b/Git/Types.hs
index e63e93077f..d805d8574f 100644
--- a/Git/Types.hs
+++ b/Git/Types.hs
@@ -57,6 +57,10 @@ type Branch = Ref
type Sha = Ref
type Tag = Ref
+{- A date in the format described in gitrevisions. Includes the
+ - braces, eg, "{yesterday}" -}
+newtype RefDate = RefDate String
+
{- Types of objects that can be stored in git. -}
data ObjectType = BlobObject | CommitObject | TreeObject
deriving (Eq)
diff --git a/Limit.hs b/Limit.hs
index f3586e0291..6f41016330 100644
--- a/Limit.hs
+++ b/Limit.hs
@@ -1,6 +1,6 @@
{- user-specified limits on files to act on
-
- - Copyright 2011-2013 Joey Hess
+ - Copyright 2011-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -13,7 +13,6 @@ import Data.Time.Clock.POSIX
import qualified Data.Set as S
import qualified Data.Map as M
import System.Path.WildMatch
-import System.PosixCompat.Files
import Common.Annex
import qualified Annex
@@ -23,12 +22,16 @@ import qualified Backend
import Annex.Content
import Annex.UUID
import Logs.Trust
+import Config.NumCopies
import Types.TrustLevel
import Types.Key
import Types.Group
import Types.FileMatcher
import Types.Limit
import Logs.Group
+import Logs.Unused
+import Logs.Location
+import Git.Types (RefDate(..))
import Utility.HumanTime
import Utility.DataUnits
@@ -48,10 +51,10 @@ limited = (not . Utility.Matcher.isEmpty) <$> getMatcher'
{- Gets a matcher for the user-specified limits. The matcher is cached for
- speed; once it's obtained the user-specified limits can't change. -}
-getMatcher :: Annex (FileInfo -> Annex Bool)
+getMatcher :: Annex (MatchInfo -> Annex Bool)
getMatcher = Utility.Matcher.matchM <$> getMatcher'
-getMatcher' :: Annex (Utility.Matcher.Matcher (FileInfo -> Annex Bool))
+getMatcher' :: Annex (Utility.Matcher.Matcher (MatchInfo -> Annex Bool))
getMatcher' = do
m <- Annex.getState Annex.limit
case m of
@@ -63,7 +66,7 @@ getMatcher' = do
return matcher
{- Adds something to the limit list, which is built up reversed. -}
-add :: Utility.Matcher.Token (FileInfo -> Annex Bool) -> Annex ()
+add :: Utility.Matcher.Token (MatchInfo -> Annex Bool) -> Annex ()
add l = Annex.changeState $ \s -> s { Annex.limit = prepend $ Annex.limit s }
where
prepend (Left ls) = Left $ l:ls
@@ -94,8 +97,8 @@ limitExclude glob = Right $ const $ return . not . matchglob glob
{- Could just use wildCheckCase, but this way the regex is only compiled
- once. Also, we use regex-TDFA when available, because it's less buggy
- in its support of non-unicode characters. -}
-matchglob :: String -> FileInfo -> Bool
-matchglob glob fi =
+matchglob :: String -> MatchInfo -> Bool
+matchglob glob (MatchingFile fi) =
#ifdef WITH_TDFA
case cregex of
Right r -> case execute r (matchFile fi) of
@@ -108,25 +111,29 @@ matchglob glob fi =
#else
wildCheckCase glob (matchFile fi)
#endif
+matchglob _ (MatchingKey _) = False
{- Adds a limit to skip files not believed to be present
- - in a specfied repository. -}
+ - in a specfied repository. Optionally on a prior date. -}
addIn :: String -> Annex ()
addIn = addLimit . limitIn
limitIn :: MkLimit
-limitIn name = Right $ \notpresent -> check $
+limitIn s = Right $ \notpresent -> checkKey $ \key ->
if name == "."
- then inhere notpresent
- else inremote notpresent
+ then if null date
+ then inhere notpresent key
+ else inuuid notpresent key =<< getUUID
+ else inuuid notpresent key =<< Remote.nameToUUID name
where
- check a = lookupFile >=> handle a
- handle _ Nothing = return False
- handle a (Just (key, _)) = a key
- inremote notpresent key = do
- u <- Remote.nameToUUID name
- us <- Remote.keyLocations key
- return $ u `elem` us && u `S.notMember` notpresent
+ (name, date) = separate (== '@') s
+ inuuid notpresent key u
+ | null date = do
+ us <- Remote.keyLocations key
+ return $ u `elem` us && u `S.notMember` notpresent
+ | otherwise = do
+ us <- loggedLocationsHistorical (RefDate date) key
+ return $ u `elem` us
inhere notpresent key
| S.null notpresent = inAnnex key
| otherwise = do
@@ -137,22 +144,20 @@ limitIn name = Right $ \notpresent -> check $
{- Limit to content that is currently present on a uuid. -}
limitPresent :: Maybe UUID -> MkLimit
-limitPresent u _ = Right $ const $ check $ \key -> do
+limitPresent u _ = Right $ const $ checkKey $ \key -> do
hereu <- getUUID
if u == Just hereu || isNothing u
then inAnnex key
else do
us <- Remote.keyLocations key
return $ maybe False (`elem` us) u
- where
- check a = lookupFile >=> handle a
- handle _ Nothing = return False
- handle a (Just (key, _)) = a key
{- Limit to content that is in a directory, anywhere in the repository tree -}
limitInDir :: FilePath -> MkLimit
-limitInDir dir = const $ Right $ const $ \fi -> return $
- any (== dir) $ splitPath $ takeDirectory $ matchFile fi
+limitInDir dir = const $ Right $ const go
+ where
+ go (MatchingFile fi) = return $ any (== dir) $ splitPath $ takeDirectory $ matchFile fi
+ go (MatchingKey _) = return False
{- Adds a limit to skip files not believed to have the specified number
- of copies. -}
@@ -169,10 +174,9 @@ limitCopies want = case split ":" want of
where
go num good = case readish num of
Nothing -> Left "bad number for copies"
- Just n -> Right $ \notpresent f ->
- lookupFile f >>= handle n good notpresent
- handle _ _ _ Nothing = return False
- handle n good notpresent (Just (key, _)) = do
+ Just n -> Right $ \notpresent -> checkKey $
+ handle n good notpresent
+ handle n good notpresent key = do
us <- filter (`S.notMember` notpresent)
<$> (filterM good =<< Remote.keyLocations key)
return $ length us >= n
@@ -182,6 +186,36 @@ limitCopies want = case split ":" want of
| "+" `isSuffixOf` s = (>=) <$> readTrustLevel (beginning s)
| otherwise = (==) <$> readTrustLevel s
+{- Adds a limit to match files that need more copies made. -}
+addLackingCopies :: Bool -> String -> Annex ()
+addLackingCopies approx = addLimit . limitLackingCopies approx
+
+limitLackingCopies :: Bool -> MkLimit
+limitLackingCopies approx want = case readish want of
+ Just needed -> Right $ \notpresent mi -> flip checkKey mi $
+ handle mi needed notpresent
+ Nothing -> Left "bad value for number of lacking copies"
+ where
+ handle mi needed notpresent key = do
+ NumCopies numcopies <- if approx
+ then approxNumCopies
+ else case mi of
+ MatchingKey _ -> approxNumCopies
+ MatchingFile fi -> getGlobalFileNumCopies $ matchFile fi
+ us <- filter (`S.notMember` notpresent)
+ <$> (trustExclude UnTrusted =<< Remote.keyLocations key)
+ return $ numcopies - length us >= needed
+ approxNumCopies = fromMaybe defaultNumCopies <$> getGlobalNumCopies
+
+{- Match keys that are unused.
+ -
+ - This has a nice optimisation: When a file exists,
+ - its key is obviously not unused.
+ -}
+limitUnused :: MatchFiles
+limitUnused _ (MatchingFile _) = return False
+limitUnused _ (MatchingKey k) = S.member k <$> unusedKeys
+
{- Adds a limit to skip files not believed to be present in all
- repositories in the specified group. -}
addInAllGroup :: String -> Annex ()
@@ -192,11 +226,10 @@ addInAllGroup groupname = do
limitInAllGroup :: GroupMap -> MkLimit
limitInAllGroup m groupname
| S.null want = Right $ const $ const $ return True
- | otherwise = Right $ \notpresent -> lookupFile >=> check notpresent
+ | otherwise = Right $ \notpresent -> checkKey $ check notpresent
where
want = fromMaybe S.empty $ M.lookup groupname $ uuidsByGroup m
- check _ Nothing = return False
- check notpresent (Just (key, _))
+ check notpresent key
-- optimisation: Check if a wanted uuid is notpresent.
| not (S.null (S.intersection want notpresent)) = return False
| otherwise = do
@@ -208,10 +241,9 @@ addInBackend :: String -> Annex ()
addInBackend = addLimit . limitInBackend
limitInBackend :: MkLimit
-limitInBackend name = Right $ const $ lookupFile >=> check
+limitInBackend name = Right $ const $ checkKey check
where
- wanted = Backend.lookupBackendName name
- check = return . maybe False ((==) wanted . snd)
+ check key = pure $ keyBackendName key == name
{- Adds a limit to skip files that are too large or too small -}
addLargerThan :: String -> Annex ()
@@ -225,8 +257,10 @@ limitSize vs s = case readSize dataUnits s of
Nothing -> Left "bad size"
Just sz -> Right $ go sz
where
- go sz _ fi = lookupFile fi >>= check fi sz
- check _ sz (Just (key, _)) = return $ keySize key `vs` Just sz
+ go sz _ (MatchingFile fi) = lookupFile fi >>= check fi sz
+ go sz _ (MatchingKey key) = checkkey sz key
+ checkkey sz key = return $ keySize key `vs` Just sz
+ check _ sz (Just (key, _)) = checkkey sz key
check fi sz Nothing = do
filesize <- liftIO $ catchMaybeIO $
fromIntegral . fileSize
@@ -249,3 +283,10 @@ addTimeLimit s = do
lookupFile :: FileInfo -> Annex (Maybe (Key, Backend))
lookupFile = Backend.lookupFile . relFile
+
+lookupFileKey :: FileInfo -> Annex (Maybe Key)
+lookupFileKey = (fst <$>) <$$> Backend.lookupFile . relFile
+
+checkKey :: (Key -> Annex Bool) -> MatchInfo -> Annex Bool
+checkKey a (MatchingFile fi) = lookupFileKey fi >>= maybe (return False) a
+checkKey a (MatchingKey k) = a k
diff --git a/Limit/Wanted.hs b/Limit/Wanted.hs
index ed4529dead..01b8da6b34 100644
--- a/Limit/Wanted.hs
+++ b/Limit/Wanted.hs
@@ -13,9 +13,11 @@ import Limit
import Types.FileMatcher
addWantGet :: Annex ()
-addWantGet = addLimit $ Right $ const $
- \fileinfo -> wantGet False (Just $ matchFile fileinfo)
+addWantGet = addLimit $ Right $ const $ checkWant $ wantGet False Nothing
addWantDrop :: Annex ()
-addWantDrop = addLimit $ Right $ const $
- \fileinfo -> wantDrop False Nothing (Just $ matchFile fileinfo)
+addWantDrop = addLimit $ Right $ const $ checkWant $ wantDrop False Nothing Nothing
+
+checkWant :: (Maybe FilePath -> Annex Bool) -> MatchInfo -> Annex Bool
+checkWant a (MatchingFile fi) = a (Just $ matchFile fi)
+checkWant _ (MatchingKey _) = return False
diff --git a/Locations.hs b/Locations.hs
index 47a009590c..553104d959 100644
--- a/Locations.hs
+++ b/Locations.hs
@@ -14,6 +14,7 @@ module Locations (
objectDir,
gitAnnexLocation,
gitAnnexLink,
+ gitAnnexContentLock,
gitAnnexMapping,
gitAnnexInodeCache,
gitAnnexInodeSentinal,
@@ -136,12 +137,18 @@ gitAnnexLocation' key r crippled
gitAnnexLink :: FilePath -> Key -> Git.Repo -> IO FilePath
gitAnnexLink file key r = do
cwd <- getCurrentDirectory
- let absfile = fromMaybe whoops $ absNormPath cwd file
+ let absfile = fromMaybe whoops $ absNormPathUnix cwd file
loc <- gitAnnexLocation' key r False
return $ relPathDirToFile (parentDir absfile) loc
where
whoops = error $ "unable to normalize " ++ file
+{- File used to lock a key's content. -}
+gitAnnexContentLock :: Key -> Git.Repo -> GitConfig -> IO FilePath
+gitAnnexContentLock key r config = do
+ loc <- gitAnnexLocation key r config
+ return $ loc ++ ".lck"
+
{- File that maps from a key to the file(s) in the git repository.
- Used in direct mode. -}
gitAnnexMapping :: Key -> Git.Repo -> GitConfig -> IO FilePath
diff --git a/Logs.hs b/Logs.hs
index 2952d6920c..828a73dc70 100644
--- a/Logs.hs
+++ b/Logs.hs
@@ -11,7 +11,11 @@ import Common.Annex
import Types.Key
{- There are several varieties of log file formats. -}
-data LogVariety = UUIDBasedLog | NewUUIDBasedLog | PresenceLog Key
+data LogVariety
+ = UUIDBasedLog
+ | NewUUIDBasedLog
+ | PresenceLog Key
+ | SingleValueLog
deriving (Show)
{- Converts a path from the git-annex branch into one of the varieties
@@ -20,6 +24,7 @@ getLogVariety :: FilePath -> Maybe LogVariety
getLogVariety f
| f `elem` topLevelUUIDBasedLogs = Just UUIDBasedLog
| isRemoteStateLog f = Just NewUUIDBasedLog
+ | f == numcopiesLog = Just SingleValueLog
| otherwise = PresenceLog <$> firstJust (presenceLogs f)
{- All the uuid-based logs stored in the top of the git-annex branch. -}
@@ -43,6 +48,9 @@ presenceLogs f =
uuidLog :: FilePath
uuidLog = "uuid.log"
+numcopiesLog :: FilePath
+numcopiesLog = "numcopies.log"
+
remoteLog :: FilePath
remoteLog = "remote.log"
@@ -118,6 +126,7 @@ prop_logs_sane dummykey = all id
, expect isPresenceLog (getLogVariety $ locationLogFile dummykey)
, expect isPresenceLog (getLogVariety $ urlLogFile dummykey)
, expect isNewUUIDBasedLog (getLogVariety $ remoteStateLogFile dummykey)
+ , expect isSingleValueLog (getLogVariety $ numcopiesLog)
]
where
expect = maybe False
@@ -127,3 +136,5 @@ prop_logs_sane dummykey = all id
isNewUUIDBasedLog _ = False
isPresenceLog (PresenceLog k) = k == dummykey
isPresenceLog _ = False
+ isSingleValueLog SingleValueLog = True
+ isSingleValueLog _ = False
diff --git a/Logs/Location.hs b/Logs/Location.hs
index f751c00de5..cb1e415fdb 100644
--- a/Logs/Location.hs
+++ b/Logs/Location.hs
@@ -8,7 +8,7 @@
- Repositories record their UUID and the date when they --get or --drop
- a value.
-
- - Copyright 2010-2011 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -18,6 +18,7 @@ module Logs.Location (
logStatus,
logChange,
loggedLocations,
+ loggedLocationsHistorical,
loggedKeys,
loggedKeysFor,
) where
@@ -27,6 +28,7 @@ import qualified Annex.Branch
import Logs
import Logs.Presence
import Annex.UUID
+import Git.Types (RefDate)
{- Log a change in the presence of a key's value in current repository. -}
logStatus :: Key -> LogStatus -> Annex ()
@@ -40,10 +42,16 @@ logChange key (UUID u) s = addLog (locationLogFile key) =<< logNow s u
logChange _ NoUUID _ = noop
{- Returns a list of repository UUIDs that, according to the log, have
- - the value of a key.
- -}
+ - the value of a key. -}
loggedLocations :: Key -> Annex [UUID]
-loggedLocations key = map toUUID <$> (currentLog . locationLogFile) key
+loggedLocations = getLoggedLocations currentLog
+
+{- Gets the location log on a particular date. -}
+loggedLocationsHistorical :: RefDate -> Key -> Annex [UUID]
+loggedLocationsHistorical = getLoggedLocations . historicalLog
+
+getLoggedLocations :: (FilePath -> Annex [String]) -> Key -> Annex [UUID]
+getLoggedLocations getter key = map toUUID <$> (getter . locationLogFile) key
{- Finds all keys that have location log information.
- (There may be duplicate keys in the list.) -}
diff --git a/Logs/NumCopies.hs b/Logs/NumCopies.hs
new file mode 100644
index 0000000000..5cce61ce62
--- /dev/null
+++ b/Logs/NumCopies.hs
@@ -0,0 +1,38 @@
+{- git-annex numcopies log
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
+module Logs.NumCopies (
+ setGlobalNumCopies,
+ getGlobalNumCopies,
+ globalNumCopiesLoad,
+) where
+
+import Common.Annex
+import qualified Annex
+import Types.NumCopies
+import Logs
+import Logs.SingleValue
+
+instance SingleValueSerializable NumCopies where
+ serialize (NumCopies n) = show n
+ deserialize = NumCopies <$$> readish
+
+setGlobalNumCopies :: NumCopies -> Annex ()
+setGlobalNumCopies = setLog numcopiesLog
+
+{- Value configured in the numcopies log. Cached for speed. -}
+getGlobalNumCopies :: Annex (Maybe NumCopies)
+getGlobalNumCopies = maybe globalNumCopiesLoad (return . Just)
+ =<< Annex.getState Annex.globalnumcopies
+
+globalNumCopiesLoad :: Annex (Maybe NumCopies)
+globalNumCopiesLoad = do
+ v <- getLog numcopiesLog
+ Annex.changeState $ \s -> s { Annex.globalnumcopies = v }
+ return v
diff --git a/Logs/PreferredContent.hs b/Logs/PreferredContent.hs
index 2a9aed36bd..4b25ea094c 100644
--- a/Logs/PreferredContent.hs
+++ b/Logs/PreferredContent.hs
@@ -38,13 +38,13 @@ import Types.StandardGroups
{- Checks if a file is preferred content for the specified repository
- (or the current repository if none is specified). -}
-isPreferredContent :: Maybe UUID -> AssumeNotPresent -> FilePath -> Bool -> Annex Bool
-isPreferredContent mu notpresent file def = do
+isPreferredContent :: Maybe UUID -> AssumeNotPresent -> Maybe Key -> AssociatedFile -> Bool -> Annex Bool
+isPreferredContent mu notpresent mkey afile def = do
u <- maybe getUUID return mu
m <- preferredContentMap
case M.lookup u m of
Nothing -> return def
- Just matcher -> checkFileMatcher' matcher file notpresent def
+ Just matcher -> checkMatcher matcher mkey afile notpresent def
{- The map is cached for speed. -}
preferredContentMap :: Annex Annex.PreferredContentMap
diff --git a/Logs/Presence.hs b/Logs/Presence.hs
index 516d59618f..7545f5afc8 100644
--- a/Logs/Presence.hs
+++ b/Logs/Presence.hs
@@ -6,7 +6,7 @@
- A line of the log will look like: "date N INFO"
- Where N=1 when the INFO is present, and 0 otherwise.
-
- - Copyright 2010-2011 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -16,7 +16,8 @@ module Logs.Presence (
addLog,
readLog,
logNow,
- currentLog
+ currentLog,
+ historicalLog
) where
import Data.Time.Clock.POSIX
@@ -24,6 +25,7 @@ import Data.Time.Clock.POSIX
import Logs.Presence.Pure as X
import Common.Annex
import qualified Annex.Branch
+import Git.Types (RefDate)
addLog :: FilePath -> LogLine -> Annex ()
addLog file line = Annex.Branch.change file $ \s ->
@@ -43,3 +45,12 @@ logNow s i = do
{- Reads a log and returns only the info that is still in effect. -}
currentLog :: FilePath -> Annex [String]
currentLog file = map info . filterPresent <$> readLog file
+
+{- Reads a historical version of a log and returns the info that was in
+ - effect at that time.
+ -
+ - The date is formatted as shown in gitrevisions man page.
+ -}
+historicalLog :: RefDate -> FilePath -> Annex [String]
+historicalLog refdate file = map info . filterPresent . parseLog
+ <$> Annex.Branch.getHistorical refdate file
diff --git a/Logs/SingleValue.hs b/Logs/SingleValue.hs
new file mode 100644
index 0000000000..cbebdc8e58
--- /dev/null
+++ b/Logs/SingleValue.hs
@@ -0,0 +1,65 @@
+{- git-annex single-value log
+ -
+ - This is used to store a value in a way that can be union merged.
+ -
+ - A line of the log will look like: "timestamp value"
+ -
+ - The line with the newest timestamp wins.
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Logs.SingleValue where
+
+import Common.Annex
+import qualified Annex.Branch
+
+import qualified Data.Set as S
+import Data.Time.Clock.POSIX
+import Data.Time
+import System.Locale
+
+class SingleValueSerializable v where
+ serialize :: v -> String
+ deserialize :: String -> Maybe v
+
+data LogEntry v = LogEntry
+ { changed :: POSIXTime
+ , value :: v
+ } deriving (Eq, Show, Ord)
+
+type Log v = S.Set (LogEntry v)
+
+showLog :: (SingleValueSerializable v) => Log v -> String
+showLog = unlines . map showline . S.toList
+ where
+ showline (LogEntry t v) = unwords [show t, serialize v]
+
+parseLog :: (Ord v, SingleValueSerializable v) => String -> Log v
+parseLog = S.fromList . mapMaybe parse . lines
+ where
+ parse line = do
+ let (ts, s) = splitword line
+ date <- utcTimeToPOSIXSeconds <$> parseTime defaultTimeLocale "%s%Qs" ts
+ v <- deserialize s
+ Just (LogEntry date v)
+ splitword = separate (== ' ')
+
+newestValue :: Log v -> Maybe v
+newestValue s
+ | S.null s = Nothing
+ | otherwise = Just (value $ S.findMax s)
+
+readLog :: (Ord v, SingleValueSerializable v) => FilePath -> Annex (Log v)
+readLog = parseLog <$$> Annex.Branch.get
+
+getLog :: (Ord v, SingleValueSerializable v) => FilePath -> Annex (Maybe v)
+getLog = newestValue <$$> readLog
+
+setLog :: (SingleValueSerializable v) => FilePath -> v -> Annex ()
+setLog f v = do
+ now <- liftIO getPOSIXTime
+ let ent = LogEntry now v
+ Annex.Branch.change f $ \_old -> showLog (S.singleton ent)
diff --git a/Logs/Transfer.hs b/Logs/Transfer.hs
index 97ec088950..e998a56b14 100644
--- a/Logs/Transfer.hs
+++ b/Logs/Transfer.hs
@@ -29,6 +29,7 @@ import System.Posix.Types (ProcessID)
#else
import System.Win32.Process (ProcessId)
import System.Win32.Process.Current (getCurrentProcessId)
+import Utility.WinLock
#endif
#ifndef mingw32_HOST_OS
@@ -147,7 +148,7 @@ runTransfer t file shouldretry a = do
openFd (transferLockFile tfile) ReadWrite (Just mode)
defaultFileFlags { trunc = True }
case mfd of
- Nothing -> return (mfd, False)
+ Nothing -> return (Nothing, False)
Just fd -> do
locked <- catchMaybeIO $
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
@@ -158,17 +159,28 @@ runTransfer t file shouldretry a = do
return (mfd, False)
#else
prep tfile _mode info = do
- mfd <- catchMaybeIO $ do
- writeFile (transferLockFile tfile) ""
- writeTransferInfoFile info tfile
- return (mfd, False)
+ v <- catchMaybeIO $ lockExclusive (transferLockFile tfile)
+ case v of
+ Nothing -> return (Nothing, False)
+ Just Nothing -> return (Nothing, True)
+ Just (Just lockhandle) -> do
+ void $ tryIO $ writeTransferInfoFile info tfile
+ return (Just lockhandle, False)
#endif
cleanup _ Nothing = noop
- cleanup tfile (Just fd) = do
+ cleanup tfile (Just lockhandle) = do
void $ tryIO $ removeFile tfile
- void $ tryIO $ removeFile $ transferLockFile tfile
#ifndef mingw32_HOST_OS
- closeFd fd
+ void $ tryIO $ removeFile $ transferLockFile tfile
+ closeFd lockhandle
+#else
+ {- Windows cannot delete the lockfile until the lock
+ - is closed. So it's possible to race with another
+ - process that takes the lock before it's removed,
+ - so ignore failure to remove.
+ -}
+ dropLock lockhandle
+ void $ tryIO $ removeFile $ transferLockFile tfile
#endif
retry oldinfo metervar run = do
v <- tryAnnex run
@@ -246,11 +258,14 @@ checkTransfer t = do
Just (pid, _) -> liftIO $ catchDefaultIO Nothing $
readTransferInfoFile (Just pid) tfile
#else
- ifM (liftIO $ doesFileExist $ transferLockFile tfile)
- ( liftIO $ catchDefaultIO Nothing $
+ v <- liftIO $ lockShared $ transferLockFile tfile
+ liftIO $ case v of
+ Nothing -> catchDefaultIO Nothing $
readTransferInfoFile Nothing tfile
- , return Nothing
- )
+ Just lockhandle -> do
+ dropLock lockhandle
+ void $ tryIO $ removeFile $ transferLockFile tfile
+ return Nothing
#endif
{- Gets all currently running transfers. -}
@@ -325,11 +340,8 @@ parseTransferFile file
bits = splitDirectories file
writeTransferInfoFile :: TransferInfo -> FilePath -> IO ()
-writeTransferInfoFile info tfile = do
- h <- openFile tfile WriteMode
- fileEncoding h
- hPutStr h $ writeTransferInfo info
- hClose h
+writeTransferInfoFile info tfile = writeFileAnyEncoding tfile $
+ writeTransferInfo info
{- File format is a header line containing the startedTime and any
- bytesComplete value. Followed by a newline and the associatedFile.
@@ -350,10 +362,8 @@ writeTransferInfo info = unlines
]
readTransferInfoFile :: Maybe PID -> FilePath -> IO (Maybe TransferInfo)
-readTransferInfoFile mpid tfile = catchDefaultIO Nothing $ do
- h <- openFile tfile ReadMode
- fileEncoding h
- hClose h `after` (readTransferInfo mpid <$> hGetContentsStrict h)
+readTransferInfoFile mpid tfile = catchDefaultIO Nothing $
+ readTransferInfo mpid <$> readFileStrictAnyEncoding tfile
readTransferInfo :: Maybe PID -> String -> Maybe TransferInfo
readTransferInfo mpid s = TransferInfo
@@ -370,8 +380,8 @@ readTransferInfo mpid s = TransferInfo
<*> pure False
where
#ifdef mingw32_HOST_OS
- (firstline, rem) = separate (== '\n') s
- (secondline, rest) = separate (== '\n') rem
+ (firstline, otherlines) = separate (== '\n') s
+ (secondline, rest) = separate (== '\n') otherlines
mpid' = readish secondline
#else
(firstline, rest) = separate (== '\n') s
diff --git a/Logs/Unused.hs b/Logs/Unused.hs
index 4de5bc17a3..d26d37dca7 100644
--- a/Logs/Unused.hs
+++ b/Logs/Unused.hs
@@ -1,32 +1,78 @@
{- git-annex unused log file
-
- - Copyright 2010,2012 Joey Hess
+ - This file is stored locally in .git/annex/, not in the git-annex branch.
+ -
+ - The format: "int key timestamp"
+ -
+ - The int is a short, stable identifier that the user can use to
+ - refer to this key. (Equivilant to a filename.)
+ -
+ - The timestamp indicates when the key was first determined to be unused.
+ - Older versions of the log omit the timestamp.
+ -
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
+{-# LANGUAGE CPP #-}
+
module Logs.Unused (
UnusedMap,
- writeUnusedLog,
+ updateUnusedLog,
readUnusedLog,
+ readUnusedMap,
+ dateUnusedLog,
unusedKeys,
+ unusedKeys',
+ setUnusedKeys,
) where
import qualified Data.Map as M
+import qualified Data.Set as S
+import Data.Time.Clock.POSIX
+import Data.Time
+import System.Locale
import Common.Annex
+import qualified Annex
import Types.Key
import Utility.Tmp
+-- everything that is stored in the unused log
+type UnusedLog = M.Map Key (Int, Maybe POSIXTime)
+
+-- used to look up unused keys specified by the user
type UnusedMap = M.Map Int Key
-writeUnusedLog :: FilePath -> [(Int, Key)] -> Annex ()
+log2map :: UnusedLog -> UnusedMap
+log2map = M.fromList . map (\(k, (i, _t)) -> (i, k)) . M.toList
+
+map2log :: POSIXTime -> UnusedMap -> UnusedLog
+map2log t = M.fromList . map (\(i, k) -> (k, (i, Just t))) . M.toList
+
+{- Only keeps keys that are in the new log, but uses any timestamps
+ - those keys had in the old log. -}
+preserveTimestamps :: UnusedLog -> UnusedLog -> UnusedLog
+preserveTimestamps oldl newl = M.intersection (M.unionWith oldts oldl newl) newl
+ where
+ oldts _old@(_, ts) _new@(int, _) = (int, ts)
+
+updateUnusedLog :: FilePath -> UnusedMap -> Annex ()
+updateUnusedLog prefix m = do
+ oldl <- readUnusedLog prefix
+ newl <- preserveTimestamps oldl . flip map2log m <$> liftIO getPOSIXTime
+ writeUnusedLog prefix newl
+
+writeUnusedLog :: FilePath -> UnusedLog -> Annex ()
writeUnusedLog prefix l = do
logfile <- fromRepo $ gitAnnexUnusedLog prefix
- liftIO $ viaTmp writeFile logfile $
- unlines $ map (\(n, k) -> show n ++ " " ++ key2file k) l
+ liftIO $ viaTmp writeFile logfile $ unlines $ map format $ M.toList l
+ where
+ format (k, (i, Just t)) = show i ++ " " ++ key2file k ++ " " ++ show t
+ format (k, (i, Nothing)) = show i ++ " " ++ key2file k
-readUnusedLog :: FilePath -> Annex UnusedMap
+readUnusedLog :: FilePath -> Annex UnusedLog
readUnusedLog prefix = do
f <- fromRepo $ gitAnnexUnusedLog prefix
ifM (liftIO $ doesFileExist f)
@@ -35,11 +81,39 @@ readUnusedLog prefix = do
, return M.empty
)
where
- parse line = case (readish tag, file2key rest) of
- (Just num, Just key) -> Just (num, key)
+ parse line = case (readish sint, file2key skey, utcTimeToPOSIXSeconds <$> parseTime defaultTimeLocale "%s%Qs" ts) of
+ (Just int, Just key, mtimestamp) -> Just (key, (int, mtimestamp))
_ -> Nothing
where
- (tag, rest) = separate (== ' ') line
+ (sint, rest) = separate (== ' ') line
+ (rts, rskey) = separate (== ' ') (reverse rest)
+ skey = reverse rskey
+ ts = reverse rts
-unusedKeys :: Annex [Key]
-unusedKeys = M.elems <$> readUnusedLog ""
+readUnusedMap :: FilePath -> Annex UnusedMap
+readUnusedMap = log2map <$$> readUnusedLog
+
+dateUnusedLog :: FilePath -> Annex (Maybe UTCTime)
+#if MIN_VERSION_directory(1,2,0)
+dateUnusedLog prefix = do
+ f <- fromRepo $ gitAnnexUnusedLog prefix
+ liftIO $ catchMaybeIO $ getModificationTime f
+#else
+#warning foo
+-- old ghc's getModificationTime returned a ClockTime
+dateUnusedLog _prefix = return Nothing
+#endif
+
+{- Set of unused keys. This is cached for speed. -}
+unusedKeys :: Annex (S.Set Key)
+unusedKeys = maybe (setUnusedKeys =<< unusedKeys') return
+ =<< Annex.getState Annex.unusedkeys
+
+unusedKeys' :: Annex [Key]
+unusedKeys' = M.keys <$> readUnusedLog ""
+
+setUnusedKeys :: [Key] -> Annex (S.Set Key)
+setUnusedKeys ks = do
+ let v = S.fromList ks
+ Annex.changeState $ \s -> s { Annex.unusedkeys = Just v }
+ return v
diff --git a/Makefile b/Makefile
index facacfe2e7..76a5f13d09 100644
--- a/Makefile
+++ b/Makefile
@@ -54,6 +54,9 @@ install: build install-docs Build/InstallDesktopFile
test: git-annex
./git-annex test
+retest: git-annex
+ ./git-annex test --rerun-update --rerun-filter failures
+
# hothasktags chokes on some template haskell etc, so ignore errors
tags:
find . | grep -v /.git/ | grep -v /tmp/ | grep -v /dist/ | grep -v /doc/ | egrep '\.hs$$' | xargs hothasktags > tags 2>/dev/null
@@ -73,14 +76,15 @@ docs: $(mans)
--disable-plugin=smiley \
--plugin=comments --set comments_pagespec="*" \
--exclude='news/.*' --exclude='design/assistant/blog/*' \
- --exclude='bugs/*' --exclude='todo/*' --exclude='forum/*'
+ --exclude='bugs/*' --exclude='todo/*' --exclude='forum/*' \
+ --exclude='users/*' --exclude='devblog/*'
clean:
rm -rf tmp dist git-annex $(mans) configure *.tix .hpc \
doc/.ikiwiki html dist tags Build/SysConfig.hs build-stamp \
Setup Build/InstallDesktopFile Build/EvilSplicer \
Build/Standalone Build/OSXMkLibs Build/LinuxMkLibs Build/DistributionUpdate \
- git-union-merge
+ git-union-merge .tasty-rerun-log
find . -name \*.o -exec rm {} \;
find . -name \*.hi -exec rm {} \;
diff --git a/Messages.hs b/Messages.hs
index 0357da12df..9f473110ac 100644
--- a/Messages.hs
+++ b/Messages.hs
@@ -1,12 +1,13 @@
{- git-annex output messages
-
- - Copyright 2010-2011 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Messages (
showStart,
+ showStart',
showNote,
showAction,
showProgress,
@@ -54,10 +55,14 @@ import Types.Key
import qualified Annex
import Utility.Metered
-showStart :: String -> String -> Annex ()
+showStart :: String -> FilePath -> Annex ()
showStart command file = handle (JSON.start command $ Just file) $
flushed $ putStr $ command ++ " " ++ file ++ " "
+showStart' :: String -> Key -> Maybe FilePath -> Annex ()
+showStart' command key afile = showStart command $
+ fromMaybe (key2file key) afile
+
showNote :: String -> Annex ()
showNote s = handle (JSON.note s) $
flushed $ putStr $ "(" ++ s ++ ") "
diff --git a/Remote.hs b/Remote.hs
index e355b09751..f2af025fb3 100644
--- a/Remote.hs
+++ b/Remote.hs
@@ -20,7 +20,7 @@ module Remote (
remoteTypes,
remoteList,
- syncableRemote,
+ gitSyncableRemote,
remoteMap,
uuidDescriptions,
byName,
@@ -41,7 +41,8 @@ module Remote (
showLocations,
forceTrust,
logStatus,
- checkAvailable
+ checkAvailable,
+ isXMPPRemote
) where
import qualified Data.Map as M
@@ -60,6 +61,7 @@ import Logs.Location hiding (logStatus)
import Remote.List
import Config
import Git.Types (RemoteName)
+import qualified Git
{- Map from UUIDs of Remotes to a calculated value. -}
remoteMap :: (Remote -> a) -> Annex (M.Map UUID a)
@@ -292,3 +294,9 @@ byCost = map snd . sortBy (comparing fst) . M.toList . costmap
checkAvailable :: Bool -> Remote -> IO Bool
checkAvailable assumenetworkavailable =
maybe (return assumenetworkavailable) doesDirectoryExist . localpath
+
+{- Remotes using the XMPP transport have urls like xmpp::user@host -}
+isXMPPRemote :: Remote -> Bool
+isXMPPRemote remote = Git.repoIsUrl r && "xmpp::" `isPrefixOf` Git.repoLocation r
+ where
+ r = repo remote
diff --git a/Remote/Bup.hs b/Remote/Bup.hs
index 370cbc1c02..62af704b2b 100644
--- a/Remote/Bup.hs
+++ b/Remote/Bup.hs
@@ -145,9 +145,8 @@ storeEncrypted r buprepo (cipher, enck) k _p =
retrieve :: BupRepo -> Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
retrieve buprepo k _f d _p = do
let params = bupParams "join" buprepo [Param $ bupRef k]
- liftIO $ catchBoolIO $ do
- tofile <- openFile d WriteMode
- pipeBup params Nothing (Just tofile)
+ liftIO $ catchBoolIO $ withFile d WriteMode $
+ pipeBup params Nothing . Just
retrieveCheap :: BupRepo -> Key -> FilePath -> Annex Bool
retrieveCheap _ _ _ = return False
diff --git a/Remote/External/Types.hs b/Remote/External/Types.hs
index 42c71b760a..1e17a2c4c5 100644
--- a/Remote/External/Types.hs
+++ b/Remote/External/Types.hs
@@ -229,11 +229,11 @@ type ProtocolVersion = Int
supportedProtocolVersions :: [ProtocolVersion]
supportedProtocolVersions = [1]
-class Serializable a where
+class ExternalSerializable a where
serialize :: a -> String
deserialize :: String -> Maybe a
-instance Serializable Direction where
+instance ExternalSerializable Direction where
serialize Upload = "STORE"
serialize Download = "RETRIEVE"
@@ -241,23 +241,23 @@ instance Serializable Direction where
deserialize "RETRIEVE" = Just Download
deserialize _ = Nothing
-instance Serializable Key where
+instance ExternalSerializable Key where
serialize = key2file
deserialize = file2key
-instance Serializable [Char] where
+instance ExternalSerializable [Char] where
serialize = id
deserialize = Just
-instance Serializable ProtocolVersion where
+instance ExternalSerializable ProtocolVersion where
serialize = show
deserialize = readish
-instance Serializable Cost where
+instance ExternalSerializable Cost where
serialize = show
deserialize = readish
-instance Serializable Availability where
+instance ExternalSerializable Availability where
serialize GloballyAvailable = "GLOBAL"
serialize LocallyAvailable = "LOCAL"
@@ -265,7 +265,7 @@ instance Serializable Availability where
deserialize "LOCAL" = Just LocallyAvailable
deserialize _ = Nothing
-instance Serializable BytesProcessed where
+instance ExternalSerializable BytesProcessed where
serialize (BytesProcessed n) = show n
deserialize = BytesProcessed <$$> readish
@@ -283,15 +283,15 @@ parse0 :: a -> Parser a
parse0 mk "" = Just mk
parse0 _ _ = Nothing
-parse1 :: Serializable p1 => (p1 -> a) -> Parser a
+parse1 :: ExternalSerializable p1 => (p1 -> a) -> Parser a
parse1 mk p1 = mk <$> deserialize p1
-parse2 :: (Serializable p1, Serializable p2) => (p1 -> p2 -> a) -> Parser a
+parse2 :: (ExternalSerializable p1, ExternalSerializable p2) => (p1 -> p2 -> a) -> Parser a
parse2 mk s = mk <$> deserialize p1 <*> deserialize p2
where
(p1, p2) = splitWord s
-parse3 :: (Serializable p1, Serializable p2, Serializable p3) => (p1 -> p2 -> p3 -> a) -> Parser a
+parse3 :: (ExternalSerializable p1, ExternalSerializable p2, ExternalSerializable p3) => (p1 -> p2 -> p3 -> a) -> Parser a
parse3 mk s = mk <$> deserialize p1 <*> deserialize p2 <*> deserialize p3
where
(p1, rest) = splitWord s
diff --git a/Remote/Git.hs b/Remote/Git.hs
index e292707e41..d714cfec52 100644
--- a/Remote/Git.hs
+++ b/Remote/Git.hs
@@ -34,9 +34,9 @@ import qualified Annex.Url as Url
import Utility.Tmp
import Config
import Config.Cost
-import Init
+import Annex.Init
import Types.Key
-import qualified Fields
+import qualified CmdLine.GitAnnexShell.Fields as Fields
import Logs.Location
import Utility.Metered
#ifndef mingw32_HOST_OS
@@ -111,7 +111,7 @@ gen r u c gc
, retrieveKeyFile = copyFromRemote new
, retrieveKeyFileCheap = copyFromRemoteCheap new
, removeKey = dropKey new
- , hasKey = inAnnex r
+ , hasKey = inAnnex new
, hasKeyCheap = repoCheap r
, whereisKey = Nothing
, remoteFsck = if Git.repoIsUrl r
@@ -197,7 +197,12 @@ tryGitConfigRead r
Left _ -> do
set_ignore "not usable by git-annex"
return r
- Right r' -> return r'
+ Right r' -> do
+ -- Cache when http remote is not bare for
+ -- optimisation.
+ unless (Git.Config.isBare r') $
+ setremote "annex-bare" (Git.Config.boolConfig False)
+ return r'
store = observe $ \r' -> do
g <- gitRepo
@@ -222,12 +227,18 @@ tryGitConfigRead r
set_ignore "does not have git-annex installed"
return r
- set_ignore msg = case Git.remoteName r of
+ set_ignore msg = do
+ let k = "annex-ignore"
+ case Git.remoteName r of
+ Nothing -> noop
+ Just n -> warning $ "Remote " ++ n ++ " " ++ msg ++ "; setting " ++ k
+ setremote k (Git.Config.boolConfig True)
+
+ setremote k v = case Git.remoteName r of
Nothing -> noop
Just n -> do
- let k = "remote." ++ n ++ ".annex-ignore"
- warning $ "Remote " ++ n ++ " " ++ msg ++ "; setting " ++ k
- inRepo $ Git.Command.run [Param "config", Param k, Param "true"]
+ let k' = "remote." ++ n ++ "." ++ k
+ inRepo $ Git.Command.run [Param "config", Param k', Param v]
handlegcrypt Nothing = return r
handlegcrypt (Just _cacheduuid) = do
@@ -242,15 +253,16 @@ tryGitConfigRead r
- If the remote cannot be accessed, or if it cannot determine
- whether it has the content, returns a Left error message.
-}
-inAnnex :: Git.Repo -> Key -> Annex (Either String Bool)
-inAnnex r key
+inAnnex :: Remote -> Key -> Annex (Either String Bool)
+inAnnex rmt key
| Git.repoIsHttp r = checkhttp =<< getHttpHeaders
| Git.repoIsUrl r = checkremote
| otherwise = checklocal
where
+ r = repo rmt
checkhttp headers = do
showChecking r
- ifM (anyM (\u -> Url.withUserAgent $ Url.checkBoth u headers (keySize key)) (keyUrls r key))
+ ifM (anyM (\u -> Url.withUserAgent $ Url.checkBoth u headers (keySize key)) (keyUrls rmt key))
( return $ Right True
, return $ Left "not found"
)
@@ -263,14 +275,19 @@ inAnnex r key
dispatch (Right (Just b)) = Right b
dispatch (Right Nothing) = cantCheck r
-keyUrls :: Git.Repo -> Key -> [String]
-keyUrls r key = map tourl locs
+keyUrls :: Remote -> Key -> [String]
+keyUrls r key = map tourl locs'
where
- tourl l = Git.repoLocation r ++ "/" ++ l
+ tourl l = Git.repoLocation (repo r) ++ "/" ++ l
+ -- If the remote is known to not be bare, try the hash locations
+ -- used for non-bare repos first, as an optimisation.
+ locs
+ | remoteAnnexBare (gitconfig r) == Just False = reverse (annexLocations key)
+ | otherwise = annexLocations key
#ifndef mingw32_HOST_OS
- locs = annexLocations key
+ locs' = locs
#else
- locs = map (replace "\\" "/") (annexLocations key)
+ locs' = map (replace "\\" "/") (annexLocations key)
#endif
dropKey :: Remote -> Key -> Annex Bool
@@ -293,7 +310,7 @@ copyFromRemote r key file dest _p = copyFromRemote' r key file dest
copyFromRemote' :: Remote -> Key -> AssociatedFile -> FilePath -> Annex Bool
copyFromRemote' r key file dest
| not $ Git.repoIsUrl (repo r) = guardUsable (repo r) False $ do
- let params = Ssh.rsyncParams r
+ let params = Ssh.rsyncParams r Download
u <- getUUID
-- run copy from perspective of remote
liftIO $ onLocal (repo r) $ do
@@ -309,7 +326,7 @@ copyFromRemote' r key file dest
direct <- isDirect
Ssh.rsyncHelper (Just feeder)
=<< Ssh.rsyncParamsRemote direct r Download key dest file
- | Git.repoIsHttp (repo r) = Annex.Content.downloadUrl (keyUrls (repo r) key) dest
+ | Git.repoIsHttp (repo r) = Annex.Content.downloadUrl (keyUrls r key) dest
| otherwise = error "copying from non-ssh, non-http remote not supported"
where
{- Feed local rsync's progress info back to the remote,
@@ -392,7 +409,7 @@ copyToRemote r key file p
-- the remote's Annex, but it needs access to the current
-- Annex monad's state.
checksuccessio <- Annex.withCurrentState checksuccess
- let params = Ssh.rsyncParams r
+ let params = Ssh.rsyncParams r Upload
u <- getUUID
-- run copy from perspective of remote
liftIO $ onLocal (repo r) $ ifM (Annex.Content.inAnnex key)
diff --git a/Remote/Helper/Hooks.hs b/Remote/Helper/Hooks.hs
index 91c6318bf3..f876649f07 100644
--- a/Remote/Helper/Hooks.hs
+++ b/Remote/Helper/Hooks.hs
@@ -17,6 +17,8 @@ import qualified Annex
import Annex.LockPool
#ifndef mingw32_HOST_OS
import Annex.Perms
+#else
+import Utility.WinLock
#endif
{- Modifies a remote's access functions to first run the
@@ -73,13 +75,13 @@ runHooks r starthook stophook a = do
run starthook
Annex.addCleanup (remoteid ++ "-stop-command") $ runstop lck
-#ifndef mingw32_HOST_OS
runstop lck = do
-- Drop any shared lock we have, and take an
-- exclusive lock, without blocking. If the lock
-- succeeds, we're the only process using this remote,
-- so can stop it.
unlockFile lck
+#ifndef mingw32_HOST_OS
mode <- annexFileMode
fd <- liftIO $ noUmask mode $
openFd lck ReadWrite (Just mode) defaultFileFlags
@@ -90,5 +92,10 @@ runHooks r starthook stophook a = do
Right _ -> run stophook
liftIO $ closeFd fd
#else
- runstop _lck = run stophook
+ v <- liftIO $ lockExclusive lck
+ case v of
+ Nothing -> noop
+ Just lockhandle -> do
+ run stophook
+ liftIO $ dropLock lockhandle
#endif
diff --git a/Remote/Helper/Ssh.hs b/Remote/Helper/Ssh.hs
index 8cf9275a0c..8de88953f6 100644
--- a/Remote/Helper/Ssh.hs
+++ b/Remote/Helper/Ssh.hs
@@ -12,8 +12,8 @@ import qualified Git
import qualified Git.Url
import Annex.UUID
import Annex.Ssh
-import Fields (Field, fieldName)
-import qualified Fields
+import CmdLine.GitAnnexShell.Fields (Field, fieldName)
+import qualified CmdLine.GitAnnexShell.Fields as Fields
import Types.GitConfig
import Types.Key
import Remote.Helper.Messages
@@ -122,7 +122,7 @@ rsyncParamsRemote direct r direction key file afile = do
fields
-- Convert the ssh command into rsync command line.
let eparam = rsyncShell (Param shellcmd:shellparams)
- let o = rsyncParams r
+ let o = rsyncParams r direction
return $ if direction == Download
then o ++ rsyncopts eparam dummy (File file)
else o ++ rsyncopts eparam (File file) dummy
@@ -140,7 +140,11 @@ rsyncParamsRemote direct r direction key file afile = do
dummy = Param "dummy:"
-- --inplace to resume partial files
-rsyncParams :: Remote -> [CommandParam]
-rsyncParams r = Params "--progress --inplace" :
- map Param (remoteAnnexRsyncOptions $ gitconfig r)
-
+rsyncParams :: Remote -> Direction -> [CommandParam]
+rsyncParams r direction = Params "--progress --inplace" :
+ map Param (remoteAnnexRsyncOptions gc ++ dps)
+ where
+ dps
+ | direction == Download = remoteAnnexRsyncDownloadOptions gc
+ | otherwise = remoteAnnexRsyncUploadOptions gc
+ gc = gitconfig r
diff --git a/Remote/List.hs b/Remote/List.hs
index 31a9209b15..e3afc939ca 100644
--- a/Remote/List.hs
+++ b/Remote/List.hs
@@ -111,6 +111,6 @@ updateRemote remote = do
| otherwise = return r
{- Checks if a remote is syncable using git. -}
-syncableRemote :: Remote -> Bool
-syncableRemote r = remotetype r `elem`
+gitSyncableRemote :: Remote -> Bool
+gitSyncableRemote r = remotetype r `elem`
[ Remote.Git.remote, Remote.GCrypt.remote ]
diff --git a/Remote/Rsync.hs b/Remote/Rsync.hs
index 409b5b7601..e27286d5a0 100644
--- a/Remote/Rsync.hs
+++ b/Remote/Rsync.hs
@@ -41,12 +41,15 @@ import Utility.Rsync
import Utility.CopyFile
import Utility.Metered
import Annex.Perms
+import Logs.Transfer
type RsyncUrl = String
data RsyncOpts = RsyncOpts
{ rsyncUrl :: RsyncUrl
, rsyncOptions :: [CommandParam]
+ , rsyncUploadOptions :: [CommandParam]
+ , rsyncDownloadOptions :: [CommandParam]
, rsyncShellEscape :: Bool
}
@@ -93,10 +96,16 @@ gen r u c gc = do
}
genRsyncOpts :: RemoteConfig -> RemoteGitConfig -> [CommandParam] -> RsyncUrl -> RsyncOpts
-genRsyncOpts c gc transport url = RsyncOpts url (transport ++ opts) escape
+genRsyncOpts c gc transport url = RsyncOpts
+ { rsyncUrl = url
+ , rsyncOptions = opts []
+ , rsyncUploadOptions = transport ++ opts (remoteAnnexRsyncUploadOptions gc)
+ , rsyncDownloadOptions = transport ++ opts (remoteAnnexRsyncDownloadOptions gc)
+ , rsyncShellEscape = M.lookup "shellescape" c /= Just "no"
+ }
where
- opts = map Param $ filter safe $ remoteAnnexRsyncOptions gc
- escape = M.lookup "shellescape" c /= Just "no"
+ opts specificopts = map Param $ filter safe $
+ remoteAnnexRsyncOptions gc ++ specificopts
safe opt
-- Don't allow user to pass --delete to rsync;
-- that could cause it to delete other keys
@@ -257,7 +266,7 @@ withRsyncScratchDir a = do
rsyncRetrieve :: RsyncOpts -> Key -> FilePath -> Maybe MeterUpdate -> Annex Bool
rsyncRetrieve o k dest callback =
- showResumable $ untilTrue (rsyncUrls o k) $ \u -> rsyncRemote o callback
+ showResumable $ untilTrue (rsyncUrls o k) $ \u -> rsyncRemote Download o callback
-- use inplace when retrieving to support resuming
[ Param "--inplace"
, Param u
@@ -272,13 +281,15 @@ showResumable a = ifM a
return False
)
-rsyncRemote :: RsyncOpts -> Maybe MeterUpdate -> [CommandParam] -> Annex Bool
-rsyncRemote o callback params = do
+rsyncRemote :: Direction -> RsyncOpts -> Maybe MeterUpdate -> [CommandParam] -> Annex Bool
+rsyncRemote direction o callback params = do
showOutput -- make way for progress bar
- liftIO $ (maybe rsync rsyncProgress callback) ps
+ liftIO $ (maybe rsync rsyncProgress callback) $
+ opts ++ [Params "--progress"] ++ params
where
- defaultParams = [Params "--progress"]
- ps = rsyncOptions o ++ defaultParams ++ params
+ opts
+ | direction == Download = rsyncDownloadOptions o
+ | otherwise = rsyncUploadOptions o
{- To send a single key is slightly tricky; need to build up a temporary
- directory structure to pass to rsync so it can create the hash
@@ -296,12 +307,12 @@ rsyncSend o callback k canrename src = withRsyncScratchDir $ \tmp -> do
liftIO $ createDirectoryIfMissing True $ parentDir dest
ok <- liftIO $ if canrename
then do
- renameFile src dest
+ rename src dest
return True
else createLinkOrCopy src dest
ps <- sendParams
if ok
- then showResumable $ rsyncRemote o (Just callback) $ ps ++
+ then showResumable $ rsyncRemote Upload o (Just callback) $ ps ++
[ Param "--recursive"
, partialParams
-- tmp/ to send contents of tmp dir
diff --git a/Test.hs b/Test.hs
index 2f632f61d1..7cbf6dbfdc 100644
--- a/Test.hs
+++ b/Test.hs
@@ -13,14 +13,16 @@ import Test.Tasty
import Test.Tasty.Runners
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
-
-import System.PosixCompat.Files
-import Control.Exception.Extensible
+import Test.Tasty.Ingredients.Rerun
import Data.Monoid
+
+import Options.Applicative hiding (command)
+import Control.Exception.Extensible
import qualified Data.Map as M
import System.IO.HVFS (SystemFS(..))
import qualified Text.JSON
import System.Path
+import qualified Data.ByteString.Lazy as L
import Common
@@ -30,6 +32,7 @@ import qualified Annex.UUID
import qualified Backend
import qualified Git.CurrentRepo
import qualified Git.Filename
+import qualified Git.Types
import qualified Locations
import qualified Types.KeySource
import qualified Types.Backend
@@ -48,7 +51,8 @@ import qualified Types.Messages
import qualified Config
import qualified Config.Cost
import qualified Crypto
-import qualified Init
+import qualified Annex.Init
+import qualified Annex.CatFile
import qualified Utility.Path
import qualified Utility.FileMode
import qualified Build.SysConfig
@@ -63,8 +67,9 @@ import qualified Utility.Exception
import qualified Utility.Hash
import qualified Utility.Scheduled
import qualified Utility.HumanTime
+import qualified Utility.ThreadScheduler
#ifndef mingw32_HOST_OS
-import qualified GitAnnex
+import qualified CmdLine.GitAnnex as GitAnnex
import qualified Remote.Helper.Encryptable
import qualified Types.Crypto
import qualified Utility.Gpg
@@ -72,33 +77,45 @@ import qualified Utility.Gpg
type TestEnv = M.Map String String
-main :: IO ()
-main = do
+main :: [String] -> IO ()
+main ps = do
+ let tests = testGroup "Tests"
+ -- Test both direct and indirect mode.
+ -- Windows is only going to use direct mode,
+ -- so don't test twice.
+ [ properties
#ifndef mingw32_HOST_OS
- indirectenv <- prepare False
- directenv <- prepare True
- let tests = testGroup "Tests"
- [ localOption (QuickCheckTests 1000) properties
- , unitTests directenv "(direct)"
- , unitTests indirectenv "(indirect)"
- ]
+ , withTestEnv True $ unitTests "(direct)"
+ , withTestEnv False $ unitTests "(indirect)"
#else
- -- Windows is only going to use direct mode, so don't test twice.
- env <- prepare False
- let tests = testGroup "Tests"
- [properties, unitTests env ""]
+ , withTestEnv False $ unitTests ""
#endif
- let runner = tryIngredients [consoleTestReporter] mempty tests
- ifM (maybe (error "tasty failed to return a runner!") id runner)
- ( exitSuccess
- , do
- putStrLn " (This could be due to a bug in git-annex, or an incompatability"
- putStrLn " with utilities, such as git, installed on this system.)"
- exitFailure
- )
+ ]
+
+ -- Can't use tasty's defaultMain because one of the command line
+ -- parameters is "test".
+ let pinfo = info (helper <*> suiteOptionParser ingredients tests)
+ ( fullDesc <> header "Builtin test suite" )
+ opts <- either (\f -> error =<< errMessage f "git-annex test") return $
+ execParserPure (prefs idm) pinfo ps
+ case tryIngredients ingredients opts tests of
+ Nothing -> error "No tests found!?"
+ Just act -> ifM act
+ ( exitSuccess
+ , do
+ putStrLn " (This could be due to a bug in git-annex, or an incompatability"
+ putStrLn " with utilities, such as git, installed on this system.)"
+ exitFailure
+ )
+
+ingredients :: [Ingredient]
+ingredients =
+ [ rerunningTests [consoleTestReporter]
+ , listingTests
+ ]
properties :: TestTree
-properties = testGroup "QuickCheck"
+properties = localOption (QuickCheckTests 1000) $ testGroup "QuickCheck"
[ testProperty "prop_idempotent_deencode_git" Git.Filename.prop_idempotent_deencode
, testProperty "prop_idempotent_deencode" Utility.Format.prop_idempotent_deencode
, testProperty "prop_idempotent_fileKey" Locations.prop_idempotent_fileKey
@@ -129,13 +146,20 @@ properties = testGroup "QuickCheck"
, testProperty "prop_duration_roundtrips" Utility.HumanTime.prop_duration_roundtrips
]
-unitTests :: TestEnv -> String -> TestTree
-unitTests env note = testGroup ("Unit Tests " ++ note)
- -- test order matters, later tests may rely on state from earlier
+{- These tests set up the test environment, but also test some basic parts
+ - of git-annex. They are always run before the unitTests. -}
+initTests :: TestEnv -> TestTree
+initTests env = testGroup ("Init Tests")
[ check "init" test_init
, check "add" test_add
- , check "add sha1dup" test_add_sha1dup
- , check "add subdirs" test_add_subdirs
+ ]
+ where
+ check desc t = testCase desc (t env)
+
+unitTests :: String -> IO TestEnv -> TestTree
+unitTests note getenv = testGroup ("Unit Tests " ++ note)
+ [ check "add sha1dup" test_add_sha1dup
+ , check "add extras" test_add_extras
, check "reinject" test_reinject
, check "unannex (no copy)" test_unannex_nocopy
, check "unannex (with copy)" test_unannex_withcopy
@@ -166,6 +190,7 @@ unitTests env note = testGroup ("Unit Tests " ++ note)
, check "union merge regression" test_union_merge_regression
, check "conflict resolution" test_conflict_resolution_movein_bug
, check "conflict_resolution (mixed directory and file)" test_mixed_conflict_resolution
+ , check "conflict_resolution (mixed directory and file) 2" test_mixed_conflict_resolution2
, check "map" test_map
, check "uninit" test_uninit
, check "uninit (in git-annex branch)" test_uninit_inbranch
@@ -177,14 +202,12 @@ unitTests env note = testGroup ("Unit Tests " ++ note)
, check "bup remote" test_bup_remote
, check "crypto" test_crypto
, check "preferred content" test_preferred_content
- , check "global cleanup" test_global_cleanup
+ , check "add subdirs" test_add_subdirs
]
where
- check desc t = testCase desc (t env)
-
-test_global_cleanup :: TestEnv -> Assertion
-test_global_cleanup _env = cleanup tmpdir
+ check desc t = testCase desc (getenv >>= t)
+-- this test case create the main repo
test_init :: TestEnv -> Assertion
test_init env = innewrepo env $ do
git_annex env "init" [reponame] @? "init failed"
@@ -203,19 +226,13 @@ test_add env = inmainrepo env $ do
git_annex env "add" [sha1annexedfile, "--backend=SHA1"] @? "add with SHA1 failed"
annexed_present sha1annexedfile
checkbackend sha1annexedfile backendSHA1
- writeFile wormannexedfile $ content wormannexedfile
- git_annex env "add" [wormannexedfile, "--backend=WORM"] @? "add with WORM failed"
- annexed_present wormannexedfile
- checkbackend wormannexedfile backendWORM
ifM (annexeval Config.isDirect)
( do
- boolSystem "rm" [Params "-f", File wormannexedfile] @? "rm failed"
writeFile ingitfile $ content ingitfile
not <$> boolSystem "git" [Param "add", File ingitfile] @? "git add failed to fail in direct mode"
boolSystem "rm" [Params "-f", File ingitfile] @? "rm failed"
git_annex env "sync" [] @? "sync failed"
, do
- boolSystem "git" [Params "rm --force -q", File wormannexedfile] @? "git rm failed"
writeFile ingitfile $ content ingitfile
boolSystem "git" [Param "add", File ingitfile] @? "git add failed"
boolSystem "git" [Params "commit -q -m commit"] @? "git commit failed"
@@ -230,18 +247,12 @@ test_add_sha1dup env = intmpclonerepo env $ do
annexed_present sha1annexedfiledup
annexed_present sha1annexedfile
-test_add_subdirs :: TestEnv -> Assertion
-test_add_subdirs env = intmpclonerepo env $ do
- createDirectory "dir"
- writeFile ("dir" > "foo") $ content annexedfile
- git_annex env "add" ["dir"] @? "add of subdir failed"
- createDirectory "dir2"
- writeFile ("dir2" > "foo") $ content annexedfile
-#ifndef mingw32_HOST_OS
- {- This does not work on Windows, for whatever reason. -}
- setCurrentDirectory "dir"
- git_annex env "add" [".." > "dir2"] @? "add of ../subdir failed"
-#endif
+test_add_extras :: TestEnv -> Assertion
+test_add_extras env = intmpclonerepo env $ do
+ writeFile wormannexedfile $ content wormannexedfile
+ git_annex env "add" [wormannexedfile, "--backend=WORM"] @? "add with WORM failed"
+ annexed_present wormannexedfile
+ checkbackend wormannexedfile backendWORM
test_reinject :: TestEnv -> Assertion
test_reinject env = intmpclonerepoInDirect env $ do
@@ -292,6 +303,9 @@ test_drop_withremote :: TestEnv -> Assertion
test_drop_withremote env = intmpclonerepo env $ do
git_annex env "get" [annexedfile] @? "get failed"
annexed_present annexedfile
+ git_annex env "numcopies" ["2"] @? "numcopies config failed"
+ not <$> git_annex env "drop" [annexedfile] @? "drop succeeded although numcopies is not satisfied"
+ git_annex env "numcopies" ["1"] @? "numcopies config failed"
git_annex env "drop" [annexedfile] @? "drop failed though origin has copy"
annexed_notpresent annexedfile
inmainrepo env $ annexed_present annexedfile
@@ -511,9 +525,9 @@ test_trust env = intmpclonerepo env $ do
test_fsck_basic :: TestEnv -> Assertion
test_fsck_basic env = intmpclonerepo env $ do
git_annex env "fsck" [] @? "fsck failed"
- boolSystem "git" [Params "config annex.numcopies 2"] @? "git config failed"
+ git_annex env "numcopies" ["2"] @? "numcopies config failed"
fsck_should_fail env "numcopies unsatisfied"
- boolSystem "git" [Params "config annex.numcopies 1"] @? "git config failed"
+ git_annex env "numcopies" ["1"] @? "numcopies config failed"
corrupt annexedfile
corrupt sha1annexedfile
where
@@ -542,7 +556,7 @@ test_fsck_localuntrusted env = intmpclonerepo env $ do
test_fsck_remoteuntrusted :: TestEnv -> Assertion
test_fsck_remoteuntrusted env = intmpclonerepo env $ do
- boolSystem "git" [Params "config annex.numcopies 2"] @? "git config failed"
+ git_annex env "numcopies" ["2"] @? "numcopies config failed"
git_annex env "get" [annexedfile] @? "get failed"
git_annex env "get" [sha1annexedfile] @? "get failed"
git_annex env "fsck" [] @? "fsck failed with numcopies=2 and 2 copies"
@@ -661,7 +675,7 @@ test_unused env = intmpclonerepoInDirect env $ do
where
checkunused expectedkeys desc = do
git_annex env "unused" [] @? "unused failed"
- unusedmap <- annexeval $ Logs.Unused.readUnusedLog ""
+ unusedmap <- annexeval $ Logs.Unused.readUnusedMap ""
let unusedkeys = M.elems unusedmap
assertEqual ("unused keys differ " ++ desc)
(sort expectedkeys) (sort unusedkeys)
@@ -758,6 +772,7 @@ test_conflict_resolution_movein_bug env = withtmpclonerepo env False $ \r1 -> do
forM_ [r1, r2] $ \r -> indir env r $ do
{- Get all files, see check below. -}
git_annex env "get" [] @? "get failed"
+ disconnectOrigin
pair env r1 r2
forM_ [r1, r2] $ \r -> indir env r $ do
{- Set up a conflict. -}
@@ -792,39 +807,62 @@ test_mixed_conflict_resolution env = do
check_mixed_conflict inr1 = withtmpclonerepo env False $ \r1 ->
withtmpclonerepo env False $ \r2 -> do
indir env r1 $ do
+ disconnectOrigin
writeFile conflictor "conflictor"
git_annex env "add" [conflictor] @? "add conflicter failed"
- git_annex env "sync" [] @? "sync failed"
+ git_annex env "sync" [] @? "sync failed in r1"
+ indir env r2 $ do
+ disconnectOrigin
+ createDirectory conflictor
+ writeFile (conflictor > "subfile") "subfile"
+ git_annex env "add" [conflictor] @? "add conflicter failed"
+ git_annex env "sync" [] @? "sync failed in r2"
+ pair env r1 r2
+ let l = if inr1 then [r1, r2] else [r2, r1]
+ forM_ l $ \r -> indir env r $
+ git_annex env "sync" [] @? "sync failed in mixed conflict"
+ checkmerge "r1" r1
+ checkmerge "r1" r2
+ conflictor = "conflictor"
+ variantprefix = conflictor ++ ".variant"
+ checkmerge what d = do
+ doesDirectoryExist (d > conflictor) @? (d ++ " conflictor directory missing")
+ l <- getDirectoryContents d
+ any (variantprefix `isPrefixOf`) l
+ @? (what ++ " conflictor file missing in: " ++ show l )
+
+{-
+ - During conflict resolution, one of the annexed files in git is
+ - accidentially converted from a symlink to a regular file.
+ - This only happens on crippled filesystems.
+ -
+ - This test case happens to detect the problem when it tries the next
+ - pass of conflict resolution, since it's unable to resolve a conflict
+ - between an annexed and non-annexed file.
+ -}
+test_mixed_conflict_resolution2 :: TestEnv -> Assertion
+test_mixed_conflict_resolution2 env = go >> go
+ where
+ go = withtmpclonerepo env False $ \r1 ->
+ withtmpclonerepo env False $ \r2 -> do
+ indir env r1 $ do
+ writeFile conflictor "conflictor"
+ git_annex env "add" [conflictor] @? "add conflicter failed"
+ git_annex env "sync" [] @? "sync failed in r1"
indir env r2 $ do
createDirectory conflictor
writeFile (conflictor > "subfile") "subfile"
git_annex env "add" [conflictor] @? "add conflicter failed"
- git_annex env "sync" [] @? "sync failed"
- pair env r1 r2
- let r = if inr1 then r1 else r2
- indir env r $ do
- git_annex env "sync" [] @? "sync failed in mixed conflict"
- checkmerge r1
- checkmerge r2
- where
- conflictor = "conflictor"
- variantprefix = conflictor ++ ".variant"
- checkmerge d = do
- doesDirectoryExist (d > conflictor) @? (d ++ " conflictor directory missing")
- (any (variantprefix `isPrefixOf`)
- <$> getDirectoryContents d)
- @? (d ++ "conflictor file missing")
+ git_annex env "sync" [] @? "sync failed in r2"
+ conflictor = "conflictor"
-{- Set up repos as remotes of each other;
- - remove origin since we're going to sync
- - some changes to a file. -}
+{- Set up repos as remotes of each other. -}
pair :: TestEnv -> FilePath -> FilePath -> Assertion
pair env r1 r2 = forM_ [r1, r2] $ \r -> indir env r $ do
when (r /= r1) $
boolSystem "git" [Params "remote add r1", File ("../../" ++ r1)] @? "remote add"
when (r /= r2) $
boolSystem "git" [Params "remote add r2", File ("../../" ++ r2)] @? "remote add"
- boolSystem "git" [Params "remote rm origin"] @? "remote rm"
test_map :: TestEnv -> Assertion
test_map env = intmpclonerepo env $ do
@@ -925,7 +963,8 @@ test_rsync_remote env = intmpclonerepo env $ do
not <$> git_annex env "drop" [annexedfile, "--numcopies=2"] @? "drop failed to fail"
annexed_present annexedfile
#else
- -- this test doesn't work in Windows TODO
+ -- Rsync remotes with a rsyncurl of a directory do not currently
+ -- work on Windows.
noop
#endif
@@ -1020,6 +1059,23 @@ test_crypto env = do
test_crypto _env = putStrLn "gpg testing not implemented on Windows"
#endif
+test_add_subdirs :: TestEnv -> Assertion
+test_add_subdirs env = intmpclonerepo env $ do
+ createDirectory "dir"
+ writeFile ("dir" > "foo") $ "dir/" ++ content annexedfile
+ git_annex env "add" ["dir"] @? "add of subdir failed"
+
+ {- Regression test for Windows bug where symlinks were not
+ - calculated correctly for files in subdirs. -}
+ git_annex env "sync" [] @? "sync failed"
+ l <- annexeval $ encodeW8 . L.unpack <$> Annex.CatFile.catObject (Git.Types.Ref "HEAD:dir/foo")
+ "../.git/annex/" `isPrefixOf` l @? ("symlink from subdir to .git/annex is wrong: " ++ l)
+
+ createDirectory "dir2"
+ writeFile ("dir2" > "foo") $ content annexedfile
+ setCurrentDirectory "dir"
+ git_annex env "add" [".." > "dir2"] @? "add of ../subdir failed"
+
-- This is equivilant to running git-annex, but it's all run in-process
-- (when the OS allows) so test coverage collection works.
git_annex :: TestEnv -> String -> [String] -> IO Bool
@@ -1083,7 +1139,7 @@ intmpclonerepoInDirect env a = intmpclonerepo env $
)
where
isdirect = annexeval $ do
- Init.initialize Nothing
+ Annex.Init.initialize Nothing
Config.isDirect
intmpbareclonerepo :: TestEnv -> Assertion -> Assertion
@@ -1094,6 +1150,9 @@ withtmpclonerepo env bare a = do
dir <- tmprepodir
bracket (clonerepo env mainrepodir dir bare) cleanup a
+disconnectOrigin :: Assertion
+disconnectOrigin = boolSystem "git" [Params "remote rm origin"] @? "remote rm"
+
withgitrepo :: TestEnv -> (FilePath -> Assertion) -> Assertion
withgitrepo env = bracket (setuprepo env mainrepodir) return
@@ -1114,9 +1173,7 @@ setuprepo env dir = do
cleanup dir
ensuretmpdir
boolSystem "git" [Params "init -q", File dir] @? "git init failed"
- indir env dir $ do
- boolSystem "git" [Params "config user.name", Param "Test User"] @? "git config failed"
- boolSystem "git" [Params "config user.email test@example.com"] @? "git config failed"
+ configrepo env dir
return dir
-- clones are always done as local clones; we cannot test ssh clones
@@ -1128,11 +1185,17 @@ clonerepo env old new bare = do
boolSystem "git" [Params ("clone -q" ++ b), File old, File new] @? "git clone failed"
indir env new $
git_annex env "init" ["-q", new] @? "git annex init failed"
+ configrepo env new
when (not bare) $
indir env new $
handleforcedirect env
return new
+configrepo :: TestEnv -> FilePath -> IO ()
+configrepo env dir = indir env dir $ do
+ boolSystem "git" [Params "config user.name", Param "Test User"] @? "git config failed"
+ boolSystem "git" [Params "config user.email test@example.com"] @? "git config failed"
+
handleforcedirect :: TestEnv -> IO ()
handleforcedirect env = when (M.lookup "FORCEDIRECT" env == Just "1") $
git_annex env "direct" ["-q"] @? "git annex direct failed"
@@ -1144,16 +1207,24 @@ ensuretmpdir = do
createDirectory tmpdir
cleanup :: FilePath -> IO ()
-cleanup dir = do
- e <- doesDirectoryExist dir
- when e $ do
- -- git-annex prevents annexed file content from being
- -- removed via directory permissions; undo
- recurseDir SystemFS dir >>=
- filterM doesDirectoryExist >>=
- mapM_ Utility.FileMode.allowWrite
- -- For unknown reasons, this sometimes fails on Windows.
- void $ tryIO $ removeDirectoryRecursive dir
+cleanup = cleanup' False
+
+cleanup' :: Bool -> FilePath -> IO ()
+cleanup' final dir = whenM (doesDirectoryExist dir) $ do
+ -- Allow all files and directories to be written to, so
+ -- they can be deleted. Both git and git-annex use file
+ -- permissions to prevent deletion.
+ recurseDir SystemFS dir >>=
+ mapM_ (void . tryIO . Utility.FileMode.allowWrite)
+ -- This sometimes fails on Windows, due to some files
+ -- being still opened by a subprocess.
+ catchIO (removeDirectoryRecursive dir) $ \e -> do
+ when final $ do
+ print e
+ putStrLn "sleeping 10 seconds and will retry directory cleanup"
+ Utility.ThreadScheduler.threadDelaySeconds (Utility.ThreadScheduler.Seconds 10)
+ whenM (doesDirectoryExist dir) $ do
+ removeDirectoryRecursive dir
checklink :: FilePath -> Assertion
checklink f = do
@@ -1242,8 +1313,24 @@ annexed_present = runchecks
unannexed :: FilePath -> Assertion
unannexed = runchecks [checkregularfile, checkcontent, checkwritable]
-prepare :: Bool -> IO TestEnv
-prepare forcedirect = do
+withTestEnv :: Bool -> (IO TestEnv -> TestTree) -> TestTree
+withTestEnv forcedirect = withResource prepare release
+ where
+ prepare = do
+ env <- prepareTestEnv forcedirect
+ case tryIngredients [consoleTestReporter] mempty (initTests env) of
+ Nothing -> error "No tests found!?"
+ Just act -> unlessM act $
+ error "init tests failed! cannot continue"
+ return env
+ release = releaseTestEnv
+
+releaseTestEnv :: TestEnv -> IO ()
+releaseTestEnv _env = do
+ cleanup' True tmpdir
+
+prepareTestEnv :: Bool -> IO TestEnv
+prepareTestEnv forcedirect = do
whenM (doesDirectoryExist tmpdir) $
error $ "The temporary directory " ++ tmpdir ++ " already exists; cannot run test suite."
diff --git a/Types/Command.hs b/Types/Command.hs
index d012c6e257..ecde75cae5 100644
--- a/Types/Command.hs
+++ b/Types/Command.hs
@@ -18,9 +18,9 @@ import Types
data CommandCheck = CommandCheck { idCheck :: Int, runCheck :: Annex () }
{- b. The seek stage takes the parameters passed to the command,
- looks through the repo to find the ones that are relevant
- - to that command (ie, new files to add), and generates
- - a list of start stage actions. -}
-type CommandSeek = [String] -> Annex [CommandStart]
+ - to that command (ie, new files to add), and runs commandAction
+ - to handle all necessary actions. -}
+type CommandSeek = [String] -> Annex ()
{- c. The start stage is run before anything is printed about the
- command, is passed some input, and can early abort it
- if the input does not make sense. It should run quickly and
@@ -42,7 +42,7 @@ data Command = Command
, cmdnomessages :: Bool -- don't output normal messages
, cmdname :: String
, cmdparamdesc :: String -- description of params for usage
- , cmdseek :: [CommandSeek] -- seek stage
+ , cmdseek :: CommandSeek
, cmdsection :: CommandSection
, cmddesc :: String -- description of command for usage
}
diff --git a/Types/FileMatcher.hs b/Types/FileMatcher.hs
index fc442b6041..e2d4eadc1b 100644
--- a/Types/FileMatcher.hs
+++ b/Types/FileMatcher.hs
@@ -7,6 +7,12 @@
module Types.FileMatcher where
+import Types.Key (Key)
+
+data MatchInfo
+ = MatchingFile FileInfo
+ | MatchingKey Key
+
data FileInfo = FileInfo
{ relFile :: FilePath -- may be relative to cwd
, matchFile :: FilePath -- filepath to match on; may be relative to top
diff --git a/Types/GitConfig.hs b/Types/GitConfig.hs
index cda53f229a..ab3dbd7b91 100644
--- a/Types/GitConfig.hs
+++ b/Types/GitConfig.hs
@@ -1,6 +1,6 @@
{- git-annex configuration
-
- - Copyright 2012 Joey Hess
+ - Copyright 2012-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -19,12 +19,14 @@ import Utility.DataUnits
import Config.Cost
import Types.Distribution
import Types.Availability
+import Types.NumCopies
+import Utility.HumanTime
{- Main git-annex settings. Each setting corresponds to a git-config key
- such as annex.foo -}
data GitConfig = GitConfig
{ annexVersion :: Maybe String
- , annexNumCopies :: Int
+ , annexNumCopies :: Maybe NumCopies
, annexDiskReserve :: Integer
, annexDirect :: Bool
, annexBackends :: [String]
@@ -45,6 +47,8 @@ data GitConfig = GitConfig
, annexLargeFiles :: Maybe String
, annexFsckNudge :: Bool
, annexAutoUpgrade :: AutoUpgrade
+ , annexExpireUnused :: Maybe (Maybe Duration)
+ , annexSecureEraseCommand :: Maybe String
, coreSymlinks :: Bool
, gcryptId :: Maybe String
}
@@ -52,7 +56,7 @@ data GitConfig = GitConfig
extractGitConfig :: Git.Repo -> GitConfig
extractGitConfig r = GitConfig
{ annexVersion = notempty $ getmaybe (annex "version")
- , annexNumCopies = get (annex "numcopies") 1
+ , annexNumCopies = NumCopies <$> getmayberead (annex "numcopies")
, annexDiskReserve = fromMaybe onemegabyte $
readSize dataUnits =<< getmaybe (annex "diskreserve")
, annexDirect = getbool (annex "direct") False
@@ -74,11 +78,13 @@ extractGitConfig r = GitConfig
, annexLargeFiles = getmaybe (annex "largefiles")
, annexFsckNudge = getbool (annex "fscknudge") True
, annexAutoUpgrade = toAutoUpgrade $ getmaybe (annex "autoupgrade")
+ , annexExpireUnused = maybe Nothing Just . parseDuration
+ <$> getmaybe (annex "expireunused")
+ , annexSecureEraseCommand = getmaybe (annex "secure-erase-command")
, coreSymlinks = getbool "core.symlinks" True
, gcryptId = getmaybe "core.gcrypt-id"
}
where
- get k def = fromMaybe def $ getmayberead k
getbool k def = fromMaybe def $ getmaybebool k
getmaybebool k = Git.Config.isTrue =<< getmaybe k
getmayberead k = readish =<< getmaybe k
@@ -103,11 +109,14 @@ data RemoteGitConfig = RemoteGitConfig
, remoteAnnexStartCommand :: Maybe String
, remoteAnnexStopCommand :: Maybe String
, remoteAnnexAvailability :: Maybe Availability
+ , remoteAnnexBare :: Maybe Bool
{- These settings are specific to particular types of remotes
- including special remotes. -}
, remoteAnnexSshOptions :: [String]
, remoteAnnexRsyncOptions :: [String]
+ , remoteAnnexRsyncUploadOptions :: [String]
+ , remoteAnnexRsyncDownloadOptions :: [String]
, remoteAnnexRsyncTransport :: [String]
, remoteAnnexGnupgOptions :: [String]
, remoteAnnexRsyncUrl :: Maybe String
@@ -133,9 +142,12 @@ extractRemoteGitConfig r remotename = RemoteGitConfig
, remoteAnnexStartCommand = notempty $ getmaybe "start-command"
, remoteAnnexStopCommand = notempty $ getmaybe "stop-command"
, remoteAnnexAvailability = getmayberead "availability"
+ , remoteAnnexBare = getmaybebool "bare"
, remoteAnnexSshOptions = getoptions "ssh-options"
, remoteAnnexRsyncOptions = getoptions "rsync-options"
+ , remoteAnnexRsyncDownloadOptions = getoptions "rsync-download-options"
+ , remoteAnnexRsyncUploadOptions = getoptions "rsync-upload-options"
, remoteAnnexRsyncTransport = getoptions "rsync-transport"
, remoteAnnexGnupgOptions = getoptions "gnupg-options"
, remoteAnnexRsyncUrl = notempty $ getmaybe "rsyncurl"
diff --git a/Types/Limit.hs b/Types/Limit.hs
index 4436f6953d..2b009a7585 100644
--- a/Types/Limit.hs
+++ b/Types/Limit.hs
@@ -17,4 +17,4 @@ import qualified Data.Set as S
type MkLimit = String -> Either String MatchFiles
type AssumeNotPresent = S.Set UUID
-type MatchFiles = AssumeNotPresent -> FileInfo -> Annex Bool
+type MatchFiles = AssumeNotPresent -> MatchInfo -> Annex Bool
diff --git a/Types/LockPool.hs b/Types/LockPool.hs
new file mode 100644
index 0000000000..dd392f28b6
--- /dev/null
+++ b/Types/LockPool.hs
@@ -0,0 +1,24 @@
+{- git-annex lock pool data types
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE CPP #-}
+
+module Types.LockPool (
+ LockPool,
+ LockHandle
+) where
+
+import qualified Data.Map as M
+
+#ifndef mingw32_HOST_OS
+import System.Posix.Types (Fd)
+type LockHandle = Fd
+#else
+import Utility.WinLock -- defines LockHandle
+#endif
+
+type LockPool = M.Map FilePath LockHandle
diff --git a/Types/NumCopies.hs b/Types/NumCopies.hs
new file mode 100644
index 0000000000..b93fcf9688
--- /dev/null
+++ b/Types/NumCopies.hs
@@ -0,0 +1,14 @@
+{- git-annex numcopies type
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Types.NumCopies where
+
+newtype NumCopies = NumCopies Int
+ deriving (Ord, Eq)
+
+fromNumCopies :: NumCopies -> Int
+fromNumCopies (NumCopies n) = n
diff --git a/Types/StandardGroups.hs b/Types/StandardGroups.hs
index 51788ec4e9..d95f28ee1b 100644
--- a/Types/StandardGroups.hs
+++ b/Types/StandardGroups.hs
@@ -75,12 +75,12 @@ associatedDirectory _ _ = Nothing
{- See doc/preferred_content.mdwn for explanations of these expressions. -}
preferredContent :: StandardGroup -> PreferredContentExpression
preferredContent ClientGroup = lastResort $
- "(exclude=*/archive/* and exclude=archive/*) or (" ++ notArchived ++ ")"
+ "((exclude=*/archive/* and exclude=archive/*) or (" ++ notArchived ++ ")) and not unused"
preferredContent TransferGroup = lastResort $
"not (inallgroup=client and copies=client:2) and (" ++ preferredContent ClientGroup ++ ")"
-preferredContent BackupGroup = "include=*"
+preferredContent BackupGroup = "include=* or unused"
preferredContent IncrementalBackupGroup = lastResort
- "include=* and (not copies=incrementalbackup:1)"
+ "(include=* or unused) and (not copies=incrementalbackup:1)"
preferredContent SmallArchiveGroup = lastResort $
"(include=*/archive/* or include=archive/*) and (" ++ preferredContent FullArchiveGroup ++ ")"
preferredContent FullArchiveGroup = lastResort notArchived
@@ -93,6 +93,8 @@ notArchived :: String
notArchived = "not (copies=archive:1 or copies=smallarchive:1)"
{- Most repositories want any content that is only on untrusted
- - or dead repositories. -}
+ - or dead repositories, or that otherwise does not have enough copies.
+ - Does not look at .gitattributes since that is quite a lot slower.
+ -}
lastResort :: String -> PreferredContentExpression
-lastResort s = "(" ++ s ++ ") or (not copies=semitrusted+:1)"
+lastResort s = "(" ++ s ++ ") or approxlackingcopies=1"
diff --git a/Utility/Daemon.hs b/Utility/Daemon.hs
index 12beb235a4..afba68535f 100644
--- a/Utility/Daemon.hs
+++ b/Utility/Daemon.hs
@@ -18,7 +18,7 @@ import Utility.LogFile
import System.Posix
import Control.Concurrent.Async
#else
-import System.PosixCompat
+import System.PosixCompat.Types
#endif
{- Run an action as a daemon, with all output sent to a file descriptor.
@@ -77,7 +77,7 @@ lockPidFile file = do
#else
writeFile newfile "-1"
#endif
- renameFile newfile file
+ rename newfile file
where
newfile = file ++ ".new"
diff --git a/Utility/DirWatcher/Win32Notify.hs b/Utility/DirWatcher/Win32Notify.hs
index 27175e1c8b..ba786839c1 100644
--- a/Utility/DirWatcher/Win32Notify.hs
+++ b/Utility/DirWatcher/Win32Notify.hs
@@ -11,7 +11,7 @@ import Common hiding (isDirectory)
import Utility.DirWatcher.Types
import System.Win32.Notify
-import qualified System.PosixCompat.Files as Files
+import qualified Utility.PosixFiles as Files
watchDir :: FilePath -> (FilePath -> Bool) -> WatchHooks -> IO WatchManager
watchDir dir ignored hooks = do
diff --git a/Utility/Directory.hs b/Utility/Directory.hs
index 6caee7efa4..c457de6e3d 100644
--- a/Utility/Directory.hs
+++ b/Utility/Directory.hs
@@ -10,7 +10,6 @@
module Utility.Directory where
import System.IO.Error
-import System.PosixCompat.Files
import System.Directory
import Control.Exception (throw)
import Control.Monad
@@ -19,6 +18,7 @@ import System.FilePath
import Control.Applicative
import System.IO.Unsafe (unsafeInterleaveIO)
+import Utility.PosixFiles
import Utility.SafeCommand
import Utility.Tmp
import Utility.Exception
diff --git a/Utility/DiskFree.hs b/Utility/DiskFree.hs
index f04f636ecc..2f296e2cb9 100644
--- a/Utility/DiskFree.hs
+++ b/Utility/DiskFree.hs
@@ -1,13 +1,16 @@
{- disk free space checking
-
- - Copyright 2012 Joey Hess
+ - Copyright 2012, 2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE ForeignFunctionInterface, CPP #-}
-module Utility.DiskFree ( getDiskFree ) where
+module Utility.DiskFree (
+ getDiskFree,
+ getDiskSize
+) where
#ifdef WITH_CLIBS
@@ -20,9 +23,12 @@ import Foreign.C.Error
foreign import ccall safe "libdiskfree.h diskfree" c_diskfree
:: CString -> IO CULLong
-getDiskFree :: FilePath -> IO (Maybe Integer)
-getDiskFree path = withFilePath path $ \c_path -> do
- free <- c_diskfree c_path
+foreign import ccall safe "libdiskfree.h disksize" c_disksize
+ :: CString -> IO CULLong
+
+getVal :: (CString -> IO CULLong) -> FilePath -> IO (Maybe Integer)
+getVal getter path = withFilePath path $ \c_path -> do
+ free <- getter c_path
ifM (safeErrno <$> getErrno)
( return $ Just $ toInteger free
, return Nothing
@@ -30,6 +36,12 @@ getDiskFree path = withFilePath path $ \c_path -> do
where
safeErrno (Errno v) = v == 0
+getDiskFree :: FilePath -> IO (Maybe Integer)
+getDiskFree = getVal c_diskfree
+
+getDiskSize :: FilePath -> IO (Maybe Integer)
+getDiskSize = getVal c_disksize
+
#else
#ifdef mingw32_HOST_OS
@@ -41,6 +53,9 @@ getDiskFree :: FilePath -> IO (Maybe Integer)
getDiskFree path = catchMaybeIO $ do
(sectors, bytes, nfree, _ntotal) <- getDiskFreeSpace (Just path)
return $ toInteger sectors * toInteger bytes * toInteger nfree
+
+getDiskSize :: FilePath -> IO (Maybe Integer)
+getDiskSize _ = return Nothing
#else
#warning Building without disk free space checking support
@@ -48,5 +63,8 @@ getDiskFree path = catchMaybeIO $ do
getDiskFree :: FilePath -> IO (Maybe Integer)
getDiskFree _ = return Nothing
+getDiskSize :: FilePath -> IO (Maybe Integer)
+getDiskSize _ = return Nothing
+
#endif
#endif
diff --git a/Utility/FileMode.hs b/Utility/FileMode.hs
index 46c6a31f5f..b17cadc3bc 100644
--- a/Utility/FileMode.hs
+++ b/Utility/FileMode.hs
@@ -133,10 +133,8 @@ setSticky f = modifyFileMode f $ addModes [stickyMode]
- as writeFile.
-}
writeFileProtected :: FilePath -> String -> IO ()
-writeFileProtected file content = do
- h <- openFile file WriteMode
+writeFileProtected file content = withFile file WriteMode $ \h -> do
void $ tryIO $
modifyFileMode file $
removeModes [groupReadMode, otherReadMode]
hPutStr h content
- hClose h
diff --git a/Utility/HumanTime.hs b/Utility/HumanTime.hs
index 644e6fbabf..297b2bd973 100644
--- a/Utility/HumanTime.hs
+++ b/Utility/HumanTime.hs
@@ -7,7 +7,10 @@
module Utility.HumanTime (
Duration(..),
+ durationSince,
durationToPOSIXTime,
+ durationToDays,
+ daysToDuration,
parseDuration,
fromDuration,
prop_duration_roundtrips
@@ -17,6 +20,7 @@ import Utility.PartialPrelude
import Utility.Applicative
import Utility.QuickCheck
+import Data.Time.Clock
import Data.Time.Clock.POSIX (POSIXTime)
import Data.Char
import Control.Applicative
@@ -25,9 +29,20 @@ import qualified Data.Map as M
newtype Duration = Duration { durationSeconds :: Integer }
deriving (Eq, Ord, Read, Show)
+durationSince :: UTCTime -> IO Duration
+durationSince pasttime = do
+ now <- getCurrentTime
+ return $ Duration $ round $ diffUTCTime now pasttime
+
durationToPOSIXTime :: Duration -> POSIXTime
durationToPOSIXTime = fromIntegral . durationSeconds
+durationToDays :: Duration -> Integer
+durationToDays d = durationSeconds d `div` dsecs
+
+daysToDuration :: Integer -> Duration
+daysToDuration i = Duration $ i * dsecs
+
{- Parses a human-input time duration, of the form "5h", "1m", "5h1m", etc -}
parseDuration :: String -> Maybe Duration
parseDuration = Duration <$$> go 0
diff --git a/Utility/LogFile.hs b/Utility/LogFile.hs
index 090ac60d0e..1c29b9ff4f 100644
--- a/Utility/LogFile.hs
+++ b/Utility/LogFile.hs
@@ -30,7 +30,7 @@ rotateLog logfile = go 0
| num > maxLogs = return ()
| otherwise = whenM (doesFileExist currfile) $ do
go (num + 1)
- renameFile currfile nextfile
+ rename currfile nextfile
where
currfile = filename num
nextfile = filename (num + 1)
diff --git a/Utility/Misc.hs b/Utility/Misc.hs
index 68199c8283..20007adad0 100644
--- a/Utility/Misc.hs
+++ b/Utility/Misc.hs
@@ -33,13 +33,20 @@ hGetContentsStrict = hGetContents >=> \s -> length s `seq` return s
readFileStrict :: FilePath -> IO String
readFileStrict = readFile >=> \s -> length s `seq` return s
-{- Reads a file strictly, and using the FileSystemEncofing, so it will
+{- Reads a file strictly, and using the FileSystemEncoding, so it will
- never crash on a badly encoded file. -}
readFileStrictAnyEncoding :: FilePath -> IO String
readFileStrictAnyEncoding f = withFile f ReadMode $ \h -> do
fileEncoding h
hClose h `after` hGetContentsStrict h
+{- Writes a file, using the FileSystemEncoding so it will never crash
+ - on a badly encoded content string. -}
+writeFileAnyEncoding :: FilePath -> String -> IO ()
+writeFileAnyEncoding f content = withFile f WriteMode $ \h -> do
+ fileEncoding h
+ hPutStr h content
+
{- Like break, but the item matching the condition is not included
- in the second result list.
-
diff --git a/Utility/Path.hs b/Utility/Path.hs
index 44ac72f068..2bcd110d83 100644
--- a/Utility/Path.hs
+++ b/Utility/Path.hs
@@ -1,6 +1,6 @@
{- path manipulation
-
- - Copyright 2010-2013 Joey Hess
+ - Copyright 2010-2014 Joey Hess
-
- Licensed under the GNU GPL version 3 or higher.
-}
@@ -21,28 +21,60 @@ import Control.Applicative
import Data.Char
import qualified System.FilePath.Posix as Posix
#else
-import qualified "MissingH" System.Path as MissingH
import System.Posix.Files
#endif
+import qualified "MissingH" System.Path as MissingH
import Utility.Monad
import Utility.UserInfo
-{- Makes a path absolute if it's not already.
+{- Simplifies a path, removing any ".." or ".", and removing the trailing
+ - path separator.
+ -
+ - On Windows, preserves whichever style of path separator might be used in
+ - the input FilePaths. This is done because some programs in Windows
+ - demand a particular path separator -- and which one actually varies!
+ -
+ - This does not guarantee that two paths that refer to the same location,
+ - and are both relative to the same location (or both absolute) will
+ - yeild the same result. Run both through normalise from System.FilePath
+ - to ensure that.
+ -}
+simplifyPath :: FilePath -> FilePath
+simplifyPath path = dropTrailingPathSeparator $
+ joinDrive drive $ joinPath $ norm [] $ splitPath path'
+ where
+ (drive, path') = splitDrive path
+
+ norm c [] = reverse c
+ norm c (p:ps)
+ | p' == ".." = norm (drop 1 c) ps
+ | p' == "." = norm c ps
+ | otherwise = norm (p:c) ps
+ where
+ p' = dropTrailingPathSeparator p
+
+{- Makes a path absolute.
+ -
- The first parameter is a base directory (ie, the cwd) to use if the path
- is not already absolute.
-
- - On Unix, collapses and normalizes ".." etc in the path. May return Nothing
- - if the path cannot be normalized.
- -
- - MissingH's absNormPath does not work on Windows, so on Windows
- - no normalization is done.
+ - Does not attempt to deal with edge cases or ensure security with
+ - untrusted inputs.
-}
-absNormPath :: FilePath -> FilePath -> Maybe FilePath
+absPathFrom :: FilePath -> FilePath -> FilePath
+absPathFrom dir path = simplifyPath (combine dir path)
+
+{- On Windows, this converts the paths to unix-style, in order to run
+ - MissingH's absNormPath on them. Resulting path will use / separators. -}
+absNormPathUnix :: FilePath -> FilePath -> Maybe FilePath
#ifndef mingw32_HOST_OS
-absNormPath dir path = MissingH.absNormPath dir path
+absNormPathUnix dir path = MissingH.absNormPath dir path
#else
-absNormPath dir path = Just $ combine dir path
+absNormPathUnix dir path = todos <$> MissingH.absNormPath (fromdos dir) (fromdos path)
+ where
+ fromdos = replace "\\" "/"
+ todos = replace "/" "\\"
#endif
{- Returns the parent directory of a path.
@@ -72,13 +104,13 @@ prop_parentDir_basics dir
- are all equivilant.
-}
dirContains :: FilePath -> FilePath -> Bool
-dirContains a b = a == b || a' == b' || (a'++[pathSeparator]) `isPrefixOf` b'
+dirContains a b = a == b || a' == b' || (addTrailingPathSeparator a') `isPrefixOf` b'
where
- norm p = fromMaybe "" $ absNormPath p "."
a' = norm a
b' = norm b
+ norm = normalise . simplifyPath
-{- Converts a filename into a normalized, absolute path.
+{- Converts a filename into an absolute path.
-
- Unlike Directory.canonicalizePath, this does not require the path
- already exists. -}
@@ -87,13 +119,6 @@ absPath file = do
cwd <- getCurrentDirectory
return $ absPathFrom cwd file
-{- Converts a filename into a normalized, absolute path
- - from the specified cwd. -}
-absPathFrom :: FilePath -> FilePath -> FilePath
-absPathFrom cwd file = fromMaybe bad $ absNormPath cwd file
- where
- bad = error $ "unable to normalize " ++ file
-
{- Constructs a relative path from the CWD to a file.
-
- For example, assuming CWD is /tmp/foo/bar:
@@ -105,7 +130,7 @@ relPathCwdToFile f = relPathDirToFile <$> getCurrentDirectory <*> absPath f
{- Constructs a relative path from a directory to a file.
-
- - Both must be absolute, and normalized (eg with absNormpath).
+ - Both must be absolute, and cannot contain .. etc. (eg use absPath first).
-}
relPathDirToFile :: FilePath -> FilePath -> FilePath
relPathDirToFile from to = join s $ dotdots ++ uncommon
diff --git a/Utility/PosixFiles.hs b/Utility/PosixFiles.hs
new file mode 100644
index 0000000000..23edc25c9b
--- /dev/null
+++ b/Utility/PosixFiles.hs
@@ -0,0 +1,33 @@
+{- POSIX files (and compatablity wrappers).
+ -
+ - This is like System.PosixCompat.Files, except with a fixed rename.
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE CPP #-}
+
+module Utility.PosixFiles (
+ module X,
+ rename
+) where
+
+import System.PosixCompat.Files as X hiding (rename)
+
+#ifndef mingw32_HOST_OS
+import System.Posix.Files (rename)
+#else
+import qualified System.Win32.File as Win32
+#endif
+
+{- System.PosixCompat.Files.rename on Windows calls renameFile,
+ - so cannot rename directories.
+ -
+ - Instead, use Win32 moveFile, which can. It needs to be told to overwrite
+ - any existing file. -}
+#ifdef mingw32_HOST_OS
+rename :: FilePath -> FilePath -> IO ()
+rename src dest = Win32.moveFileEx src dest Win32.mOVEFILE_REPLACE_EXISTING
+#endif
diff --git a/Utility/SshConfig.hs b/Utility/SshConfig.hs
index d6cd320787..080f6479f4 100644
--- a/Utility/SshConfig.hs
+++ b/Utility/SshConfig.hs
@@ -127,9 +127,13 @@ writeSshConfig f s = do
{- Ensure that the ssh config file lacks any group or other write bits,
- since ssh is paranoid about not working if other users can write
- - to one of its config files (.ssh/config and .ssh/authorized_keys) -}
+ - to one of its config files (.ssh/config and .ssh/authorized_keys).
+ -
+ - If the chmod fails, ignore the failure, as it might be a filesystem like
+ - Android's that does not support file modes.
+ -}
setSshConfigMode :: FilePath -> IO ()
-setSshConfigMode f = modifyFileMode f $
+setSshConfigMode f = void $ tryIO $ modifyFileMode f $
removeModes [groupWriteMode, otherWriteMode]
sshDir :: IO FilePath
diff --git a/Utility/Tmp.hs b/Utility/Tmp.hs
index 891ce50835..f46e1a5ee5 100644
--- a/Utility/Tmp.hs
+++ b/Utility/Tmp.hs
@@ -13,10 +13,11 @@ import Control.Exception (bracket)
import System.IO
import System.Directory
import Control.Monad.IfElse
+import System.FilePath
import Utility.Exception
-import System.FilePath
import Utility.FileSystemEncoding
+import Utility.PosixFiles
type Template = String
@@ -30,7 +31,7 @@ viaTmp a file content = do
(tmpfile, handle) <- openTempFile dir (base ++ ".tmp")
hClose handle
a tmpfile content
- renameFile tmpfile file
+ rename tmpfile file
{- Runs an action with a tmp file located in the system's tmp directory
- (or in "." if there is none) then removes the file. -}
diff --git a/Utility/WinLock.hs b/Utility/WinLock.hs
new file mode 100644
index 0000000000..7b7cf7132c
--- /dev/null
+++ b/Utility/WinLock.hs
@@ -0,0 +1,69 @@
+{- Windows lock files
+ -
+ - Copyright 2014 Joey Hess
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Utility.WinLock (
+ lockShared,
+ lockExclusive,
+ dropLock,
+ waitToLock,
+ LockHandle
+) where
+
+import System.Win32.Types
+import System.Win32.File
+import Control.Concurrent
+
+{- Locking is exclusive, and prevents the file from being opened for read
+ - or write by any other process. So for advisory locking of a file, a
+ - different LockFile should be used. -}
+type LockFile = FilePath
+
+type LockHandle = HANDLE
+
+{- Tries to lock a file with a shared lock, which allows other processes to
+ - also lock it shared. Fails is the file is exclusively locked. -}
+lockShared :: LockFile -> IO (Maybe LockHandle)
+lockShared = openLock fILE_SHARE_READ
+
+{- Tries to take an exclusive lock on a file. Fails if another process has
+ - a shared or exclusive lock. -}
+lockExclusive :: LockFile -> IO (Maybe LockHandle)
+lockExclusive = openLock fILE_SHARE_NONE
+
+{- Windows considers just opening a file enough to lock it. This will
+ - create the LockFile if it does not already exist.
+ -
+ - Will fail if the file is already open with an incompatable ShareMode.
+ - Note that this may happen if an unrelated process, such as a virus
+ - scanner, even looks at the file. See http://support.microsoft.com/kb/316609
+ -
+ - Note that createFile busy-waits to try to avoid failing when some other
+ - process briefly has a file open. But that would make checking locks
+ - much more expensive, so is not done here. Thus, the use of c_CreateFile.
+ -}
+openLock :: ShareMode -> LockFile -> IO (Maybe LockHandle)
+openLock sharemode f = do
+ h <- withTString f $ \c_f ->
+ c_CreateFile c_f gENERIC_READ sharemode (maybePtr Nothing)
+ oPEN_ALWAYS fILE_ATTRIBUTE_NORMAL (maybePtr Nothing)
+ return $ if h == iNVALID_HANDLE_VALUE
+ then Nothing
+ else Just h
+
+dropLock :: LockHandle -> IO ()
+dropLock = closeHandle
+
+{- If the initial lock fails, this is a BUSY wait, and does not
+ - guarentee FIFO order of waiters. In other news, Windows is a POS. -}
+waitToLock :: IO (Maybe LockHandle) -> IO LockHandle
+waitToLock locker = takelock
+ where
+ takelock = go =<< locker
+ go (Just lck) = return lck
+ go Nothing = do
+ threadDelay (500000) -- half a second
+ takelock
diff --git a/Utility/libdiskfree.c b/Utility/libdiskfree.c
index d2843ed203..8c9ab6145b 100644
--- a/Utility/libdiskfree.c
+++ b/Utility/libdiskfree.c
@@ -1,6 +1,6 @@
/* disk free space checking, C mini-library
*
- * Copyright 2012 Joey Hess
+ * Copyright 2012, 2014 Joey Hess
*
* Licensed under the GNU GPL version 3 or higher.
*/
@@ -43,16 +43,12 @@
#include
#include
-/* Checks the amount of disk that is available to regular (non-root) users.
- * (If there's an error, or this is not supported,
- * returns 0 and sets errno to nonzero.)
- */
-unsigned long long int diskfree(const char *path) {
+unsigned long long int get(const char *path, int req) {
#ifdef UNKNOWN
errno = 1;
return 0;
#else
- unsigned long long int available, blocksize;
+ unsigned long long int v, blocksize;
struct STATSTRUCT buf;
if (STATCALL(path, &buf) != 0)
@@ -60,12 +56,35 @@ unsigned long long int diskfree(const char *path) {
else
errno = 0;
- available = buf.f_bavail;
+ switch (req) {
+ case 0:
+ v = buf.f_blocks;
+ break;
+ case 1:
+ v = buf.f_bavail;
+ break;
+ default:
+ v = 0;
+ }
+
blocksize = buf.f_bsize;
- return available * blocksize;
+ return v * blocksize;
#endif
}
+/* Checks the amount of disk that is available to regular (non-root) users.
+ * (If there's an error, or this is not supported,
+ * returns 0 and sets errno to nonzero.)
+ */
+unsigned long long int diskfree(const char *path) {
+ return get(path, 1);
+}
+
+/* Gets the total size of the disk. */
+unsigned long long int disksize(const char *path) {
+ return get(path, 0);
+}
+
/*
main () {
printf("%lli\n", diskfree("."));
diff --git a/debian/changelog b/debian/changelog
index b454a2d3cf..a1a47219e6 100644
--- a/debian/changelog
+++ b/debian/changelog
@@ -1,3 +1,104 @@
+git-annex (5.20140210~bpo70+2) wheezy-backports; urgency=medium
+
+ * Updating backport to newest release.
+ * Remaining differences in this backport:
+ - No webdav special remote support.
+ - Test suite is not built into git-annex as it now uses haskell-tasty,
+ which is not yet backported.
+ - No skein hash support.
+
+ -- Joey Hess Thu, 20 Feb 2014 22:56:45 +0000
+
+git-annex (5.20140210) unstable; urgency=medium
+
+ * --in can now refer to files that were located in a repository at
+ some past date. For example, --in="here@{yesterday}"
+ * Fixed direct mode annexed content locking code, which is used to
+ guard against recursive file drops.
+ * This is the first beta-level release of the Windows port with important
+ fixes (see below).
+ (The webapp and assistant are still alpha-level on Windows.)
+ * sync --content: Honor annex-ignore configuration.
+ * sync: Don't try to sync with xmpp remotes, which are only currently
+ supported when using the assistant.
+ * sync --content: Re-pull from remotes after downloading content,
+ since that can take a while and other changes may be pushed in the
+ meantime.
+ * sync --content: Reuse smart copy code from copy command, including
+ handling and repairing out of date location tracking info.
+ Closes: #737480
+ * sync --content: Drop files from remotes that don't want them after
+ getting them.
+ * sync: Fix bug in automatic merge conflict resolution code when used
+ on a filesystem not supporting symlinks, which resulted in it losing
+ track of the symlink bit of annexed files.
+ * Added ways to configure rsync options to be used only when uploading
+ or downloading from a remote. Useful to eg limit upload bandwidth.
+ * Fix initremote with encryption=pubkey to work with S3, glacier, webdav,
+ and external special remotes.
+ * Avoid building with DAV 0.6 which is badly broken (see #737902).
+ * Fix dropping of unused keys with spaces in their name.
+ * Fix build on platforms not supporting the webapp.
+ * Document in man page that sshcaching uses ssh ControlMaster.
+ Closes: #737476
+ * Windows: It's now safe to run multiple git-annex processes concurrently
+ on Windows; the lock files have been sorted out.
+ * Windows: Avoid using unix-compat's rename, which refuses to rename
+ directories.
+ * Windows: Fix deletion of repositories by test suite and webapp.
+ * Windows: Test suite 100% passes again.
+ * Windows: Fix bug in symlink calculation code.
+ * Windows: Fix handling of absolute unix-style git repository paths.
+ * Android: Avoid crashing when unable to set file mode for ssh config file
+ due to Android filesystem horribleness.
+
+ -- Joey Hess Mon, 10 Feb 2014 12:54:57 -0400
+
+git-annex (5.20140127) unstable; urgency=medium
+
+ * sync --content: New option that makes the content of annexed files be
+ transferred. Similar to the assistant, this honors any configured
+ preferred content expressions.
+ * Remove --json option from commands not supporting it.
+ * status: Support --json.
+ * list: Fix specifying of files to list.
+ * Allow --all to be mixed with matching options like --copies and --in
+ (but not --include and --exclude).
+ * numcopies: New command, sets global numcopies value that is seen by all
+ clones of a repository.
+ * The annex.numcopies git config setting is deprecated. Once the numcopies
+ command is used to set the global number of copies, any annex.numcopies
+ git configs will be ignored.
+ * assistant: Make the prefs page set the global numcopies.
+ * Add lackingcopies, approxlackingcopies, and unused to
+ preferred content expressions.
+ * Client, transfer, incremental backup, and archive repositories
+ now want to get content that does not yet have enough copies.
+ * Client, transfer, and source repositories now do not want to retain
+ unused file contents.
+ * assistant: Checks daily for unused file contents, and when possible
+ moves them to a repository (such as a backup repository) that
+ wants to retain them.
+ * assistant: annex.expireunused can be configured to cause unused
+ file contents to be deleted after some period of time.
+ * webapp: Nudge user to see if they want to expire old unused file
+ contents when a lot of them seem to be piling up in the repository.
+ * repair: Check git version at run time.
+ * assistant: Run the periodic git gc in batch mode.
+ * added annex.secure-erase-command config option.
+ * test suite: Use tasty-rerun, and expose tasty command-line options.
+ * Optimise non-bare http remotes; no longer does a 404 to the wrong
+ url every time before trying the right url. Needs annex-bare to be
+ set to false, which is done when initially probing the uuid of a
+ http remote.
+ * webapp: After upgrading a git repository to git-annex, fix
+ bug that made it temporarily not be synced with.
+ * whereis: Support --all.
+ * All commands that support --all also support a --key option,
+ which limits them to acting on a single key.
+
+ -- Joey Hess Mon, 27 Jan 2014 13:43:28 -0400
+
git-annex (5.20140117~bpo70+2) wheezy-backports; urgency=medium
* Version build-dep on haskell-gnutls, so that backport will build with
diff --git a/doc/assistant/unused.png b/doc/assistant/unused.png
new file mode 100644
index 0000000000..b0ace763cf
Binary files /dev/null and b/doc/assistant/unused.png differ
diff --git a/doc/bugs/--json_is_broken_for_status.mdwn b/doc/bugs/--json_is_broken_for_status.mdwn
new file mode 100644
index 0000000000..0ce9dc7fa1
--- /dev/null
+++ b/doc/bugs/--json_is_broken_for_status.mdwn
@@ -0,0 +1,34 @@
+### Please describe the problem.
+
+bad json produced
+
+### What steps will reproduce the problem?
+
+
+[[!format sh """
+$> git annex status --json
+,"success":true}
+
+in another one
+
+$> git annex status --json
+D hardware/g-box/builds/mine/.#yoh-debug-lastdidnotconnect.txt
+,"success":true}
+"""]]
+
+### What version of git-annex are you using? On what operating system?
+
+Debian sid 5.20140116
+
+### 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.
+"""]]
+
+> Not all commands support json. Made this explict by making --json not be
+> a global option. Added --json support to status. [[done]]. --[[Joey]]
diff --git a/doc/bugs/Android:_Adding_Repository_on_Box.net_fails_with___34__Internal_Server_Error__34__.mdwn b/doc/bugs/Android:_Adding_Repository_on_Box.net_fails_with___34__Internal_Server_Error__34__.mdwn
new file mode 100644
index 0000000000..d7035432aa
--- /dev/null
+++ b/doc/bugs/Android:_Adding_Repository_on_Box.net_fails_with___34__Internal_Server_Error__34__.mdwn
@@ -0,0 +1,22 @@
+### Please describe the problem.
+On Andorid adding a respository on box.net account to an exisiting repository does not work. The following error message is displayed:
+
+
+Internal Server Error
+WebDAV failed to write file: /etc/ssl/certs/: getDirectoryContents: does not exist (No such file or directory): user error
+
+The directory does not exist, indeed.
+
+### What steps will reproduce the problem?
+Add a repository on a Box.net server to an existing repository from the webapp (encrypted and shared with other devices and friends). The error appears after clicking on "Add repository"
+
+
+### What version of git-annex are you using? On what operating system?
+
+git annex 5.20140128-g32f1f68 on Android 4.1.2 (Samsung GTN8010)
+Build flags: Assistant Webapp S3 WebDAV Inotify XMPP DNS Feeds Quvi TDFA CryptoHash
+
+> Cooincidentially I noticed I'd dropped the patch that fixes that on
+> Android, and have been in the process of rebuilding the Android
+> autobuilder with it today. That build has finished now. [[done]]
+> --[[Joey]]
diff --git a/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__.mdwn b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__.mdwn
new file mode 100644
index 0000000000..ed0eb14696
--- /dev/null
+++ b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__.mdwn
@@ -0,0 +1,20 @@
+### Please describe the problem.
+
+On Andorid adding a respository on a remote server (ssh) to an exisiting repository does not work. After selecting "Make unencrypted repository" in the webapp the following error message is displayed:
+
+Internal Server Error
+/sdcard/git-annex.home/.ssh/config: setFileMode: permission denied (Operation not permitted)
+
+The file "/sdcard/git-annex.home/.ssh/config" is created and its content seems to be fine. I could not find anything related to file mode in logcat / daemon.log.
+
+### What steps will reproduce the problem?
+
+Add a repository on a remote server to an existing repository. After selecting "Make unencrypted repository" the error messages is displayed.
+
+### What version of git-annex are you using? On what operating system?
+
+git-annex version 5.20140116-g2d9ec29
+Android version 4.4 (running on a Nexus 5)
+
+> I have made this failure to set the file mode not be a fatal error.
+> [[fixed|done]] --[[Joey]]
diff --git a/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_1_414adc1bee73711e3133c7fe8811aae2._comment b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_1_414adc1bee73711e3133c7fe8811aae2._comment
new file mode 100644
index 0000000000..d1a5bf0c1d
--- /dev/null
+++ b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_1_414adc1bee73711e3133c7fe8811aae2._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkViAynw-AW5kjf3w_QDwCVwhPc3k7gY5E"
+ nickname="Thomas"
+ subject="I see the same fail"
+ date="2014-01-29T21:52:18Z"
+ content="""
+I se the same failure at both my android devices:
+Nexus 7, Android 4.4.2, git-annex 5.20140128 and
+Xperia phone, Android 4.1.2, git-annex 5.20140108
+"""]]
diff --git a/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_2_977a529f488ce0c167035675f76ebabf._comment b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_2_977a529f488ce0c167035675f76ebabf._comment
new file mode 100644
index 0000000000..55a368cc30
--- /dev/null
+++ b/doc/bugs/Android:_Adding_Repository_on_Remote_Server_fails_with___34__Internal_Server_Error__34__/comment_2_977a529f488ce0c167035675f76ebabf._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnx07B9weuZowXqh--1BDvGw8VM25aXsRw"
+ nickname="Matthew"
+ subject="comment 2"
+ date="2014-02-01T02:44:47Z"
+ content="""
+Same here, any workarounds?
+"""]]
diff --git a/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable.mdwn b/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable.mdwn
new file mode 100644
index 0000000000..45475f7400
--- /dev/null
+++ b/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable.mdwn
@@ -0,0 +1,13 @@
+### Please describe the problem.
+
+In order to handle the fact that the directory where pictures are saved is not configurable on my phone, I set up a second git annex repository with the Repository group "file source".
+
+### What version of git-annex are you using? On what operating system?
+
+5.20140108-gce9652
+
+### Please provide any additional information below.
+
+In the log, there are many "too many open files" errors like these :
+
+git:createProcess: runInteractiveProcess: pipe: resource exhausted (Too many open files)
diff --git a/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable/comment_1_1fe5f8c68a430b2436649cf4ba8f4987._comment b/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable/comment_1_1fe5f8c68a430b2436649cf4ba8f4987._comment
new file mode 100644
index 0000000000..eea1f2094d
--- /dev/null
+++ b/doc/bugs/Android_:_handling_DCIM__47__Camera_not_being_configurable/comment_1_1fe5f8c68a430b2436649cf4ba8f4987._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T18:59:29Z"
+ content="""
+I guess that this bug report is not about the DCIM/Camera location not being configurable, since that is up to Android, not git-annex.
+
+So, it seems to be a bug report about a file descriptor leak. It would be helpful, if you can reproduce the leak, to look at /proc/$pid/fd/ to see what files git-annex has open.
+"""]]
diff --git a/doc/bugs/Auto_update_not_updating_to_newest_version/comment_4_2705fbfd74652ab097ac48ec687517c7._comment b/doc/bugs/Auto_update_not_updating_to_newest_version/comment_4_2705fbfd74652ab097ac48ec687517c7._comment
new file mode 100644
index 0000000000..f0e3268467
--- /dev/null
+++ b/doc/bugs/Auto_update_not_updating_to_newest_version/comment_4_2705fbfd74652ab097ac48ec687517c7._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.43"
+ subject="comment 4"
+ date="2014-01-17T19:36:39Z"
+ content="""
+Well that upgrade did seem to succeed. The log almost looks like 2 git-annex assistant processes were running (which should not happen), it seems to have downloaded the upgrade twice somehow.
+"""]]
diff --git a/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__.mdwn b/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__.mdwn
new file mode 100644
index 0000000000..e7a8490213
--- /dev/null
+++ b/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__.mdwn
@@ -0,0 +1,74 @@
+### Please describe the problem.
+
+I get the following error when building:
+
+[[!format sh """
+$ cabal install git-annex --bindir=$HOME/bin -f"-assistant -webapp -webdav -pairing -xmpp -dns"
+
+...
+
+Configuring git-annex-5.20140127...
+Building git-annex-5.20140127...
+Preprocessing executable 'git-annex' for git-annex-5.20140127...
+[ 1 of 281] Compiling Utility.Dot ( Utility/Dot.hs, dist/build/git-annex/git-annex-tmp/Utility/Dot.o )
+[ 2 of 281] Compiling BuildFlags ( BuildFlags.hs, dist/build/git-annex/git-annex-tmp/BuildFlags.o )
+[ 3 of 281] Compiling Utility.Shell ( Utility/Shell.hs, dist/build/git-annex/git-annex-tmp/Utility/Shell.o )
+
+...
+
+[111 of 281] Compiling Backend.Hash ( Backend/Hash.hs, dist/build/git-annex/git-annex-tmp/Backend/Hash.o )
+[112 of 281] Compiling Annex.Queue ( Annex/Queue.hs, dist/build/git-annex/git-annex-tmp/Annex/Queue.o )
+[113 of 281] Compiling RunCommand ( RunCommand.hs, dist/build/git-annex/git-annex-tmp/RunCommand.o )
+
+RunCommand.hs:44:17:
+ Ambiguous occurrence `callCommand'
+ It could refer to either `RunCommand.callCommand',
+ defined at RunCommand.hs:62:1
+ or `Common.Annex.callCommand',
+ imported from `Common.Annex' at RunCommand.hs:12:1-19
+ (and originally defined in `System.Process')
+cabal: Error: some packages failed to install:
+git-annex-5.20140127 failed during the building phase. The exception was:
+ExitFailure 1
+"""]]
+
+### What steps will reproduce the problem?
+
+Try building the same version.
+
+### What version of git-annex are you using? On what operating system?
+
+Building git-annex-5.20140127...
+
+[[!format sh """
+$ cabal --version
+cabal-install version 0.14.0
+using version 1.14.0 of the Cabal library
+
+$ ghc --version
+The Glorious Glasgow Haskell Compilation System, version 7.4.1
+
+$ lsb_release -a
+No LSB modules are available.
+Distributor ID: Ubuntu
+Description: Ubuntu 12.04.3 LTS
+Release: 12.04
+Codename: precise
+
+$ uname -a
+Linux sahnlpt0116 3.2.0-58-generic #88-Ubuntu SMP Tue Dec 3 17:37:58 UTC 2013 x86_64 x86_64 x86_64 GNU/Linux
+"""]]
+
+### Please provide any additional information below.
+
+Sorry but I don't know what else could help you.
+
+[[!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 in git and will update cabal soon [[done]] --[[Joey]]
diff --git a/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__/comment_1_3127b3c448888fdf70096f24c7cbfd3c._comment b/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__/comment_1_3127b3c448888fdf70096f24c7cbfd3c._comment
new file mode 100644
index 0000000000..ad28f9cce2
--- /dev/null
+++ b/doc/bugs/Build_error:_Ambiguous_occurrence___96__callCommand__39__/comment_1_3127b3c448888fdf70096f24c7cbfd3c._comment
@@ -0,0 +1,50 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnzFs0ZJvkUvEVI_OAp0aAP1CTOw2UUXl4"
+ nickname="Christian"
+ subject="A patch to fix the problem"
+ date="2014-01-29T17:26:58Z"
+ content="""
+The following patch lets me compile everything, but I am not sure it is right:
+
+[[!format sh \"\"\"
+diff --git a/Command/PreCommit.hs b/Command/PreCommit.hs
+index 6644f6f..f3ad454 100644
+--- a/Command/PreCommit.hs
++++ b/Command/PreCommit.hs
+@@ -7,7 +7,7 @@
+
+ module Command.PreCommit where
+
+-import Common.Annex
++import Common.Annex hiding (callCommand)
+ import Command
+ import Config
+ import qualified Command.Add
+diff --git a/Command/Sync.hs b/Command/Sync.hs
+index 6ef111b..fde4a9a 100644
+--- a/Command/Sync.hs
++++ b/Command/Sync.hs
+@@ -8,7 +8,7 @@
+
+ module Command.Sync where
+
+-import Common.Annex
++import Common.Annex hiding (callCommand)
+ import Command
+ import qualified Annex
+ import qualified Annex.Branch
+diff --git a/RunCommand.hs b/RunCommand.hs
+index 937686d..d76b457 100644
+--- a/RunCommand.hs
++++ b/RunCommand.hs
+@@ -9,7 +9,7 @@
+
+ module RunCommand where
+
+-import Common.Annex
++import Common.Annex hiding (callCommand)
+ import qualified Annex
+ import Types.Command
+ import qualified Annex.Queue
+\"\"\"]]
+"""]]
diff --git a/doc/bugs/Building_on_OpenBSD/comment_2_4a37935080b86643ecda717fe17f8f87._comment b/doc/bugs/Building_on_OpenBSD/comment_2_4a37935080b86643ecda717fe17f8f87._comment
new file mode 100644
index 0000000000..3a7f85fdc8
--- /dev/null
+++ b/doc/bugs/Building_on_OpenBSD/comment_2_4a37935080b86643ecda717fe17f8f87._comment
@@ -0,0 +1,18 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 2"
+ date="2014-02-04T13:45:25Z"
+ content="""
+Sorry for the long delay, but I've tried what you said:
+``% cabal install git-annex --bindir=$HOME/bin --flags=\"-pairing -webdav\" -j2``
+
+and it STILL fails with:
+``cabal: user error (Error: some packages failed to install:
+git-annex-5.20140129 depends on network-info-0.2.0.3 which failed to install.
+network-info-0.2.0.3 failed during the building phase. The exception was:
+ExitFailure 1
+uuid-1.3.3 depends on network-info-0.2.0.3 which failed to install.
+)``
+
+"""]]
diff --git a/doc/bugs/Building_on_OpenBSD/comment_3_2df229eb965189e2f7ea6dcd66cf68ca._comment b/doc/bugs/Building_on_OpenBSD/comment_3_2df229eb965189e2f7ea6dcd66cf68ca._comment
new file mode 100644
index 0000000000..51153b671d
--- /dev/null
+++ b/doc/bugs/Building_on_OpenBSD/comment_3_2df229eb965189e2f7ea6dcd66cf68ca._comment
@@ -0,0 +1,24 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 3"
+ date="2014-02-04T14:04:33Z"
+ content="""
+And the UUID package requires network-info and git-annex seems to require the UUID package.
+Also notice that the configure can't find the SHA commands:
+ checking sha1... not available
+ checking sha256... not available
+ checking sha512... not available
+ checking sha224... not available
+ checking sha384... not available
+ Configuring git-annex-5.20140129...
+ setup: user error (At least the following dependencies are missing:
+ uuid -any)
+
+Even though:
+ % which sha1
+ /bin/sha1
+ % which sha256
+ /bin/sha256
+
+"""]]
diff --git a/doc/bugs/Building_on_OpenBSD/comment_4_d141c0bac92bdfbc8b95d532d032174c._comment b/doc/bugs/Building_on_OpenBSD/comment_4_d141c0bac92bdfbc8b95d532d032174c._comment
new file mode 100644
index 0000000000..090fed4542
--- /dev/null
+++ b/doc/bugs/Building_on_OpenBSD/comment_4_d141c0bac92bdfbc8b95d532d032174c._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 4"
+ date="2014-02-04T14:05:19Z"
+ content="""
+And why isn't the formatting working? :p
+"""]]
diff --git a/doc/bugs/Building_on_OpenBSD/comment_5_8aba96ef58eb6954f1d15029e0dda9ed._comment b/doc/bugs/Building_on_OpenBSD/comment_5_8aba96ef58eb6954f1d15029e0dda9ed._comment
new file mode 100644
index 0000000000..89bd81b608
--- /dev/null
+++ b/doc/bugs/Building_on_OpenBSD/comment_5_8aba96ef58eb6954f1d15029e0dda9ed._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 5"
+ date="2014-02-06T17:10:59Z"
+ content="""
+Ok, I missed that uuid needs network-info. Actually, git-annex does not use that part of uuid (it does not put IP info in its uuids). There is a past version of uuid that did not depend on network-info. Perhaps you should first install it: `cabal install uuid-1.2.14`
+
+As far as it not finding or liking the sha* commands, it may be that it is not able to parse the OpenBSD output, or doesn't see the output it expects when testing them. These commands are only used as a minor optimisation, if not available it will fall back to using a haskell implementation which is a few percent slower (or faster) than the linux coreutils version of sha*. I don't know how the speeds compare on OpenBSD, but it's probably not worth worrying about.
+"""]]
diff --git a/doc/bugs/Building_on_OpenBSD/comment_6_82e6744e246fe5caa72081d4e921b168._comment b/doc/bugs/Building_on_OpenBSD/comment_6_82e6744e246fe5caa72081d4e921b168._comment
new file mode 100644
index 0000000000..ac01f1a5ce
--- /dev/null
+++ b/doc/bugs/Building_on_OpenBSD/comment_6_82e6744e246fe5caa72081d4e921b168._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 6"
+ date="2014-02-07T11:16:17Z"
+ content="""
+Actually what I did was to patch network-info to build under openbsd.
+I've literally never touched Haskell but fortunately it was C code that needed fixing and so far it seems to be working.
+
+I'm intending to contact the maintainer of that package and let him know
+"""]]
diff --git a/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9.mdwn b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9.mdwn
new file mode 100644
index 0000000000..61bed09271
--- /dev/null
+++ b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9.mdwn
@@ -0,0 +1,24 @@
+### Please describe the problem.
+
+I can't seem to add the rsync.net remote on an OS X 10.9 machine running git-annex assistant version 5.20140128-g0ac94c3. The process complains about a missing `/usr/libexec/ssh-askpass` in the logs, and after a few retries rsync.net locks me out. This program doesn't exist on my system.
+
+### What steps will reproduce the problem?
+
+1. Click "Add another repository"
+2. Pick rsync.net
+3. Enter the credentials I got in the email from rsync.net
+4. Click "Use this rsync repository"
+
+The resulting logs will state that `/usr/libexec/ssh-askpass` can't be found.
+
+### What version of git-annex are you using? On what operating system?
+
+git-annex assistant version 5.20140128-g0ac94c3 on OS X 10.9.1.
+
+### Please provide any additional information below.
+
+I think I have found a workaround in creating that program as a shell script which echoes my password to stdout, but can't test right now because rsync.net have wisely ratelimited my password login attempts. (-:
+
+I'll update this page if I can confirm the workaround works.
+
+(I fully intend to roll that password as soon as I'm in, so no worries about a stale password falling into evildoers' hands.)
diff --git a/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_1_91a961cfa5dd4d6f0e4abfbbcfb81e92._comment b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_1_91a961cfa5dd4d6f0e4abfbbcfb81e92._comment
new file mode 100644
index 0000000000..7ab46c3bb7
--- /dev/null
+++ b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_1_91a961cfa5dd4d6f0e4abfbbcfb81e92._comment
@@ -0,0 +1,35 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawl7Tgnd2BBdIXVlNKjG4dkTj3paf7FHeHQ"
+ nickname="Andreas"
+ subject="ssh-askpass workaround does work"
+ date="2014-02-01T06:28:41Z"
+ content="""
+I've just gotten my rsync.net account unwedged, and can confirm that the ssh-askpass hack does work. After what seemed like git-annex successfully uploading an ssh keypair to the rsync.net remote, I removed the ssh-askpass stub script and rolled my rsync.net password. Now, I'm getting these log entries:
+
+```
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+Received disconnect from 69.43.165.5: 2: Too many authentication failures for 40407
+rsync: connection unexpectedly closed (0 bytes received so far) [sender]
+rsync error: unexplained error (code 255) at /SourceCache/rsync/rsync-42/rsync/io.c(452) [sender=2.6.9]
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+Permission denied, please try again.
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+Received disconnect from 69.43.165.5: 2: Too many authentication failures for 40407
+rsync: connection unexpectedly closed (0 bytes received so far) [sender]
+rsync error: unexplained error (code 255) at /SourceCache/rsync/rsync-42/rsync/io.c(452) [sender=2.6.9]
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+Permission denied, please try again.
+ssh_askpass: exec(/usr/libexec/ssh-askpass): No such file or directory
+Received disconnect from 69.43.165.5: 2: Too many authentication failures for 40407
+rsync: connection unexpectedly closed (0 bytes received so far) [sender]
+rsync error: unexplained error (code 255) at /SourceCache/rsync/rsync-42/rsync/io.c(452) [sender=2.6.9]
+```
+
+Looks like git-annex asks for the password for some reason? I'm not sure what's going on here, please advise.
+"""]]
diff --git a/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_2_0b5266e31fe7014bd11ea164f8e4744e._comment b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_2_0b5266e31fe7014bd11ea164f8e4744e._comment
new file mode 100644
index 0000000000..7792d2396d
--- /dev/null
+++ b/doc/bugs/Can__39__t_set_up_rsync.net_repo_on_OS_X_10.9/comment_2_0b5266e31fe7014bd11ea164f8e4744e._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 2"
+ date="2014-02-07T19:21:21Z"
+ content="""
+git-annex does not run ssh-askpass. But your ssh program may try to do so, if git-annex is started without a controlling terminal. So a workaround is to start git-annex from a terminal window and then password prompts will happen there.
+
+[[design/assistant/sshpassword]] is on the roadmap to fix this so git-annex overrides ssh's password prompting, which seems to be broken on a number of systems.
+
+I don't know why it would continue prompting for a ssh password if git-annex successfully set up a ssh keypair for rsync.net. My guess is that it failed to do so.
+"""]]
diff --git a/doc/bugs/Can__39__t_start_it_on_Debian_Wheezy.mdwn b/doc/bugs/Can__39__t_start_it_on_Debian_Wheezy.mdwn
index 2084394964..a7e7613d53 100644
--- a/doc/bugs/Can__39__t_start_it_on_Debian_Wheezy.mdwn
+++ b/doc/bugs/Can__39__t_start_it_on_Debian_Wheezy.mdwn
@@ -21,3 +21,6 @@ I don't know where is that log
# End of transcript or log.
"""]]
+
+> Wheezy was released before git-annex had the webapp. If you want it,
+> install the backport. [[done]] --[[Joey]]
diff --git a/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails.mdwn b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails.mdwn
new file mode 100644
index 0000000000..f780ace7ca
--- /dev/null
+++ b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails.mdwn
@@ -0,0 +1,8 @@
+### Please describe the problem.
+The webapp does not offer me the option to delete a remote repository that it did not succeed to synchronize with. Status of the repository is sync enabled (metadata only) but in settings I may only edit the repo, but cannot delete it.
+
+### What steps will reproduce the problem?
+Set up git-annex on a new computer. Forget to enable ssh on the machine. Perform a local pairing (success). The sync fails for obvious reasons.
+
+### What version of git-annex are you using? On what operating system?
+System is ubuntu but I assume this is a general issue. Version of git-annex is 5.20140117
diff --git a/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_1_3c8e8fae688a9db8e18e869a187fb4eb._comment b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_1_3c8e8fae688a9db8e18e869a187fb4eb._comment
new file mode 100644
index 0000000000..c89d1cb0c7
--- /dev/null
+++ b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_1_3c8e8fae688a9db8e18e869a187fb4eb._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.46"
+ subject="comment 1"
+ date="2014-01-26T17:57:25Z"
+ content="""
+If you go to Edit, it will let you upgrade the repository, which should fix your problem.
+"""]]
diff --git a/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_2_e189617c4ac23df50f02af8c517fa399._comment b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_2_e189617c4ac23df50f02af8c517fa399._comment
new file mode 100644
index 0000000000..0d2f2e99b1
--- /dev/null
+++ b/doc/bugs/Cannot_delete_remote_when_ssh_sync_fails/comment_2_e189617c4ac23df50f02af8c517fa399._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmXtqLEfN6cGcF9gW_09QUDoRpsexSdRcM"
+ nickname="Thomas"
+ subject="comment 2"
+ date="2014-01-26T18:12:08Z"
+ content="""
+Unfortunately, upgrading did not fix it. I suppose, a restart of the remote server (ssh was just installed) would have been necessary. Instead, I just deleted the repository on the remote.
+
+Now my local repository was caught in a situation, where I couldn't upgrade the broken remote and I couldn't delete it either.
+
+By recreating the repository on the remote, I finally was able to get rid of the broken link, but I think the proper solution would be to have the ability to remove unsynced repositories.
+
+Thanks for the quick response!
+"""]]
diff --git a/doc/bugs/ControlPath_too_long_for_Unix_domain_socket/comment_2_9c0c65389a3b4e7e81b8de96d430a3f1._comment b/doc/bugs/ControlPath_too_long_for_Unix_domain_socket/comment_2_9c0c65389a3b4e7e81b8de96d430a3f1._comment
new file mode 100644
index 0000000000..9f62af9560
--- /dev/null
+++ b/doc/bugs/ControlPath_too_long_for_Unix_domain_socket/comment_2_9c0c65389a3b4e7e81b8de96d430a3f1._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmI_rfI0tsu93LcMlAvh5WTXtKFIMkHrJQ"
+ nickname="Pawan"
+ subject="Long Path Tool"
+ date="2014-01-24T10:43:09Z"
+ content="""
+Well, you can also use Long Path Tool for such problems, it really works good I will say.
+"""]]
diff --git a/doc/bugs/Creating_a_WebDAV_repo_under_OpenBSD.mdwn b/doc/bugs/Creating_a_WebDAV_repo_under_OpenBSD.mdwn
new file mode 100644
index 0000000000..f82f914fff
--- /dev/null
+++ b/doc/bugs/Creating_a_WebDAV_repo_under_OpenBSD.mdwn
@@ -0,0 +1,53 @@
+### Please describe the problem.
+When creating a https webdav repository under openbsd it complains that /etc/ssl/certs doesn't exist. This is true considering all certs are stored in /etc/ssl/cert.pem.
+After /etc/ssl/certs is created it complains about that the certificate has an unknown CA, for obvious reasons.
+
+A workaround is to symlink /etc/ssl/cert.pem in /etc/ssl/certs
+
+### What steps will reproduce the problem?
+See below
+
+### What version of git-annex are you using? On what operating system?
+5.20140129 under OpenBSD 5.4
+
+### 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
+WEBDAV_USERNAME= WEBDAV_PASSWORD= git annex initremote box.com type=webdav url=https://dav.box.com/dav/Documents chunksize=100mb encryption=hybrid keyid= mac=HMACSHA512
+initremote box.com (encryption setup) (hybrid cipher with gpg key ) (testing WebDAV server...)
+
+git-annex: WebDAV failed to write file: /etc/ssl/certs/: getDirectoryContents: does not exist (No such file or directory): user error
+failed
+git-annex: initremote: 1 failed
+
+
+# End of transcript or log.
+"""]]
+
+> This needs to be fixed in the haskell certificate library.
+> I have filed a bug there:
+>
+>
+> Patch would probably be pretty simple. Based on description, something like
+> this:
+
+[[!format patch """
+diff --git a/System/Certificate/X509/Unix.hs b/System/Certificate/X509/Unix.hs
+index 8463465..74316e9 100644
+--- a/System/Certificate/X509/Unix.hs
++++ b/System/Certificate/X509/Unix.hs
+@@ -50,7 +50,7 @@ listDirectoryCerts path = (map (path >) . filter isCert <$> getDirectoryConten
+ isCert x = (not $ isPrefixOf "." x) && (not $ isHashedFile x)
+
+ getSystemCertificateStore :: IO CertificateStore
+-getSystemCertificateStore = makeCertificateStore . concat <$> (getSystemPath >>= listDirectoryCerts >>= mapM readCertificates)
++getSystemCertificateStore = makeCertificateStore <$> readCertificates "/etc/ssl/cert.pem"
+
+ getSystemPath :: IO FilePath
+ getSystemPath = E.catch (getEnv envPathOverride) inDefault
+"""]]
+
+>
+> [[closing|done]] as no changes to git-annex can fix this. --[[Joey]]
diff --git a/doc/bugs/Creating_a_box.com_repository_fails.mdwn b/doc/bugs/Creating_a_box.com_repository_fails.mdwn
new file mode 100644
index 0000000000..75d59c9bc3
--- /dev/null
+++ b/doc/bugs/Creating_a_box.com_repository_fails.mdwn
@@ -0,0 +1,37 @@
+### Please describe the problem.
+
+Adding a repository on box.com, using the assistant, fails with an error message (as seen in the log below).
+
+### What steps will reproduce the problem?
+
+Start up the assistant. Create a new empty repository. Enable consistency checking as suggested. Click add another repository, select box.com, fill in your credentials, keep shared ticked and encrypt all selected, click add repository. Error message appears.
+
+
+### What version of git-annex are you using? On what operating system?
+
+5.20140117.1 from ppa of François Marier
+
+ubuntu 13.10 (saucy), i686
+
+### 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-01-26 20:40:10 CET] main: starting assistant version 5.20140117.1
+[2014-01-26 20:40:10 CET] Cronner: You should enable consistency checking to protect your data.
+(Recording state in git...)
+(scanning...) [2014-01-26 20:40:10 CET] Watcher: Performing startup scan
+(started...) [2014-01-26 20:41:10 CET] Cronner: Consistency check in progress
+
+(Recording state in git...)
+(encryption setup) (shared cipher) (testing WebDAV server...)
+26/Jan/2014:20:41:24 +0100 [Error#yesod-core] InternalIOException : hPutBuf: illegal operation (handle is closed) @(yesod-core-1.2.3:Yesod.Core.Class.Yesod ./Yesod/Core/Class/Yesod.hs:471:5)
+
+# End of transcript or log.
+"""]]
+
+> Seems that [DAV-0.6 is badly broken](http://bugs.debian.org/737902).
+> I have adjusted the cabal file to refuse to build with that broken
+> version.
diff --git a/doc/bugs/Creating_a_box.com_repository_fails/comment_1_c0b4855b65cb7052daf6538c2ad73e99._comment b/doc/bugs/Creating_a_box.com_repository_fails/comment_1_c0b4855b65cb7052daf6538c2ad73e99._comment
new file mode 100644
index 0000000000..0aee0102a0
--- /dev/null
+++ b/doc/bugs/Creating_a_box.com_repository_fails/comment_1_c0b4855b65cb7052daf6538c2ad73e99._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk9nck8WX8-ADF3Fdh5vFo4Qrw1I_bJcR8"
+ nickname="Jon Ander"
+ subject="comment 1"
+ date="2014-02-02T16:48:37Z"
+ content="""
+I'm also experiencing a similar issue, I get this error when I try to upload a file to Box.com:
+
+ git annex copy my_file --to box.com
+ copy my_file (gpg) (checking box.com...) git-annex: InternalIOException : hPutBuf: illegal operation (handle is closed)
+"""]]
diff --git a/doc/bugs/Creating_a_box.com_repository_fails/comment_2_b05a1e7b37989c698353cc6b3fd02d7c._comment b/doc/bugs/Creating_a_box.com_repository_fails/comment_2_b05a1e7b37989c698353cc6b3fd02d7c._comment
new file mode 100644
index 0000000000..c278ced968
--- /dev/null
+++ b/doc/bugs/Creating_a_box.com_repository_fails/comment_2_b05a1e7b37989c698353cc6b3fd02d7c._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk9nck8WX8-ADF3Fdh5vFo4Qrw1I_bJcR8"
+ nickname="Jon Ander"
+ subject="comment 2"
+ date="2014-02-03T11:31:48Z"
+ content="""
+I have more information on the issue. I have another computer synced with my main one, but with Box.com disabled. When trying to enable it now I get the following error:
+
+ StatusCodeException (Status {statusCode = 404, statusMessage = \"Not Found\"}) [(\"Server\",\"nginx\"),(\"Date\",\"Mon, 03 Feb 2014 11:29:17 GMT\"),(\"Content-Type\",\"text/html; charset=UTF-8\"),(\"Content-Length\",\"0\"),(\"Connection\",\"keep-alive\"),(\"X-Robots-Tag\",\"noindex, nofollow\"),(\"Set-Cookie\",\"box_visitor_id=52ef7d8cf20e56.10269052; expires=Tue, 03-Feb-2015 11:29:16 GMT; path=/; domain=.box.com\"),(\"Set-Cookie\",\"bv=OPS-35591; expires=Mon, 10-Feb-2014 11:29:16 GMT; path=/; domain=.box.com\"),(\"Set-Cookie\",\"cn=11; expires=Mon, 10-Feb-2014 11:29:16 GMT; path=/; domain=.box.com\"),(\"Set-Cookie\",\"presentation=desktop; path=/; domain=.box.com\"),(\"Set-Cookie\",\"box_locale=es_ES; expires=Thu, 03-Apr-2014 10:29:17 GMT; path=/; domain=.box.com\"),(\"X-Response-Body-Start\",\"\")] (CJ {expose = [Cookie {cookie_name = \"box_locale\", cookie_value = \"es_ES\", cookie_expiry_time = 2014-04-03 10:29:17 UTC, cookie_domain = \"box.com\", cookie_path = \"/\", cookie_creation_time = 2014-02-03 11:29:17.202283 UTC, cookie_last_access_time = 2014-02-03 11:29:17.202283 UTC, cookie_persistent = True, cookie_host_only = False, cookie_secure_only = False, cookie_http_only = False},Cookie {cookie_name = \"presentation\", cookie_value = \"desktop\", cookie_expiry_time = 3013-06-06 00:00:00 UTC, cookie_domain = \"box.com\", cookie_path = \"/\", cookie_creation_time = 2014-02-03 11:29:17.202283 UTC, cookie_last_access_time = 2014-02-03 11:29:17.202283 UTC, cookie_persistent = False, cookie_host_only = False, cookie_secure_only = False, cookie_http_only = False},Cookie {cookie_name = \"cn\", cookie_value = \"11\", cookie_expiry_time = 2014-02-10 11:29:16 UTC, cookie_domain = \"box.com\", cookie_path = \"/\", cookie_creation_time = 2014-02-03 11:29:17.202283 UTC, cookie_last_access_time = 2014-02-03 11:29:17.202283 UTC, cookie_persistent = True, cookie_host_only = False, cookie_secure_only = False, cookie_http_only = False},Cookie {cookie_name = \"bv\", cookie_value = \"OPS-35591\", cookie_expiry_time = 2014-02-10 11:29:16 UTC, cookie_domain = \"box.com\", cookie_path = \"/\", cookie_creation_time = 2014-02-03 11:29:17.202283 UTC, cookie_last_access_time = 2014-02-03 11:29:17.202283 UTC, cookie_persistent = True, cookie_host_only = False, cookie_secure_only = False, cookie_http_only = False},Cookie {cookie_name = \"box_visitor_id\", cookie_value = \"52ef7d8cf20e56.10269052\", cookie_expiry_time = 2015-02-03 11:29:16 UTC, cookie_domain = \"box.com\", cookie_path = \"/\", cookie_creation_time = 2014-02-03 11:29:17.202283 UTC, cookie_last_access_time = 2014-02-03 11:29:17.202283 UTC, cookie_persistent = True, cookie_host_only = False, cookie_secure_only = False, cookie_http_only = False}]})
+
+This computer is running 5.20140127 in Debian testing and my main computer is running the same git-annex but in Debian sid. Both are using the webapp.
+"""]]
diff --git a/doc/bugs/File_that_are_in_two_place_can_be_sequentially_copy_then_dropped.mdwn b/doc/bugs/File_that_are_in_two_place_can_be_sequentially_copy_then_dropped.mdwn
new file mode 100644
index 0000000000..b794e6a3f5
--- /dev/null
+++ b/doc/bugs/File_that_are_in_two_place_can_be_sequentially_copy_then_dropped.mdwn
@@ -0,0 +1,17 @@
+### Please describe the problem.
+I've a repository with a prefered content of "exclude=cours/vieux/* and ( include=cours/* or include=Programmes/* or include=Stage/* )", but there is a repository that has a (identical) copy both in cours/vieux and in Stage/ so git annex sync --content will
+- get the content in Stage/
+- then drop it because it is in cours/vieux/
+
+And again, and again...
+
+### What version of git-annex are you using? On what operating system?
+git-annex 5.20140127 in debian/sid
+
+> This is actually a duplicate of
+> [[Handling_of_files_inside_and_outside_archive_directory_at_the_same_time]].
+> As noted in that bug report, this should already be fixed in direct mode,
+> but still happens in indirect mode when the full scan is done (at
+> startup, and occasionally at other times).
+>
+> [[dup|done]] --[[Joey]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__.mdwn b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__.mdwn
new file mode 100644
index 0000000000..bf7f4f3918
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__.mdwn
@@ -0,0 +1,44 @@
+### Please describe the problem.
+When I try to create a megaannex remote with pubkey encryption GPG complains about not finding the public key.
+
+### What steps will reproduce the problem?
+See below
+
+
+### What version of git-annex are you using? On what operating system?
+5.20140129 under OSX.
+
+
+### Please provide any additional information below.
+
+[[!format sh """
+% USERNAME="" PASSWORD='' git annex -vd initremote mega type=external externaltype=mega encryption=pubkey keyid=X folder=Documents mac=HMACSHA512
+[2014-02-06 11:39:14 CET] read: git ["--git-dir=/Users/dxtr/Documents/.git","--work-tree=/Users/dxtr/Documents","show-ref","git-annex"]
+[2014-02-06 11:39:14 CET] read: git ["--git-dir=/Users/dxtr/Documents/.git","--work-tree=/Users/dxtr/Documents","show-ref","--hash","refs/heads/git-annex"]
+[2014-02-06 11:39:14 CET] read: git ["--git-dir=/Users/dxtr/Documents/.git","--work-tree=/Users/dxtr/Documents","log","refs/heads/git-annex..62dc22cced06268fa5adcf54992eb1169c6ca1aa","--oneline","-n1"]
+[2014-02-06 11:39:14 CET] chat: git ["--git-dir=/Users/dxtr/Documents/.git","--work-tree=/Users/dxtr/Documents","cat-file","--batch"]
+initremote mega (encryption setup) [2014-02-06 11:39:14 CET] read: gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--with-colons","--list-public-keys","46726B9A"]
+[2014-02-06 11:39:14 CET] read: gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--gen-random","--armor","2","256"]
+[2014-02-06 11:39:14 CET] chat: gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--recipient","X","--encrypt","--no-encrypt-to","--no-default-recipient","--force-mdc","--no-textmode"]
+(pubkey crypto with gpg key X) [2014-02-06 11:39:15 CET] chat: git-annex-remote-mega []
+[2014-02-06 11:39:15 CET] git-annex-remote-mega --> VERSION 1
+[2014-02-06 11:39:15 CET] git-annex-remote-mega <-- INITREMOTE
+[2014-02-06 11:39:15 CET] git-annex-remote-mega --> GETCONFIG encryption
+[2014-02-06 11:39:15 CET] git-annex-remote-mega <-- VALUE pubkey
+[2014-02-06 11:39:15 CET] git-annex-remote-mega --> GETCONFIG folder
+[2014-02-06 11:39:15 CET] git-annex-remote-mega <-- VALUE Documents
+[2014-02-06 11:39:15 CET] git-annex-remote-mega --> SETCREDS mycreds
+(gpg) [2014-02-06 11:39:15 CET] chat: gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--decrypt"]
+[2014-02-06 11:39:15 CET] chat: gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--batch","--encrypt","--no-encrypt-to","--no-default-recipient","--force-mdc","--no-textmode"]
+gpg: no valid addressees
+gpg: [stdin]: encryption failed: no such user id
+
+git-annex: user error (gpg ["--batch","--no-tty","--use-agent","--quiet","--trust-model","always","--batch","--encrypt","--no-encrypt-to","--no-default-recipient","--force-mdc","--no-textmode"] exited 2)
+failed
+git-annex: initremote: 1 failed
+
+
+# End of transcript or log.
+"""]]
+
+> [[fixed|done]] --[[Joey]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_1_ac3631024abf372e6f578a472b86d792._comment b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_1_ac3631024abf372e6f578a472b86d792._comment
new file mode 100644
index 0000000000..1d71eebf4b
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_1_ac3631024abf372e6f578a472b86d792._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 1"
+ date="2014-02-06T11:00:49Z"
+ content="""
+I just confirmed it works with encryption=hybrid
+"""]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_980c149d7f9040f5e71e662d95a5fbf1._comment b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_980c149d7f9040f5e71e662d95a5fbf1._comment
new file mode 100644
index 0000000000..2c5bdc120d
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_980c149d7f9040f5e71e662d95a5fbf1._comment
@@ -0,0 +1,9 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 3"
+ date="2014-02-06T21:53:23Z"
+ content="""
+I can reproduce this, but only when using the hook special remote, so it's some problem with it.
+directory special remote works ok.
+"""]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_c279f5cc3f96910287e72bf59120d02b._comment b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_c279f5cc3f96910287e72bf59120d02b._comment
new file mode 100644
index 0000000000..b5e9c3c21b
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_3_c279f5cc3f96910287e72bf59120d02b._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 3"
+ date="2014-02-06T22:07:55Z"
+ content="""
+Actually, it seems to affect also S3 and other remotes that call setCreds.
+"""]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_4_ec6abe7074f767f866e9618d65a4a900._comment b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_4_ec6abe7074f767f866e9618d65a4a900._comment
new file mode 100644
index 0000000000..b61b0626a2
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_4_ec6abe7074f767f866e9618d65a4a900._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 4"
+ date="2014-02-07T11:11:23Z"
+ content="""
+Could it be some general issue with setCreds?
+
+The reason I'm wondering is that megaannex isn't really working. It doesn't seem to (properly) get the credentials so it's acting funny and getting an Invalid Argument exception where, according to what I understand from the documentation, it shouldn't be possible to get an Invalid Argument exception.
+
+Ofcourse I have contacted the maintainer of megaannex (TobiasTheViking on github) too. I've also started looking in to it myself.
+"""]]
diff --git a/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_5_44f80d89360a5620f919f8bc7c1c2879._comment b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_5_44f80d89360a5620f919f8bc7c1c2879._comment
new file mode 100644
index 0000000000..b5495e4540
--- /dev/null
+++ b/doc/bugs/GPG_issues_with_pubkey___40__Again__63____41__/comment_5_44f80d89360a5620f919f8bc7c1c2879._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 5"
+ date="2014-02-07T11:12:24Z"
+ content="""
+Oh, sorry. I didn't see that you had already fixed it.
+"""]]
diff --git a/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case.mdwn b/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case.mdwn
new file mode 100644
index 0000000000..823d12679d
--- /dev/null
+++ b/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case.mdwn
@@ -0,0 +1,70 @@
+### Please describe the problem.
+When creating a simple "parent" git repo, creating another "child" repo with an annexed file, then adding the child repo as a submodule of the parent, the symlink path of the large file contained by the submodule is incorrect.
+
+
+### What steps will reproduce the problem?
+Here are the exact steps for this simple use case (I have removed unrelated output for brevity, and setting up the repos is error-free):
+
+ # Create "parent" repo
+ $ mkdir parent
+ $ cd parent/
+ $ git init
+ $ touch parent_start
+ $ git add parent_start
+ $ git commit -a -m 'New parent repo'
+ $ cd ../
+
+ # Create "child" repo
+ $ mkdir child
+ $ cd child/
+ $ git init
+ $ touch child_start
+ $ git add child_start
+ $ git commit -a -m 'New child repo'
+ $ git annex init
+ $ cp ~/Desktop/some_big_file child_big_file
+ $ git annex add child_big_file
+ $ git commit -a -m 'Added big file'
+ $ cd ../
+
+ # Add "child" repo as a submodule of "parent" repo
+ $ cd parent/
+ $ git submodule add ../child ./submodule
+ $ git commit -m 'Added submodule'
+
+ # Try to get annexed file
+ $ cd submodule/
+ $ git annex init
+ $ git annex get
+ $ ls ./
+ -rw-r--r-- .git
+ lrwxr-xr-x child_big_file -> .git/annex/objects/F5/f2/SHA256E-s1117253--ce17632dfd9c61a0a8c1384d25fb3a8a197f8056f224e15fbcad89904a82c5fd/SHA256E-s1117253--ce17632dfd9c61a0a8c1384d25fb3a8a197f8056f224e15fbcad89904a82c5fd
+ -rw-r--r-- child_start
+
+ # As you can see above, the child_big_file symlink path is incorrect (the ".git/annex/..." location is not a directory, and should instead be "../.git/modules/submodule/annex/...")
+
+ # Show the actual location of the annexed file
+ $ cd ../
+ $ ls .git/modules/submodule/annex/objects/F5/f2/SHA256E-s1117253--ce17632dfd9c61a0a8c1384d25fb3a8a197f8056f224e15fbcad89904a82c5fd
+ -r--r--r-- SHA256E-s1117253--ce17632dfd9c61a0a8c1384d25fb3a8a197f8056f224e15fbcad89904a82c5fd
+
+
+### What version of git-annex are you using? On what operating system?
+Mac OS X Mountain Lion. git-annex files are from within the downloadable git-annex assistant.
+
+ $ sw_vers -productVersion
+ 10.8.5
+ $ git --version
+ git version 1.7.12.4 (Apple Git-37)
+ $ git-annex version
+ git-annex version: 4.20131105-g136b030
+ build flags: Assistant Webapp Pairing Testsuite S3 WebDAV FsEvents XMPP DNS Feeds Quvi TDFA
+ key/value backends: SHA256E SHA1E SHA512E SHA224E SHA384E SHA256 SHA1 SHA512 SHA224 SHA384 WORM URL
+ remote types: git gcrypt S3 bup directory rsync web webdav glacier hook
+ local repository version: 3
+ default repository version: 3
+ supported repository versions: 3 4
+ upgrade supported from repository versions: 0 1 2
+
+
+Thanks for your help :)
diff --git a/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case/comment_1_73b4dc5f90c8ba5634caee35cd31af1a._comment b/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case/comment_1_73b4dc5f90c8ba5634caee35cd31af1a._comment
new file mode 100644
index 0000000000..d8539041d3
--- /dev/null
+++ b/doc/bugs/Incorrect_symlink_path_in_simple_submodule_use_case/comment_1_73b4dc5f90c8ba5634caee35cd31af1a._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 1"
+ date="2014-02-06T16:58:54Z"
+ content="""
+Since the symlinks are committed to git, they can only point at one location, which is whereever the .git/annex directory was in the repository where they were created in the first place. You can run `git annex fix` in the submodule and it should correct the links. But then they'll point to the wrong location in the non-submodule clone of the repository.
+
+So, it seems you need to pick whether a given repository will be a submodule or not (and where it will be mounted in the parent repository if so), and stick with that choice. You can't have it both ways.
+
+I cannot imagine any change to git-annex that could change this limitation. Except perhaps using direct mode everywhere, in which case where the symlinks point internally doesn't really matter..
+
+( might be a usable alternative to submodules for you, that does not have this problem.)
+"""]]
diff --git a/doc/bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport.mdwn b/doc/bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport.mdwn
new file mode 100644
index 0000000000..0ea1a96a92
--- /dev/null
+++ b/doc/bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport.mdwn
@@ -0,0 +1,12 @@
+### Please describe the problem.
+I've installed Git-annex via the backport, everything looks fine. But when I go to Configuration>Configure jabber account I've got this message :
+
+[[!format sh """
+ Jabber not supported
+ This build of git-annex does not support Jabber. Sorry !
+"""]]
+
+### What version of git-annex are you using? On what operating system?
+5.20140117~bpo70+1 and Debian Wheezy with lxde
+
+> Build dependency problem. Fixed and backport updated. [[done]] --[[Joey]]
diff --git a/doc/bugs/Mac_OS_git_version_too_old_to_honour_.gitignore.mdwn b/doc/bugs/Mac_OS_git_version_too_old_to_honour_.gitignore.mdwn
new file mode 100644
index 0000000000..0cf61bb0fc
--- /dev/null
+++ b/doc/bugs/Mac_OS_git_version_too_old_to_honour_.gitignore.mdwn
@@ -0,0 +1,38 @@
+### Please describe the problem.
+
+Git annex assistant ignores .gitignore file due to packaged git version being too old.
+
+I have a locally installed version that is greater than the 1.8.4 needed to respect .gitignore but git annex doesn't use it.
+
+### What steps will reproduce the problem?
+
+- Create local repository using webapp
+- Add .gitignore file to local repository
+- Add files that match .gitignore patterns and watch git annex add them
+
+### What version of git-annex are you using? On what operating system?
+
+Git Annex assistant version 5.20140128-g0ac94c3 on Mac OS 10.9.1
+
+### Please provide any additional information below.
+
+Log message is "The installed version of git is too old for .gitignores to be honored by git-annex."
+
+[[!format sh """
+# /Applications/git-annex.app/Contents/MacOS/git-annex version
+git-annex version: 5.20140128-g0ac94c3
+build flags: Assistant Webapp Pairing S3 WebDAV FsEvents XMPP 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
+
+# /Applications/git-annex.app/Contents/MacOS/git --version
+git version 1.8.3.4 (Apple Git-47)
+
+# which git
+/usr/local/bin/git
+
+# /usr/local/bin/git --version
+git version 1.8.5.3
+"""]]
+
+> [[fixed|done]]; it has been updated to 1.8.5.3 on the autobuilder. --[[Joey]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD.mdwn b/doc/bugs/More_build_oddities_under_OpenBSD.mdwn
new file mode 100644
index 0000000000..3eda52fa32
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD.mdwn
@@ -0,0 +1,37 @@
+### Please describe the problem.
+I have managed to get most things working under OpenBSD 5.4 now.
+
+One of the last hurdles is that if I enable XMPP the build fails on "Loading package gnuidn-0.2.1..."
+See the error below.
+
+I suspect this is an error in git-annex because network-protocol-xmpp AND gnuidn compiles (and links) fine.
+
+I will gladly do anything I can to get this working, but I'm at a loss what to do right now. It's the last major piece of the puzzle before I get it properly functioning under OpenBSD.
+
+### What steps will reproduce the problem?
+Building with XMPP support under OpenBSD 5.4
+
+### What version of git-annex are you using? On what operating system?
+5.20140129 under OpenBSD 5.4
+
+### 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
+Loading package gnuidn-0.2.1 ...
+
+GHCi runtime linker: fatal error: I found a duplicate definition for symbol
+ c_isascii
+whilst processing object file
+ /usr/local/lib/libidn.a
+This could be caused by:
+ * Loading two different object files which export the same symbol
+ * Specifying the same object file twice on the GHCi command line
+ * An incorrect `package.conf' entry, causing some object to be
+ loaded twice.
+GHCi cannot safely continue in this situation. Exiting now. Sorry.
+
+
+# End of transcript or log.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_10_09297f99f3c1c081738ca4ab32808fde._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_10_09297f99f3c1c081738ca4ab32808fde._comment
new file mode 100644
index 0000000000..e3871ea612
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_10_09297f99f3c1c081738ca4ab32808fde._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 10"
+ date="2014-02-08T18:31:23Z"
+ content="""
+But you said that setSocketOption failed when you were using XMPP, not when starting the webapp, so I think it's more likely to be one of the setSocketOption calls in the network library, or possibly somewhere else.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_11_1407efc78b92a3c6156154f54e4a14e2._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_11_1407efc78b92a3c6156154f54e4a14e2._comment
new file mode 100644
index 0000000000..78c430533d
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_11_1407efc78b92a3c6156154f54e4a14e2._comment
@@ -0,0 +1,97 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 11"
+ date="2014-02-08T19:18:17Z"
+ content="""
+I honestly have no idea why that move works because
+
+ % ls -lh /usr/lib|grep -E '(gsasl|xml2|gnutls|idn)'
+
+returns nothing. But couldn't those symbols already be in the other libraries considering, from what I've read at least, haskell stuff are statically compiled by default?
+
+Anyway, you are completely right that this happened when I try to use XMPP. The reason I was looking in the wrong place to begin with was because the webapp spit out the error messsage. I have redirected my attention to the network library and the xmpp library.
+
+But I might have found something interesting in the network library. Keep in mind that I just learned a little today, so do correct me if I'm wrong.
+
+Looking at http://hackage.haskell.org/package/network-2.2.1.8/docs/src/Network-Socket.html I found:
+
+ setSocketOption :: Socket
+ -> SocketOption -- Option Name
+ -> Int -- Option Value
+ -> IO ()
+ setSocketOption (MkSocket s _ _ _ _) so v = do
+ with (fromIntegral v) $ \ptr_v -> do
+ throwErrnoIfMinus1_ \"setSocketOption\" $
+ c_setsockopt s (socketOptLevel so) (packSocketOption so) ptr_v
+ (fromIntegral (sizeOf v))
+ return ()
+
+Everything here looks good. So I decided to take a look at SocketOption, socketOptLevel and packSocketOption.
+
+ data SocketOption
+ = DummySocketOption__
+ | Debug {- SO_DEBUG -}
+ | ReuseAddr {- SO_REUSEADDR -}
+ | Type {- SO_TYPE -}
+ | SoError {- SO_ERROR -}
+ | DontRoute {- SO_DONTROUTE -}
+ | Broadcast {- SO_BROADCAST -}
+ | SendBuffer {- SO_SNDBUF -}
+ | RecvBuffer {- SO_RCVBUF -}
+ | KeepAlive {- SO_KEEPALIVE -}
+ | OOBInline {- SO_OOBINLINE -}
+ | TimeToLive {- IP_TTL -}
+ | MaxSegment {- TCP_MAXSEG -}
+ | NoDelay {- TCP_NODELAY -}
+ | Linger {- SO_LINGER -}
+ | RecvLowWater {- SO_RCVLOWAT -}
+ | SendLowWater {- SO_SNDLOWAT -}
+ | RecvTimeOut {- SO_RCVTIMEO -}
+ | SendTimeOut {- SO_SNDTIMEO -}
+
+ socketOptLevel :: SocketOption -> CInt
+ socketOptLevel so =
+ case so of
+ TimeToLive -> 0
+ MaxSegment -> 6
+ NoDelay -> 6
+ _ -> 1
+
+ packSocketOption :: SocketOption -> CInt
+ packSocketOption so =
+ case so of
+ Debug -> 1
+ ReuseAddr -> 2
+ Type -> 3
+ SoError -> 4
+ DontRoute -> 5
+ Broadcast -> 6
+ SendBuffer -> 7
+ RecvBuffer -> 8
+ KeepAlive -> 9
+ OOBInline -> 10
+ TimeToLive -> 2
+ MaxSegment -> 2
+ NoDelay -> 1
+ Linger -> 13
+ RecvLowWater -> 18
+ SendLowWater -> 19
+ RecvTimeOut -> 20
+ SendTimeOut -> 21
+
+Everything looks good so I thought long and hard about this. Then, by chance, I just looked at the man page for setsockopt() and it mentioned SOL_SOCKET and I was like \"Hmm...\"
+
+ % grep -R SOL_SOCKET /usr/include
+ /usr/include/openssl/e_os.h:#define ioctlsocket(a,b,c) setsockopt((a),SOL_SOCKET,(b),(c),sizeof(*(c)))
+ /usr/include/sys/socket.h:#define SOL_SOCKET 0xffff /* options for socket level */
+ /usr/include/sys/socket.h:/* Read using getsockopt() with SOL_SOCKET, SO_PEERCRED */
+
+Wat?
+
+ #define SOL_SOCKET 0xffff
+
+Going back to the Haskell code above I realized that SetSocketOption will NEVER feed 0xffff as level to setsockopt() because socketOptLevel returns 1 unless optname is TimeToLive, MaxSegment or NoDelay.
+
+Am I way off?
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_12_fdec033e37652c51fbcd74438586d285._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_12_fdec033e37652c51fbcd74438586d285._comment
new file mode 100644
index 0000000000..77c8edc68a
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_12_fdec033e37652c51fbcd74438586d285._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 12"
+ date="2014-02-08T20:03:30Z"
+ content="""
+WRT haskell static linking, AFAIK that only affects haskell libraries. If they in turn link with C libs, the linking is still dynamic. At least this is the case on both Linux and the limited BSDs I've used it on. Have no OpenBSD experience.
+
+`SOL_SOCKET` is 1 on linux, so you may have the culprit.
+
+However.. That's a really old version of network! 2.2.1.8 is from 2010. In a more current 2.4.x version, packSocketOption uses the `SOL_SOCKET` value and not 1, so should work AFAICS.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_13_ed3716baf787ca17d227ce2e327a1959._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_13_ed3716baf787ca17d227ce2e327a1959._comment
new file mode 100644
index 0000000000..3981d32bfd
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_13_ed3716baf787ca17d227ce2e327a1959._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 13"
+ date="2014-02-08T20:12:12Z"
+ content="""
+Does your binary end up dynamically linked to libxml2 etc? If not, it certianly seems plausible that the haskell libs statically linked with the C libs, and then at binary link time it tried to redundantly link with the libs again and failed. If this is the case, it seems it would probably be a bug in ghc. You can use `cabal build --ghc-options=-v` to get a look at how the linker is run.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_14_cf5f92e5cdfc738e7f6178c1d7a73ceb._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_14_cf5f92e5cdfc738e7f6178c1d7a73ceb._comment
new file mode 100644
index 0000000000..bb4d095a37
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_14_cf5f92e5cdfc738e7f6178c1d7a73ceb._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 14"
+ date="2014-02-08T20:29:46Z"
+ content="""
+Sigh.. Ofcourse it was an old version. It never occurred to me to check that. I was just Googling around and stumbled over that page.
+Do you have any pointers on how I would debug this further?
+
+Regarding the linking; I haven't checked it any further actually. I'm planning on investigating that further once I can get this error sorted out. But my hypothesis is that it's all statically linked all the way through, like I said. That would also explain those error messages I got during linking before.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_15_ad4b7191c9b8f67def33b26a1d762a5d._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_15_ad4b7191c9b8f67def33b26a1d762a5d._comment
new file mode 100644
index 0000000000..4aeda69ebf
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_15_ad4b7191c9b8f67def33b26a1d762a5d._comment
@@ -0,0 +1,26 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 15"
+ date="2014-02-08T20:56:10Z"
+ content="""
+I think you need to find which calls to setSocketOption are failing and/or what value is causing the crash. It's a bit of a pain to get a backtrace on error (would need to build everything with profiling enabled and run git-annex with +RTS -xc options). Probably simplest to modify the setSocketOption code:
+
+[[!format patch \"\"\"
+diff --git a/Network/Socket.hsc b/Network/Socket.hsc
+index 2fe62ee..0c66432 100644
+--- a/Network/Socket.hsc
++++ b/Network/Socket.hsc
+@@ -963,7 +963,7 @@ setSocketOption :: Socket
+ setSocketOption (MkSocket s _ _ _ _) so v = do
+ (level, opt) <- packSocketOption' \"setSocketOption\" so
+ with (fromIntegral v) $ \ptr_v -> do
+- throwSocketErrorIfMinus1_ \"setSocketOption\" $
++ throwSocketErrorIfMinus1_ (\"setSocketOption \" ++ show so ++ \" \" ++ show v) $
+ c_setsockopt s level opt ptr_v
+ (fromIntegral (sizeOf (undefined :: CInt)))
+ return ()
+\"\"\"]]
+
+Which should make it print out a quite nice symbolic name of the option being used on failure, which will make it easy to find any call sites and more importantly, determine what's wrong with that option.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_16_2e765b5286d816bea00880a17a20cbfb._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_16_2e765b5286d816bea00880a17a20cbfb._comment
new file mode 100644
index 0000000000..def40653da
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_16_2e765b5286d816bea00880a17a20cbfb._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 16"
+ date="2014-02-08T21:08:38Z"
+ content="""
+Thanks for that code snippet! I'll try it out within the next few minutes.
+
+Also, how would I go about rebuilding everything with profiling support? I'm doing this testing in a virtual machine so I can always start over from scratch.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_17_ded9011dcdbe4de05189a0e8d040f045._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_17_ded9011dcdbe4de05189a0e8d040f045._comment
new file mode 100644
index 0000000000..f361268419
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_17_ded9011dcdbe4de05189a0e8d040f045._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 17"
+ date="2014-02-08T21:23:02Z"
+ content="""
+Blow away ~/.ghc and ~/.cabal; cabal update; put `library-profiling: True` in ~/.cabal/config; and reinstall everything.
+
+Note that you may need to first build ghc's own bundled libraries with profiling support, if your ghc installation does not already include them. I don't know how to do that since on debian I can just `apt-get install ghc-prof`. If that's needed, ghc will tell you and refuse to build stuff with profiling.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_18_f7a85b46bf7afaaf431d6771219c66b0._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_18_f7a85b46bf7afaaf431d6771219c66b0._comment
new file mode 100644
index 0000000000..d8d73a0b77
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_18_f7a85b46bf7afaaf431d6771219c66b0._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 18"
+ date="2014-02-08T23:25:29Z"
+ content="""
+I applied your patch and rebuilt. I even tried doing it from scratch just to get it right.
+
+I have three news:
+
+1) I got it completely working in a virtual machine
+
+2) On my actual (physical) openbsd machine it still isn't working, even though they're almost identical. The only difference is that the physical one also has IPv6 connectivity, while the virtual machine doesn't. Could that be it? I don't know yet, although I'm about to try it.
+
+3) Your patch did not help. It still didn't print out anything more useful, suggesting that it in fact isn't that function that is throwing the error. [This](http://i.imgur.com/tmBiseE.png) is what the actual error looks like and shows up after I enter the jabber account details.
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_19_217be2000e423e844241d405ba9f64c8._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_19_217be2000e423e844241d405ba9f64c8._comment
new file mode 100644
index 0000000000..7ea52c150a
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_19_217be2000e423e844241d405ba9f64c8._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.172"
+ subject="comment 19"
+ date="2014-02-09T02:13:20Z"
+ content="""
+I'll bet you didn't rebuild all the libraries that depend on network. (Which all that static linking makes necessary...)
+
+IPv6 was my first guess; see http://git-annex.branchable.com/bugs/More_build_oddities_under_OpenBSD/#comment-84ee81cd162d22283fcccc1a41c8f8b3
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_1_4ffea64907656ff2ec65ff4450aadda7._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_1_4ffea64907656ff2ec65ff4450aadda7._comment
new file mode 100644
index 0000000000..f2ac7af8f0
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_1_4ffea64907656ff2ec65ff4450aadda7._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T18:49:38Z"
+ content="""
+This is definitely not an issue in git-annex's code. Two C libraries are exporting the same symbol (gnulib might be the other one, or it could be part of the OpenBSD libc as it's some deprecated POSIX symbol, I don't know) and this is simply not apparent until the linker tries to make a binary linking with both.
+
+I have dealt with a similar issue on Android by modifying C libraries to not export colliding symbols. See:
+
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_2_4fb96984757b3d37a1a5ebce664aa8fe._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_2_4fb96984757b3d37a1a5ebce664aa8fe._comment
new file mode 100644
index 0000000000..248f7fb335
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_2_4fb96984757b3d37a1a5ebce664aa8fe._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 2"
+ date="2014-02-07T19:38:14Z"
+ content="""
+I do realize that it's not a fault in git-annex' code. I'm sorry if it was a stupid idea to post it here, but I was thinking if there exists some kind of workaround one could implement in the build system. I mean.. This isn't the first time someone compiles a program with libidn, gettext and/or gnutls (According to 'grep -R c_isascii /usr')
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_3_c5fdf29499a02be83850d1238fc8ce23._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_3_c5fdf29499a02be83850d1238fc8ce23._comment
new file mode 100644
index 0000000000..ee7c537d91
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_3_c5fdf29499a02be83850d1238fc8ce23._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 3"
+ date="2014-02-07T20:57:54Z"
+ content="""
+I have researched this a little more and I am not entirely convinced it is an actual conflict anywhere. I did, in fact, compile a patched version of libidn WITHOUT the c_isascii symbols and.. It suddenly started complaining about even MORE symbols (stringprep_utf8_to_unichar).
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_4_d42106128c3dac2dd7761a82cc03912f._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_4_d42106128c3dac2dd7761a82cc03912f._comment
new file mode 100644
index 0000000000..9677848d3d
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_4_d42106128c3dac2dd7761a82cc03912f._comment
@@ -0,0 +1,9 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 4"
+ date="2014-02-07T22:12:43Z"
+ content="""
+Couldn't it be possible that something is passed twice on the command line, like that message says could be the reason? Because I have inspected my systems and the only thing I can find that even contains such a string (stringprep_utf8_to_unichar) is libidn so there shouldn't be any conflicts.
+
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_5_71166beb796f22dcee065a167cd5e0ed._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_5_71166beb796f22dcee065a167cd5e0ed._comment
new file mode 100644
index 0000000000..a2772452d2
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_5_71166beb796f22dcee065a167cd5e0ed._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 5"
+ date="2014-02-08T14:46:10Z"
+ content="""
+Okay, so I did work around this with an ugly hack (I'm not even sure it will work properly) so I now have XMPP support, according to git-annex.
+
+But.. When I try to play around with XMPP I get:
+
+ setSocketOption: invalid argument (Invalid argument)
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_6_65913a2de8bbe981beaa66c58d2429b5._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_6_65913a2de8bbe981beaa66c58d2429b5._comment
new file mode 100644
index 0000000000..ff76fb3ded
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_6_65913a2de8bbe981beaa66c58d2429b5._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 6"
+ date="2014-02-08T17:23:54Z"
+ content="""
+Googling around I found [this](http://lpaste.net/77947) codesnippet that suggests setSocketOption is broken under OpenBSD
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_7_8dd46cec230125d1410d8e6824aeddf2._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_7_8dd46cec230125d1410d8e6824aeddf2._comment
new file mode 100644
index 0000000000..72b427357a
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_7_8dd46cec230125d1410d8e6824aeddf2._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 7"
+ date="2014-02-08T17:42:52Z"
+ content="""
+What was the ugly hack that got it to link?
+
+I've seen setSocketOption fail on other OS's for various portability reasons. The haskell library that is responsible for this is , and you can find several setSocketOption calls in it. I've had good luck ifdefing those out when they don't work.
+
+Here's a patch where I disable the IPv6Only setting on Android (amoung other unrelated porting)
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_8_275d3e62cb5667a2d6ddd90db7a40bff._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_8_275d3e62cb5667a2d6ddd90db7a40bff._comment
new file mode 100644
index 0000000000..f7f7e34291
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_8_275d3e62cb5667a2d6ddd90db7a40bff._comment
@@ -0,0 +1,18 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkzwmw_zyMpZC9_J7ey--woeYPoZkAOgGw"
+ nickname="dxtrish"
+ subject="comment 8"
+ date="2014-02-08T18:13:33Z"
+ content="""
+What I did was to temporarily move away (or rename) the offending libs. What I essentially did was this:
+
+ cabal configure
+ cabal build
+ sudo mv /usr/local/lib/lib{xml2,gnutls,gsasl,idn}.a /tmp
+ cabal install
+ sudo mv /tmp/lib{xml2,gnutls,gsasl,idn}.a /usr/local/lib
+
+but I've also had to patch network-info. I've contacted the maintainer of that package but I haven't received anything. I'm considering creating an actual fork with my changes but that would almost seem kind of silly as I don't know *ANY* haskell.. But I am looking at the Haskell wiki as I'm typing this so I can see what I'm looking at :).
+
+Won't break anything by not setting SO_REUSEADDR? I suspect you're setting it for a reason?
+"""]]
diff --git a/doc/bugs/More_build_oddities_under_OpenBSD/comment_9_ec6a1eb6c7b264c23ec4bbd45465d7d8._comment b/doc/bugs/More_build_oddities_under_OpenBSD/comment_9_ec6a1eb6c7b264c23ec4bbd45465d7d8._comment
new file mode 100644
index 0000000000..dee77a69f8
--- /dev/null
+++ b/doc/bugs/More_build_oddities_under_OpenBSD/comment_9_ec6a1eb6c7b264c23ec4bbd45465d7d8._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 9"
+ date="2014-02-08T18:29:41Z"
+ content="""
+So you moved away libs in /usr/local to expose usable ones in /usr?
+
+I've had luck before sending the network-info mantainer pull requests:
+
+git-annex does set ReuseAddr in one place; in Utility/Webapp.hs. The only time that would have a benefit would be when using `git annex webapp --listen=address:port` and starting and restarting the webapp. Normally the webapp chooses a random free port so it shouldn't need that.
+"""]]
diff --git a/doc/bugs/On_Windows_the_Comitted_Symlinks_are_not_Relative.mdwn b/doc/bugs/On_Windows_the_Comitted_Symlinks_are_not_Relative.mdwn
new file mode 100644
index 0000000000..3ea44f8575
--- /dev/null
+++ b/doc/bugs/On_Windows_the_Comitted_Symlinks_are_not_Relative.mdwn
@@ -0,0 +1,102 @@
+### Please describe the problem.
+On Windows 7, the committed symlink files are always relative to the repo's .git root; they are not prefixed with the correct number of ../ for the given level of directing nesting.
+
+Trying to correct this with `git annex fix` returns "You cannot run this command in a direct mode repository."
+
+I believe that this is also the source of a pathological case I'm seeing on Windows. After adding a lot of content, commands like `git annex sync` and `git annex status` appear to re-checksum the entire annex. After syncing the repo to a Linux machine, fixing the symlinks there, and syncing back, these commands become snappy again.
+
+### What steps will reproduce the problem?
+
+[[!format sh """
+git init
+git annex init
+mkdir -p one/two/three/four/five/six
+
+# drop files into the dir structure
+git annex add .
+git annex sync
+git log -p
+"""]]
+
+### What version of git-annex are you using? On what operating system?
+
+git-annex version: 5.20140203-g83e6fb7
+
+on Windows 7 Pro
+
+### Please provide any additional information below.
+
+The output of `git log -p` for me:
+
+ commit f4d88b6bc99cc94a0b0154da41d06bad3f23cc1e
+ Author: Justin Geibel <...>
+ Date: Tue Feb 4 20:56:32 2014 -0500
+
+ git-annex automatic sync
+
+ diff --git a/git-annex-installer.exe b/git-annex-installer.exe
+ new file mode 120000
+ index 0000000..64f7d83
+ --- /dev/null
+ +++ b/git-annex-installer.exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/GW/Wk/SHA256E-s14413167--ea3a1e4c09ad12fdb2993a157b77b246a058f7f0ca2cd174d8cc675d1495ec4d.exe/SHA256E-s14413167--ea3a1e4c09ad12fdb2993a157b77b246a058f7f0ca2cd174d8cc675d1495ec4d.exe
+ \ No newline at end of file
+ diff --git a/one/git-annex-installer(1).exe b/one/git-annex-installer(1).exe
+ new file mode 120000
+ index 0000000..5b37a29
+ --- /dev/null
+ +++ b/one/git-annex-installer(1).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/6k/8K/SHA256E-s19286321--add3e1ac7ceabce7aa1ed1907895ae527fc095610d1e21127e99814728b24f11.exe/SHA256E-s19286321--add3e1ac7ceabce7aa1ed1907895ae527fc095610d1e21127e99814728b24f11.exe
+ \ No newline at end of file
+ diff --git a/one/two/git-annex-installer(2).exe b/one/two/git-annex-installer(2).exe
+ new file mode 120000
+ index 0000000..f89508f
+ --- /dev/null
+ +++ b/one/two/git-annex-installer(2).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/Zm/6K/SHA256E-s19573485--4f2a22c5b96308cf694c85564940d3cba22b5e8b3b714b242116c91369be75ee.exe/SHA256E-s19573485--4f2a22c5b96308cf694c85564940d3cba22b5e8b3b714b242116c91369be75ee.exe
+ \ No newline at end of file
+ diff --git a/one/two/three/four/five/git-annex-installer(5).exe b/one/two/three/four/five/git-annex-installer(5).exe
+ new file mode 120000
+ index 0000000..34565f9
+ --- /dev/null
+ +++ b/one/two/three/four/five/git-annex-installer(5).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/p3/Xq/SHA256E-s19956630--ec421bfc6cb0b4df2b5195d9229cbcc27a2e5505e0b879bf07e1be38dcc64a42.exe/SHA256E-s19956630--ec421bfc6cb0b4df2b5195d9229cbcc27a2e5505e0b879bf07e1be38dcc64a42.exe
+ \ No newline at end of file
+ diff --git a/one/two/three/four/five/six/git-annex-installer(6).exe b/one/two/three/four/five/six/git-annex-installer(6).exe
+ new file mode 120000
+ index 0000000..d6f97d9
+ --- /dev/null
+ +++ b/one/two/three/four/five/six/git-annex-installer(6).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/9G/5g/SHA256E-s19967171--c9e33dff779a43e76089ec3bee3411299d5b8abfa67ae1b459cee5a812c5194d.exe/SHA256E-s19967171--c9e33dff779a43e76089ec3bee3411299d5b8abfa67ae1b459cee5a812c5194d.exe
+ \ No newline at end of file
+ diff --git a/one/two/three/four/git-annex-installer(4).exe b/one/two/three/four/git-annex-installer(4).exe
+ new file mode 120000
+ index 0000000..a4f791c
+ --- /dev/null
+ +++ b/one/two/three/four/git-annex-installer(4).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/8J/pM/SHA256E-s19959961--7e4521036f891bba97f4c04527946e26ef43b14576d874c666e73dee405c18cf.exe/SHA256E-s19959961--7e4521036f891bba97f4c04527946e26ef43b14576d874c666e73dee405c18cf.exe
+ \ No newline at end of file
+ diff --git a/one/two/three/git-annex-installer(3).exe b/one/two/three/git-annex-installer(3).exe
+ new file mode 120000
+ index 0000000..dda7284
+ --- /dev/null
+ +++ b/one/two/three/git-annex-installer(3).exe
+ @@ -0,0 +1 @@
+ +.git/annex/objects/5X/qQ/SHA256E-s19915186--c6dc288ec8a77404c0ebc22cbe9b4ec911103fd022c3ca74eec582604dff80a7.exe/SHA256E-s19915186--c6dc288ec8a77404c0ebc22cbe9b4ec911103fd022c3ca74eec582604dff80a7.exe
+ \ No newline at end of file
+
+> [[fixed|done]] -- I didn't notice this before because it happened to do
+> the right thing if you cd'd into the subdir before adding the file there.
+>
+> WRT the slow down issue, I don't see how it could matter to git-annex on
+> Windows whether the symlinks point to the right place. It only looks at
+> the basename of the symlink target to get the key. If you have a
+> repository that behaves poorly, you can probably use --debug to see if
+> git-annex is calling some expensive series of git commands somehow.
+> --[[Joey]]
diff --git a/doc/bugs/Repository_in_manual_mode_does_not_hold_files.mdwn b/doc/bugs/Repository_in_manual_mode_does_not_hold_files.mdwn
new file mode 100644
index 0000000000..9572487dd8
--- /dev/null
+++ b/doc/bugs/Repository_in_manual_mode_does_not_hold_files.mdwn
@@ -0,0 +1,305 @@
+### Please describe the problem.
+
+I have two repositories in my local network which are locally paired and synced using git-annex assistant (setup using webapp, both in direct mode). The one (master) has all files and is in mode "full backup". The second one (slave) is in "manual" mode and should therefore only contain the file content it already has. But it also should not loose any content it has until I explicitely drop it but this is exactly what happens! Files are getting dropped (I think it happens during git-annex startup of the slave repository, but I am not sure).
+
+### What steps will reproduce the problem?
+
+1. Setup two repositories using git-annex webapp in local network
+2. Set one to "full backup" mode, the second to "manual" mode
+3. Add files to the master repository
+4. Pair both repositories over webapp
+5. Call git-annex get folderA on slave system to transfer some file contents to it.
+
+=> After some time the file contents from folderA seem to disappear on slave system.
+
+### What version of git-annex are you using? On what operating system?
+
+* Master (full backup) repository is running on Ubuntu Server 12.04 and git-annex 5.20140117.1 from PPA. Git version 1.7.9.5
+* Slave (manual) repository is running on Gentoo Linux with 5.20140116, created from own ebuild. Git version 1.8.4.5
+
+### Please provide any additional information below.
+
+[[!format sh """
+[2014-01-29 09:14:15 CET] main: starting assistant version 5.20140116
+[2014-01-29 09:19:33 CET] TransferScanner: Syncing with Eifel.fritz.box__mnt_raid_Media
+Already up-to-date.
+
+(scanning...) [2014-01-29 09:19:34 CET] Watcher: Performing startup scan
+Already up-to-date.
+Already up-to-date.
+[2014-01-29 09:35:31 CET] Committer: Committing changes to git
+[2014-01-29 09:35:31 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+[2014-01-29 09:40:37 CET] Committer: Committing changes to git
+[2014-01-29 09:44:15 CET] Committer: Committing changes to git
+Von ssh://git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media
+ 390c764..7775ce1 annex/direct/master -> Eifel.fritz.box__mnt_raid_Media/annex/direct/master
+ eca59d1..59db343 git-annex -> Eifel.fritz.box__mnt_raid_Media/git-annex
+ + a1f3176...7775ce1 synced/master -> Eifel.fritz.box__mnt_raid_Media/synced/master (Aktualisierung erzwungen)
+Already up-to-date.
+error: Ref refs/heads/synced/master is at a1f3176ff3821cdd9aa74bfa310dfdccb8452247 but expected 7775ce196da4561367ee231ce116fe5849827c51
+remote: error: failed to lock refs/heads/synced/master
+To ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/
+ 98219eb..3d2b713 git-annex -> synced/git-annex
+ ! [remote rejected] annex/direct/master -> synced/master (failed to lock)
+error: Fehler beim Versenden einiger Referenzen nach 'ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/'
+Von ssh://git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media
+ 7775ce1..a1f3176 annex/direct/master -> Eifel.fritz.box__mnt_raid_Media/annex/direct/master
+ 59db343..6e39b5b git-annex -> Eifel.fritz.box__mnt_raid_Media/git-annex
+ 7775ce1..a1f3176 synced/master -> Eifel.fritz.box__mnt_raid_Media/synced/master
+Already up-to-date.
+[2014-01-29 09:51:41 CET] Committer: Committing changes to git
+error: Ref refs/heads/synced/git-annex is at 3d2b7131d39c78fc56f67e29617e72b177807449 but expected 98219eb545d5dc51da9984ede4b4c5c41ec188d0
+remote: error: failed to lock refs/heads/synced/git-annex
+To ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/
+ ! [remote rejected] git-annex -> synced/git-annex (failed to lock)
+error: Fehler beim Versenden einiger Referenzen nach 'ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/'
+To ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/
+ 3d2b713..5bd0d7e git-annex -> synced/git-annex
+[2014-01-29 09:51:51 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+Everything up-to-date
+Everything up-to-date
+[2014-01-29 09:53:01 CET] Committer: Committing changes to git
+[2014-01-29 09:53:01 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+Everything up-to-date
+
+
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(merging synced/git-annex into git-annex...)
+(Recording state in git...)
+(merging synced/git-annex into git-annex...)
+(Recording state in git...)
+
+
+(Recording state in git...)
+(Recording state in git...)
+(started...) [2014-01-29 09:53:48 CET] Committer: Committing changes to git
+[2014-01-29 09:53:48 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+Everything up-to-date
+[2014-01-29 10:19:33 CET] NetWatcherFallback: Syncing with Eifel.fritz.box__mnt_raid_Media
+Von ssh://git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media
+ 6e39b5b..5bd0d7e git-annex -> Eifel.fritz.box__mnt_raid_Media/git-annex
+Everything up-to-date
+[2014-01-29 10:39:49 CET] Committer: Committing changes to git
+[2014-01-29 10:39:49 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+[2014-01-29 10:39:50 CET] Committer: Committing changes to git
+[2014-01-29 10:39:51 CET] Committer: Committing changes to git
+[2014-01-29 10:39:53 CET] Committer: Committing changes to git
+[2014-01-29 10:39:54 CET] Committer: Committing changes to git
+[2014-01-29 10:39:55 CET] Committer: Committing changes to git
+[2014-01-29 10:39:56 CET] Committer: Committing changes to git
+[2014-01-29 10:39:57 CET] Committer: Committing changes to git
+[2014-01-29 10:39:59 CET] Committer: Committing changes to git
+[2014-01-29 10:40:00 CET] Committer: Committing changes to git
+[2014-01-29 10:40:01 CET] Committer: Committing changes to git
+[2014-01-29 10:40:02 CET] Committer: Committing changes to git
+[2014-01-29 10:40:03 CET] Committer: Committing changes to git
+[2014-01-29 10:40:05 CET] Committer: Committing changes to git
+[2014-01-29 10:40:07 CET] Committer: Adding AlbumArtSmall.jpg Folder.jpg
+
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+add Audio/Musik/2raumwohnung/2002 - In Wirklich/AlbumArtSmall.jpg ok
+add Audio/Musik/2raumwohnung/2002 - In Wirklich/Folder.jpg [2014-01-29 10:40:07 CET] Committer: Committing changes to git
+[2014-01-29 10:40:08 CET] Committer: Committing changes to git
+[2014-01-29 10:40:09 CET] Committer: Committing changes to git
+[2014-01-29 10:40:11 CET] Committer: Committing changes to git
+[2014-01-29 10:40:12 CET] Committer: Committing changes to git
+[2014-01-29 10:40:13 CET] Committer: Committing changes to git
+[2014-01-29 10:40:14 CET] Committer: Committing changes to git
+[2014-01-29 10:40:16 CET] Committer: Committing changes to git
+[2014-01-29 10:40:17 CET] Committer: Committing changes to git
+[2014-01-29 10:40:18 CET] Committer: Committing changes to git
+[2014-01-29 10:40:19 CET] Committer: Committing changes to git
+[2014-01-29 10:40:20 CET] Committer: Committing changes to git
+[2014-01-29 10:40:21 CET] Committer: Committing changes to git
+[2014-01-29 10:40:23 CET] Committer: Committing changes to git
+[2014-01-29 10:40:24 CET] Committer: Committing changes to git
+[2014-01-29 10:40:26 CET] Committer: Committing changes to git
+[2014-01-29 10:40:27 CET] Committer: Committing changes to git
+[2014-01-29 10:40:28 CET] Committer: Committing changes to git
+[2014-01-29 10:40:29 CET] Committer: Committing changes to git
+[2014-01-29 10:40:30 CET] Committer: Committing changes to git
+[2014-01-29 10:40:31 CET] Committer: Committing changes to git
+[2014-01-29 10:40:32 CET] Committer: Committing changes to git
+[2014-01-29 10:40:34 CET] Committer: Committing changes to git
+[2014-01-29 10:40:35 CET] Committer: Committing changes to git
+[2014-01-29 10:40:36 CET] Committer: Committing changes to git
+[2014-01-29 10:40:37 CET] Committer: Committing changes to git
+[2014-01-29 10:40:39 CET] Committer: Committing changes to git
+[2014-01-29 10:40:40 CET] Committer: Committing changes to git
+[2014-01-29 10:40:41 CET] Committer: Committing changes to git
+[2014-01-29 10:40:42 CET] Committer: Committing changes to git
+[2014-01-29 10:40:44 CET] Committer: Committing changes to git
+[2014-01-29 10:40:45 CET] Committer: Committing changes to git
+[2014-01-29 10:40:46 CET] Committer: Committing changes to git
+[2014-01-29 10:40:47 CET] Committer: Committing changes to git
+[2014-01-29 10:40:48 CET] Committer: Committing changes to git
+[2014-01-29 10:40:50 CET] Committer: Committing changes to git
+[2014-01-29 10:40:51 CET] Committer: Committing changes to git
+[2014-01-29 10:40:52 CET] Committer: Committing changes to git
+[2014-01-29 10:40:53 CET] Committer: Committing changes to git
+[2014-01-29 10:40:54 CET] Committer: Committing changes to git
+[2014-01-29 10:40:55 CET] Committer: Committing changes to git
+[2014-01-29 10:40:57 CET] Committer: Committing changes to git
+[2014-01-29 10:40:58 CET] Committer: Committing changes to git
+[2014-01-29 10:40:59 CET] Committer: Committing changes to git
+[2014-01-29 10:41:00 CET] Committer: Committing changes to git
+[2014-01-29 10:41:02 CET] Committer: Committing changes to git
+[2014-01-29 10:41:03 CET] Committer: Committing changes to git
+[2014-01-29 10:41:04 CET] Committer: Committing changes to git
+[2014-01-29 10:41:05 CET] Committer: Committing changes to git
+[2014-01-29 10:41:06 CET] Committer: Committing changes to git
+[2014-01-29 10:41:07 CET] Committer: Committing changes to git
+[2014-01-29 10:41:09 CET] Committer: Committing changes to git
+[2014-01-29 10:41:10 CET] Committer: Committing changes to git
+[2014-01-29 10:41:11 CET] Committer: Committing changes to git
+[2014-01-29 10:41:12 CET] Committer: Committing changes to git
+[2014-01-29 10:41:23 CET] Committer: Committing changes to git
+[2014-01-29 10:41:24 CET] Committer: Committing changes to git
+[2014-01-29 10:41:29 CET] Committer: Committing changes to git
+[2014-01-29 10:41:30 CET] Committer: Committing changes to git
+[2014-01-29 10:41:32 CET] Committer: Committing changes to git
+[2014-01-29 10:41:33 CET] Committer: Committing changes to git
+[2014-01-29 10:41:34 CET] Committer: Committing changes to git
+[2014-01-29 10:41:35 CET] Committer: Committing changes to git
+[2014-01-29 10:41:36 CET] Committer: Committing changes to git
+[2014-01-29 10:41:38 CET] Committer: Adding AlbumArt_..Small.jpg Folder.jpg
+ok
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+(Recording state in git...)
+add Audio/Musik/Alanis Morissette/1995 - Jagged Little Pill/AlbumArt_{79951A99-BD71-4029-80F6-C3705D930871}_Small.jpg ok
+add Audio/Musik/Alanis Morissette/1995 - Jagged Little Pill/Folder.jpg [2014-01-29 10:41:38 CET] Committer: Committing changes to git
+[2014-01-29 10:41:39 CET] Committer: Committing changes to git
+[2014-01-29 10:41:41 CET] Committer: Committing changes to git
+[2014-01-29 10:41:42 CET] Committer: Committing changes to git
+[2014-01-29 10:41:44 CET] Committer: Committing changes to git
+[2014-01-29 10:41:45 CET] Committer: Committing changes to git
+[2014-01-29 10:41:46 CET] Committer: Committing changes to git
+[2014-01-29 10:41:47 CET] Committer: Committing changes to git
+[2014-01-29 10:41:48 CET] Committer: Committing changes to git
+[2014-01-29 10:41:49 CET] Committer: Committing changes to git
+[2014-01-29 10:41:51 CET] Committer: Committing changes to git
+[2014-01-29 10:41:52 CET] Committer: Committing changes to git
+[2014-01-29 10:41:54 CET] Committer: Committing changes to git
+[2014-01-29 10:41:55 CET] Committer: Committing changes to git
+[2014-01-29 10:41:56 CET] Committer: Committing changes to git
+[2014-01-29 10:41:58 CET] Committer: Committing changes to git
+[2014-01-29 10:41:59 CET] Committer: Committing changes to git
+[2014-01-29 10:42:00 CET] Committer: Committing changes to git
+[2014-01-29 10:42:01 CET] Committer: Committing changes to git
+[2014-01-29 10:42:02 CET] Committer: Committing changes to git
+[2014-01-29 10:42:04 CET] Committer: Committing changes to git
+[2014-01-29 10:42:05 CET] Committer: Committing changes to git
+[2014-01-29 10:42:06 CET] Committer: Committing changes to git
+[2014-01-29 10:42:07 CET] Committer: Committing changes to git
+[2014-01-29 10:42:08 CET] Committer: Committing changes to git
+[2014-01-29 10:42:10 CET] Committer: Committing changes to git
+[2014-01-29 10:42:11 CET] Committer: Committing changes to git
+[2014-01-29 10:42:12 CET] Committer: Committing changes to git
+[2014-01-29 10:42:13 CET] Committer: Committing changes to git
+[2014-01-29 10:42:14 CET] Committer: Committing changes to git
+[2014-01-29 10:42:15 CET] Committer: Committing changes to git
+[2014-01-29 10:42:17 CET] Committer: Committing changes to git
+[2014-01-29 10:42:18 CET] Committer: Committing changes to git
+[2014-01-29 10:42:19 CET] Committer: Committing changes to git
+[2014-01-29 10:42:20 CET] Committer: Committing changes to git
+[2014-01-29 10:42:21 CET] Committer: Committing changes to git
+[2014-01-29 10:42:23 CET] Committer: Committing changes to git
+[2014-01-29 10:42:24 CET] Committer: Committing changes to git
+[2014-01-29 10:42:25 CET] Committer: Committing changes to git
+[2014-01-29 10:42:26 CET] Committer: Committing changes to git
+[2014-01-29 10:42:27 CET] Committer: Committing changes to git
+[2014-01-29 10:42:28 CET] Committer: Committing changes to git
+To ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/
+ 5bd0d7e..1eda3be git-annex -> synced/git-annex
+[2014-01-29 10:43:43 CET] Pusher: Syncing with Eifel.fritz.box__mnt_raid_Media
+To ssh://fabian@git-annex-Eifel.fritz.box-fabian_.2Fmnt.2Fraid.2FMedia/mnt/raid/Media/
+ 1eda3be..4c70ad2 git-annex -> synced/git-annex
+"""]]
+
+> The only way a repository can become "unwanted" is if you
+> tell git-annex to start deleting it (or perhaps set its group to unwanted
+> manually). This will cause git-annex to try to move all files away from
+> that repository.
+>
+> So, AFAICS, this must have been a case of operator error. [[done]]
+> --[[Joey]]
diff --git a/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_1_86e8a4e546610e8e265806eb245d8aba._comment b/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_1_86e8a4e546610e8e265806eb245d8aba._comment
new file mode 100644
index 0000000000..855f3bf854
--- /dev/null
+++ b/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_1_86e8a4e546610e8e265806eb245d8aba._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 1"
+ date="2014-01-29T17:49:18Z"
+ content="""
+The preferred content setting for manual mode will try to clear out files that are in archive directories (once they reach an archive repository), but not other locations. I've re-tested it, and it still works that way. Perhaps your files are located inside archive directories; you don't say. If not, you will need to enable debug mode and show debug output.
+"""]]
diff --git a/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_2_17d5775a38b67ba4f0e73f6b89cff2d0._comment b/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_2_17d5775a38b67ba4f0e73f6b89cff2d0._comment
new file mode 100644
index 0000000000..f715db4588
--- /dev/null
+++ b/doc/bugs/Repository_in_manual_mode_does_not_hold_files/comment_2_17d5775a38b67ba4f0e73f6b89cff2d0._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://launchpad.net/~maestro-alubia"
+ nickname="maestro-alubia"
+ subject="comment 2"
+ date="2014-01-30T20:50:32Z"
+ content="""
+I did not configure any archive repositories or directories. But I just noticed my repository changed to \"unwanted\" in webapp. I am pretty sure I did not set this... I will set it back to manual now and see if this problem occurs again. But anyway, thanks for your help so far!
+"""]]
diff --git a/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour.mdwn b/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour.mdwn
new file mode 100644
index 0000000000..74966415eb
--- /dev/null
+++ b/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour.mdwn
@@ -0,0 +1,16 @@
+### Please describe the problem.
+
+trying to add a remote host using its avahi local name : nas.local (for example).
+
+### What steps will reproduce the problem?
+
+add remote server, use nas.local > cannot resolve nas.local
+
+### What version of git-annex are you using? On what operating system?
+
+Version: 5.20140116-g2d9ec29
+Ubuntu
+
+### Please provide any additional information below.
+
+
diff --git a/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour/comment_1_71cfedf4328eab224c7fb797c420ad0a._comment b/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour/comment_1_71cfedf4328eab224c7fb797c420ad0a._comment
new file mode 100644
index 0000000000..17fae5a3b1
--- /dev/null
+++ b/doc/bugs/Resolve_.local_adresses_using_avahi_or_bonjour/comment_1_71cfedf4328eab224c7fb797c420ad0a._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.68"
+ subject="comment 1"
+ date="2014-01-19T22:43:10Z"
+ content="""
+AFAIK, this will work fine if your OS is able to resolve those addresses using its regular resolver. Works fine here. Is `libnss-mdns` installed?
+"""]]
diff --git a/doc/bugs/S3_memory_leaks/comment_2_320a8e3bb7b207d1aff8926b9247f5ba._comment b/doc/bugs/S3_memory_leaks/comment_2_320a8e3bb7b207d1aff8926b9247f5ba._comment
new file mode 100644
index 0000000000..d4648b9c4f
--- /dev/null
+++ b/doc/bugs/S3_memory_leaks/comment_2_320a8e3bb7b207d1aff8926b9247f5ba._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://schnouki.net/"
+ nickname="Schnouki"
+ subject="comment 2"
+ date="2014-01-29T01:19:27Z"
+ content="""
+Any news about this?
+"""]]
diff --git a/doc/bugs/Share_with_friends_crash_in_osx/comment_10_8d90e23514d9f14283857c57017a5fcf._comment b/doc/bugs/Share_with_friends_crash_in_osx/comment_10_8d90e23514d9f14283857c57017a5fcf._comment
new file mode 100644
index 0000000000..ef7579c46b
--- /dev/null
+++ b/doc/bugs/Share_with_friends_crash_in_osx/comment_10_8d90e23514d9f14283857c57017a5fcf._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.68"
+ subject="comment 10"
+ date="2014-01-20T16:28:43Z"
+ content="""
+I have updated the autobuild again, now nettle is built with more optimisations disabled. I hope this fixes it because I'm running out of things to try.
+"""]]
diff --git a/doc/bugs/Share_with_friends_crash_in_osx/comment_11_1a0e174969e99e7b562854d2c3b3e606._comment b/doc/bugs/Share_with_friends_crash_in_osx/comment_11_1a0e174969e99e7b562854d2c3b3e606._comment
new file mode 100644
index 0000000000..5b5b94a401
--- /dev/null
+++ b/doc/bugs/Share_with_friends_crash_in_osx/comment_11_1a0e174969e99e7b562854d2c3b3e606._comment
@@ -0,0 +1,19 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkLdR1fuu5aEz3s9VKTBKVMize_SmeNRJM"
+ nickname="David"
+ subject="Past the SHA issues"
+ date="2014-01-20T23:14:53Z"
+ content="""
+Now we still have an issue with nettle, but now it's part of urandom. I'm not sure what to suggest...
+
+[[!format sh \"\"\"
+Thread 1 Crashed:
+0 H 0x00000001075d9756 do_device_source_urandom + 108
+1 H 0x00000001075d9686 do_device_source + 46
+2 H 0x00000001075d92b9 wrap_nettle_rnd_init + 74
+3 H 0x000000010755d585 _gnutls_rnd_init + 32
+4 H 0x0000000107551dae gnutls_global_init + 262
+5 git-annex 0x00000001054a28c3 0x103c83000 + 25295043
+6 git-annex 0x000000010692ab28 0x103c83000 + 46824232
+\"\"\"]]
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_1_dfb520258fdd633285b44cb16fd35612._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_1_dfb520258fdd633285b44cb16fd35612._comment
new file mode 100644
index 0000000000..7ece79f420
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_1_dfb520258fdd633285b44cb16fd35612._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawltxdgYMUK4CMJh3jC8AlegwyoiHA9Ka7o"
+ nickname="Justin"
+ subject="This test is still failing on Windows"
+ date="2014-01-29T14:37:33Z"
+ content="""
+This 1 test is still failing for me on Windows 7 Pro with the latest release (git-annex version: 5.20140128-gddb2083).
+
+I also followed the manual steps provided in the initial bug report. This resulted in two cloned repos which appeared to have resolved the conflict differently. Upon further investigation, I see that the conflict was in fact resolved consistently, just that the file sizes in the working directories are different because the file contents has not been synced (so some files contain the \"symlink\" path rather than the actual contents).
+
+After running a sync in both repositories with the new --contents option, the two working directories appear to be resolved consistently.
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_2_7908bf367652d2485ec703ae8958891b._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_2_7908bf367652d2485ec703ae8958891b._comment
new file mode 100644
index 0000000000..0a9e852f2f
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_2_7908bf367652d2485ec703ae8958891b._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 2"
+ date="2014-01-29T17:52:27Z"
+ content="""
+AFAICS, the test suite does not look at the contents of the files when testing this. Anyway, you said a lot about how it works when you try to reproduce the bug manually, but you didn't actually show how the test suite is failing.
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_3_30684a993b667b2594890f734638e91b._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_3_30684a993b667b2594890f734638e91b._comment
new file mode 100644
index 0000000000..83c033aed7
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_3_30684a993b667b2594890f734638e91b._comment
@@ -0,0 +1,142 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawltxdgYMUK4CMJh3jC8AlegwyoiHA9Ka7o"
+ nickname="Justin"
+ subject="comment 3"
+ date="2014-01-29T18:43:07Z"
+ content="""
+Here is the relevant portion of the test output. Sorry for getting caught up in my manual troubleshooting and not providing this info earlier.
+
+ conflict_resolution (mixed directory and file): Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ add conflictor ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ ok
+ push origin
+ Counting objects: 21, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (13/13), done.
+ Writing objects: 100% (16/16), 1.62 KiB | 0 bytes/s, done.
+ Total 16 (delta 2), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ 5a1abd2..b0de6d7 git-annex -> synced/git-annex
+ 4539cc8..af0b4de annex/direct/master -> synced/master
+ ok
+ add conflictor/subfile ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ remote: Counting objects: 21, done.
+ remote: Compressing objects: 100% (13/13), done.
+ remote: Total 16 (delta 2), reused 0 (delta 0)
+ Unpacking objects: 100% (16/16), done.
+ From c:/Users/geibeljt/annex/.t\repo
+ 4539cc8..af0b4de master -> origin/master
+ 5a1abd2..b0de6d7 synced/git-annex -> origin/synced/git-annex
+ 4539cc8..af0b4de synced/master -> origin/synced/master
+
+ Adding conflictor/subfile
+ CONFLICT (directory/file): There is a directory with name conflictor in HEAD. Adding conflictor as conflictor~
+ refs_remotes_origin_synced_master
+ Automatic merge failed; fix conflicts and then commit the result.
+ (Recording state in git...)
+ conflictor: needs merge
+ [annex/direct/master 7b21326] git-annex automatic merge conflict fix
+
+ Merge conflict was automatically resolved; you may want to examine the result.
+ ok
+ (merging origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ push origin
+ Counting objects: 32, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (19/19), done.
+ Writing objects: 100% (23/23), 2.18 KiB | 0 bytes/s, done.
+ Total 23 (delta 7), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ b0de6d7..b64838f git-annex -> synced/git-annex
+ af0b4de..7b21326 annex/direct/master -> synced/master
+ ok
+ commit ok
+ pull r2
+ remote: Counting objects: 32, done.
+ remote: Compressing objects: 100% (19/19), done.
+ remote: Total 23 (delta 7), reused 0 (delta 0)
+ Unpacking objects: 100% (23/23), done.
+ From ../../.t\tmprepo36
+ * [new branch] annex/direct/master -> r2/annex/direct/master
+ * [new branch] git-annex -> r2/git-annex
+ * [new branch] master -> r2/master
+ * [new branch] synced/master -> r2/synced/master
+
+ Updating af0b4de..7b21326
+ Fast-forward
+ conflictor | 1 -
+ conflictor.variant-cc12 | 1 +
+ conflictor/subfile | 1 +
+ 3 files changed, 2 insertions(+), 1 deletion(-)
+ delete mode 120000 conflictor
+ create mode 120000 conflictor.variant-cc12
+ create mode 120000 conflictor/subfile
+
+ Already up-to-date.
+ ok
+ (merging r2/git-annex into git-annex...)
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ add conflictor ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+
+ Adding conflictor/subfile
+ CONFLICT (file/directory): There is a directory with name conflictor in refs/remotes/origin/synced/master. Add
+ ing conflictor as conflictor~HEAD
+ Automatic merge failed; fix conflicts and then commit the result.
+ conflictor: needs merge
+
+ git-annex: c:\Users\geibeljt\annex\.t\tmprepo37\.git\annex\merge\conflictor: renameFile: inappropriate type (i
+ s a directory)
+ failed
+ push origin
+ Counting objects: 29, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (15/15), done.
+ Writing objects: 100% (19/19), 1.71 KiB | 0 bytes/s, done.
+ Total 19 (delta 5), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ b64838f..0c094c8 git-annex -> synced/git-annex
+ ! [rejected] annex/direct/master -> synced/master (non-fast-forward)
+ error: failed to push some refs to 'c:/Users/geibeljt/annex/.t\repo'
+ hint: Updates were rejected because a pushed branch tip is behind its remote
+ hint: counterpart. Check out this branch and integrate the remote changes
+ hint: (e.g. 'git pull ...') before pushing again.
+ hint: See the 'Note about fast-forwards' in 'git push --help' for details.
+
+ Pushing to origin failed.
+
+ (non-fast-forward problems can be solved by setting receive.denyNonFastforwards to false in the remote's git
+ config)
+ failed
+ git-annex: sync: 2 failed
+ FAIL
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_4_30e847ff438eda036c57cc740b638d8a._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_4_30e847ff438eda036c57cc740b638d8a._comment
new file mode 100644
index 0000000000..9a33c64ccf
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_4_30e847ff438eda036c57cc740b638d8a._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 4"
+ date="2014-01-29T19:48:51Z"
+ content="""
+Ok, what's happening is that code path calls System.PosixCompat.Files.rename, and on unix that maps to regular rename() which can rename files or directories, but on windows, it's a compatability stub that calls haskell's renameFile, which oddly refuses to rename directories.
+
+I remember testing my fix to the parent bug originally, but I don't know how. Possibly I changed something afterwards that exposed this new problem.
+
+Need to use System.Win32.File.moveFile, which actually can move directories too. Made this change in git, and you can download an windows autobuild of it already if you'd like.
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_5_04232cf2097676057cddf841ad47f44c._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_5_04232cf2097676057cddf841ad47f44c._comment
new file mode 100644
index 0000000000..b6d3383184
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_5_04232cf2097676057cddf841ad47f44c._comment
@@ -0,0 +1,86 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawltxdgYMUK4CMJh3jC8AlegwyoiHA9Ka7o"
+ nickname="Justin"
+ subject="comment 5"
+ date="2014-01-29T20:26:15Z"
+ content="""
+This seems to have affected a lot of tests, I'm now getting \"20 out of 72 tests failed\". In particular, error messages similar to the following show up now in many tests (with different paths for each test).
+
+ git-annex: MoveFile \"c:\\Users\\geibeljt\\annex\\.t\\tmprepo36\\.git\\annex\\objects\\574\\4ca\\SHA256E-s7--6f
+ e7bd6dcd1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7\\SHA256E-s7--6fe7bd6dcd1d46cfa98027c64f1e51d596
+ 64989c3b1e80a980bac1cb352a2ba7.map25112.tmp\" \"c:\\Users\\geibeljt\\annex\\.t\\tmprepo36\\.git\\annex\\objects\
+ \574\\4ca\\SHA256E-s7--6fe7bd6dcd1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7\\SHA256E-s7--6fe7bd6dc
+ d1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7.map\": already exists (Cannot create a file when that f
+ ile already exists.)
+
+
+---
+And here is the full output for the test that was originally failing. It now appears to fail much earlier than before.
+
+ conflict_resolution (mixed directory and file): Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ add conflictor ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ ok
+ push origin
+ Counting objects: 21, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (13/13), done.
+ Writing objects: 100% (16/16), 1.57 KiB | 0 bytes/s, done.
+ Total 16 (delta 3), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ a462941..43dcc49 git-annex -> synced/git-annex
+ 8268d47..3012c35 annex/direct/master -> synced/master
+ ok
+ add conflictor/subfile ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit
+ git-annex: MoveFile \"c:\\Users\\geibeljt\\annex\\.t\\tmprepo36\\.git\\annex\\objects\\574\\4ca\\SHA256E-s7--6f
+ e7bd6dcd1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7\\SHA256E-s7--6fe7bd6dcd1d46cfa98027c64f1e51d596
+ 64989c3b1e80a980bac1cb352a2ba7.map25112.tmp\" \"c:\\Users\\geibeljt\\annex\\.t\\tmprepo36\\.git\\annex\\objects\
+ \574\\4ca\\SHA256E-s7--6fe7bd6dcd1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7\\SHA256E-s7--6fe7bd6dc
+ d1d46cfa98027c64f1e51d59664989c3b1e80a980bac1cb352a2ba7.map\": already exists (Cannot create a file when that f
+ ile already exists.)
+ failed
+ pull origin
+ remote: Counting objects: 21, done.
+ remote: Compressing objects: 100% (13/13), done.
+ remote: Total 16 (delta 3), reused 0 (delta 0)
+ Unpacking objects: 100% (16/16), done.
+ From c:/Users/geibeljt/annex/.t\repo
+ 8268d47..3012c35 master -> origin/master
+ a462941..43dcc49 synced/git-annex -> origin/synced/git-annex
+ 8268d47..3012c35 synced/master -> origin/synced/master
+
+ Updating 8268d47..3012c35
+ Fast-forward
+ conflictor | 1 +
+ 1 file changed, 1 insertion(+)
+ create mode 120000 conflictor
+ ok
+ (merging origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ push origin
+ Counting objects: 24, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (13/13), done.
+ Writing objects: 100% (16/16), 1.42 KiB | 0 bytes/s, done.
+ Total 16 (delta 6), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ 43dcc49..c040cd6 git-annex -> synced/git-annex
+ ok
+ git-annex: sync: 1 failed
+ FAIL
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_6_9cb32f198eee25b7175cc9ad1795acb3._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_6_9cb32f198eee25b7175cc9ad1795acb3._comment
new file mode 100644
index 0000000000..3ba917fcb2
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_6_9cb32f198eee25b7175cc9ad1795acb3._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 6"
+ date="2014-01-29T21:24:34Z"
+ content="""
+I missed that moveFile refuses to overwrite existing files. This is fixed in git, and the autobuild is updating.
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_7_f8a70156d56c4be6cfbadb50e8a08285._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_7_f8a70156d56c4be6cfbadb50e8a08285._comment
new file mode 100644
index 0000000000..a41cf40afe
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_7_f8a70156d56c4be6cfbadb50e8a08285._comment
@@ -0,0 +1,174 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawltxdgYMUK4CMJh3jC8AlegwyoiHA9Ka7o"
+ nickname="Justin"
+ subject="comment 7"
+ date="2014-01-30T16:02:08Z"
+ content="""
+Alright, I've grabbed the latest autobuild and have tested again with 5.20140130-gcb99900. Back to failing just this one test case. Compared to my last two comments, the test appears to be getting further along before failing.
+
+ conflict_resolution (mixed directory and file): Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ add conflictor ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ ok
+ push origin
+ Counting objects: 21, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (13/13), done.
+ Writing objects: 100% (16/16), 1.66 KiB | 0 bytes/s, done.
+ Total 16 (delta 1), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ dafdb0b..2d106aa git-annex -> synced/git-annex
+ 688224a..18c2edb annex/direct/master -> synced/master
+ ok
+ add conflictor/subfile ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ remote: Counting objects: 21, done.
+ remote: Compressing objects: 100% (13/13), done.
+ remote: Total 16 (delta 1), reused 0 (delta 0)
+ Unpacking objects: 100% (16/16), done.
+ From c:/Users/geibeljt/annex/.t\repo
+ 688224a..18c2edb master -> origin/master
+ dafdb0b..2d106aa synced/git-annex -> origin/synced/git-annex
+ 688224a..18c2edb synced/master -> origin/synced/master
+
+ Adding conflictor/subfile
+ CONFLICT (directory/file): There is a directory with name conflictor in HEAD. Adding conflictor as conflictor~
+ refs_remotes_origin_synced_master
+ Automatic merge failed; fix conflicts and then commit the result.
+ (Recording state in git...)
+ conflictor: needs merge
+ [annex/direct/master 5026450] git-annex automatic merge conflict fix
+
+ Merge conflict was automatically resolved; you may want to examine the result.
+ ok
+ (merging origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ push origin
+ Counting objects: 32, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (19/19), done.
+ Writing objects: 100% (23/23), 2.18 KiB | 0 bytes/s, done.
+ Total 23 (delta 7), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ 2d106aa..aca0d04 git-annex -> synced/git-annex
+ 18c2edb..5026450 annex/direct/master -> synced/master
+ ok
+ commit ok
+ pull r2
+ remote: Counting objects: 32, done.
+ remote: Compressing objects: 100% (19/19), done.
+ remote: Total 23 (delta 7), reused 0 (delta 0)
+ Unpacking objects: 100% (23/23), done.
+ From ../../.t\tmprepo36
+ * [new branch] annex/direct/master -> r2/annex/direct/master
+ * [new branch] git-annex -> r2/git-annex
+ * [new branch] master -> r2/master
+ * [new branch] synced/master -> r2/synced/master
+
+ Updating 18c2edb..5026450
+ Fast-forward
+ conflictor | 1 -
+ conflictor.variant-cc12 | 1 +
+ conflictor/subfile | 1 +
+ 3 files changed, 2 insertions(+), 1 deletion(-)
+ delete mode 120000 conflictor
+ create mode 120000 conflictor.variant-cc12
+ create mode 120000 conflictor/subfile
+
+ Already up-to-date.
+ ok
+ (merging r2/git-annex into git-annex...)
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ Detected a filesystem without fifo support.
+ Disabling ssh connection caching.
+ Detected a crippled filesystem.
+ Enabling direct mode.
+ add conflictor ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+
+ Adding conflictor/subfile
+ CONFLICT (file/directory): There is a directory with name conflictor in refs/remotes/origin/synced/master. Add
+ ing conflictor as conflictor~HEAD
+ Automatic merge failed; fix conflicts and then commit the result.
+ conflictor: needs merge
+ (Recording state in git...)
+ [annex/direct/master 82abd2f] git-annex automatic merge conflict fix
+
+ Merge conflict was automatically resolved; you may want to examine the result.
+ ok
+ push origin
+ Counting objects: 32, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (17/17), done.
+ Writing objects: 100% (22/22), 1.95 KiB | 0 bytes/s, done.
+ Total 22 (delta 7), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ aca0d04..9d475c9 git-annex -> synced/git-annex
+ 5026450..82abd2f annex/direct/master -> synced/master
+ ok
+ add conflictor/subfile ok
+ (Recording state in git...)
+ (merging origin/git-annex origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ commit ok
+ pull origin
+ remote: Counting objects: 32, done.
+ remote: Compressing objects: 100% (17/17), done.
+ remote: Total 22 (delta 7), reused 0 (delta 0)
+ Unpacking objects: 100% (22/22), done.
+ From c:/Users/geibeljt/annex/.t\repo
+ 5026450..82abd2f master -> origin/master
+ aca0d04..9d475c9 synced/git-annex -> origin/synced/git-annex
+ 5026450..82abd2f synced/master -> origin/synced/master
+
+ Auto-merging conflictor/subfile
+ CONFLICT (add/add): Merge conflict in conflictor/subfile
+ Automatic merge failed; fix conflicts and then commit the result.
+ failed
+ (merging origin/synced/git-annex into git-annex...)
+ (Recording state in git...)
+ push origin
+ Counting objects: 34, done.
+ Delta compression using up to 4 threads.
+ Compressing objects: 100% (17/17), done.
+ Writing objects: 100% (22/22), 2.05 KiB | 0 bytes/s, done.
+ Total 22 (delta 5), reused 0 (delta 0)
+ To c:/Users/geibeljt/annex/.t\repo
+ 9d475c9..13a0faa git-annex -> synced/git-annex
+ ! [rejected] annex/direct/master -> synced/master (non-fast-forward)
+ error: failed to push some refs to 'c:/Users/geibeljt/annex/.t\repo'
+ hint: Updates were rejected because a pushed branch tip is behind its remote
+ hint: counterpart. Check out this branch and integrate the remote changes
+ hint: (e.g. 'git pull ...') before pushing again.
+ hint: See the 'Note about fast-forwards' in 'git push --help' for details.
+
+ Pushing to origin failed.
+
+ (non-fast-forward problems can be solved by setting receive.denyNonFastforwards to false in the remote's git
+ config)
+ failed
+ git-annex: sync: 2 failed
+ FAIL
+"""]]
diff --git a/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_8_02699dbf30270db090b00192850831db._comment b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_8_02699dbf30270db090b00192850831db._comment
new file mode 100644
index 0000000000..4db1b7786b
--- /dev/null
+++ b/doc/bugs/Test_test__95__mixed__95__conflict__95__resolution_fails_on_Windows_with___34__conflictor_directory_missing__34__/comment_8_02699dbf30270db090b00192850831db._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawltxdgYMUK4CMJh3jC8AlegwyoiHA9Ka7o"
+ nickname="Justin"
+ subject="comment 8"
+ date="2014-02-04T02:05:36Z"
+ content="""
+With the changes pushed today, I confirm I also have all 72 tests passing on Windows 7 with 5.20140203-g83e6fb7.
+
+Thanks!
+"""]]
diff --git a/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__.mdwn b/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__.mdwn
new file mode 100644
index 0000000000..0110891315
--- /dev/null
+++ b/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__.mdwn
@@ -0,0 +1,16 @@
+### Please describe the problem.
+After branching from master/HEAD^ and deleting the master branch, I was surprised that content introduced in master/HEAD is not reported as unused. Instead, one first has to delete the synced/master branch, and also the remote-tracking branches for master.
+
+Would it make sense to discount synced/* and the remote tracking branches when gathering unused files? If the remote-tracking branch always reflects the state of the remote, tracking a branch should not cause annex to think that the local annex is somehow using all the files on the remote. Or would that be unsafe? As for the synced/* branches I'm not so sure.
+
+### What steps will reproduce the problem?
+Clone annex A to B.
+Branch off of master^ in B.
+Delete master.
+Issue git annex unused. --> Content introduced in master is still not reported as unused.
+Delete synced/master --> Cf. above.
+Delete origin/master and origin/synced/master --> Content is now reported as unused.
+
+### What version of git-annex are you using? On what operating system?
+
+5.20131230
diff --git a/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__/comment_1_8fe44da0581d9b8c6ab5fe6aea8d83d1._comment b/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__/comment_1_8fe44da0581d9b8c6ab5fe6aea8d83d1._comment
new file mode 100644
index 0000000000..a89f761a41
--- /dev/null
+++ b/doc/bugs/Unused_files_not_being_reported:_Do_not_take_remote_tracking_branches_into_account__63__/comment_1_8fe44da0581d9b8c6ab5fe6aea8d83d1._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.46"
+ subject="comment 1"
+ date="2014-01-26T18:08:21Z"
+ content="""
+I'd rather that people not lose the content of annexed files that are in either their current local branch, or the current branch of any other clones of the repository that they might be working on. This is why `unused` looks at the remote tracking branches, and the various sync branches.
+"""]]
diff --git a/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency.mdwn b/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency.mdwn
new file mode 100644
index 0000000000..12a5e0c142
--- /dev/null
+++ b/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency.mdwn
@@ -0,0 +1,95 @@
+### Please describe the problem.
+
+Building a recent git-annex with cabal with the `minimal build'
+options given in the installation instructions fails. It is probably
+just a matter of fixing the dependencies in the cabal file.
+
+### What steps will reproduce the problem?
+Compile with:
+
+cabal install git-annex-5.20140108 --bindir=$HOME/bin -f"-assistant -webapp -webdav -pairing -xmpp -dns"
+
+### What version of git-annex are you using? On what operating system?
+Linux 2.6.32-5-686 i686 GNU/Linux
+
+
+### 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
+Resolving dependencies...
+[ 1 of 27] Compiling Utility.PartialPrelude ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/PartialPrelude.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/PartialPrelude.o )
+[ 2 of 27] Compiling Utility.FileSystemEncoding ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/FileSystemEncoding.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/FileSystemEncoding.o )
+[ 3 of 27] Compiling Utility.Applicative ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Applicative.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Applicative.o )
+[ 4 of 27] Compiling Utility.Data ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Data.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Data.o )
+[ 5 of 27] Compiling Utility.Exception ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Exception.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Exception.o )
+[ 6 of 27] Compiling Utility.Tmp ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Tmp.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Tmp.o )
+[ 7 of 27] Compiling Utility.Env ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Env.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Env.o )
+[ 8 of 27] Compiling Utility.UserInfo ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/UserInfo.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/UserInfo.o )
+[ 9 of 27] Compiling Utility.OSX ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/OSX.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/OSX.o )
+[10 of 27] Compiling Utility.Monad ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Monad.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Monad.o )
+[11 of 27] Compiling Utility.Misc ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Misc.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Misc.o )
+[12 of 27] Compiling Utility.Process ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Process.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Process.o )
+[13 of 27] Compiling Utility.Path ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Path.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Path.o )
+[14 of 27] Compiling Utility.FreeDesktop ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/FreeDesktop.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/FreeDesktop.o )
+[15 of 27] Compiling Assistant.Install.AutoStart ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Assistant/Install/AutoStart.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Assistant/Install/AutoStart.o )
+[16 of 27] Compiling Utility.SafeCommand ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/SafeCommand.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/SafeCommand.o )
+[17 of 27] Compiling Utility.ExternalSHA ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/ExternalSHA.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/ExternalSHA.o )
+[18 of 27] Compiling Utility.Directory ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Utility/Directory.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Utility/Directory.o )
+[19 of 27] Compiling Common ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Common.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Common.o )
+[20 of 27] Compiling Git.Version ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Git/Version.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Git/Version.o )
+[21 of 27] Compiling Config.Files ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Config/Files.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Config/Files.o )
+[22 of 27] Compiling Assistant.Install.Menu ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Assistant/Install/Menu.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Assistant/Install/Menu.o )
+[23 of 27] Compiling Build.TestConfig ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Build/TestConfig.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Build/TestConfig.o )
+[24 of 27] Compiling Build.Version ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Build/Version.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Build/Version.o )
+[25 of 27] Compiling Build.Configure ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Build/Configure.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Build/Configure.o )
+[26 of 27] Compiling Build.DesktopFile ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Build/DesktopFile.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Build/DesktopFile.o )
+[27 of 27] Compiling Main ( /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/Setup.hs, /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/Main.o )
+Linking /tmp/git-annex-5.20140108-30015/git-annex-5.20140108/dist/setup/setup ...
+ checking version...fatal: Not a git repository (or any of the parent directories): .git
+ 5.20140107
+ checking UPGRADE_LOCATION... not available
+ checking git... yes
+ checking git version... 1.7.2.5
+ checking cp -a... yes
+ checking cp -p... yes
+ checking cp --reflink=auto... yes
+ checking xargs -0... yes
+ checking rsync... yes
+ checking curl... no
+ checking wget... yes
+ checking bup... no
+ checking quvi... no
+ checking newquvi... no
+ checking nice... yes
+ checking ionice... yes
+ checking nocache... no
+ checking gpg... gpg
+ checking lsof... lsof
+ checking git-remote-gcrypt... not available
+ checking ssh connection caching... no
+ checking sha1... sha1sum
+ checking sha256... sha256sum
+ checking sha512... sha512sum
+ checking sha224... sha224sum
+ checking sha384... sha384sum
+Configuring git-annex-5.20140108...
+Building git-annex-5.20140108...
+Preprocessing executable 'git-annex' for git-annex-5.20140108...
+
+Remote/External.hs:29:8:
+ Could not find module `Control.Concurrent.STM'
+ It is a member of the hidden package `stm-2.4.2'.
+ Perhaps you need to add `stm' to the build-depends in your .cabal file.
+ Use -v to see a list of the files searched for.
+Failed to install git-annex-5.20140108
+cabal: Error: some packages failed to install:
+git-annex-5.20140108 failed during the building phase. The exception was:
+ExitFailure 1
+
+
+# End of transcript or log.
+"""]]
+
+> [[fixed|done]] --[[Joey]]
diff --git a/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency/comment_1_86e26ee9ec90aa00f25392052737f0f0._comment b/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency/comment_1_86e26ee9ec90aa00f25392052737f0f0._comment
new file mode 100644
index 0000000000..7b86c07cce
--- /dev/null
+++ b/doc/bugs/__96__minimal_build__39____fails_due_to_missing_stm_dependency/comment_1_86e26ee9ec90aa00f25392052737f0f0._comment
@@ -0,0 +1,36 @@
+[[!comment format=txt
+ username="https://www.google.com/accounts/o8/id?id=AItOawnlotDRSLW2JVXY3SLSwhrcHteqUHhTtoY"
+ nickname="Péter"
+ subject="Not fixed."
+ date="2014-01-27T00:43:45Z"
+ content="""
+It's still failing for me, on both i386 and amd64.
+
+Where exactly is it fixed?
+
+How is it possible to install git-annex using Cabal?
+
+http://stackoverflow.com/questions/21371272/cabal-missing-dependency-error
+
+$ cabal install git-annex --force-reinstalls --bindir=$HOME/bin.local -f\"-assistant -webapp -webdav -pairing -xmpp -dns\"
+...
+Configuring git-annex-5.20140116...
+Building git-annex-5.20140116...
+Preprocessing executable 'git-annex' for git-annex-5.20140116...
+
+Remote/External.hs:29:8:
+ Could not find module `Control.Concurrent.STM'
+ It is a member of the hidden package `stm-2.4.2'.
+ Perhaps you need to add `stm' to the build-depends in your .cabal file.
+ It is a member of the hidden package `stm-2.2.0.1'.
+ Perhaps you need to add `stm' to the build-depends in your .cabal file.
+ Use -v to see a list of the files searched for.
+cabal: Error: some packages failed to install:
+git-annex-5.20140116 failed during the building phase. The exception was: ExitFailure 1
+$ cabal install stm --force-reinstalls --bindir=$HOME/bin.local
+Resolving dependencies...
+All the requested packages are already installed:
+stm-2.4.2
+Use --reinstall if you want to reinstall anyway.
+
+"""]]
diff --git a/doc/bugs/assistant_eats_all_CPU/comment_16_16382708d1683a7a9eaaf953f3cdb735._comment b/doc/bugs/assistant_eats_all_CPU/comment_16_16382708d1683a7a9eaaf953f3cdb735._comment
new file mode 100644
index 0000000000..66c2b2724f
--- /dev/null
+++ b/doc/bugs/assistant_eats_all_CPU/comment_16_16382708d1683a7a9eaaf953f3cdb735._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.43"
+ subject="comment 16"
+ date="2014-01-17T19:07:10Z"
+ content="""
+This bug is about cpu usage when git-annex assistant should be sitting idle, not about the statup scan.
+"""]]
diff --git a/doc/bugs/assistant_eats_all_CPU/comment_17_bfa64822ad9b48fbd4d06c3e3a185b59._comment b/doc/bugs/assistant_eats_all_CPU/comment_17_bfa64822ad9b48fbd4d06c3e3a185b59._comment
new file mode 100644
index 0000000000..d44cb9ac9a
--- /dev/null
+++ b/doc/bugs/assistant_eats_all_CPU/comment_17_bfa64822ad9b48fbd4d06c3e3a185b59._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://id.koumbit.net/anarcat"
+ ip="2001:1928:1:9::1"
+ subject="comment 17"
+ date="2014-01-30T04:57:24Z"
+ content="""
+@joeyh - any other ideas? I still can't really use the assistant...
+"""]]
diff --git a/doc/bugs/assistant_on_windows_adding_remote_containing_linux_paths.mdwn b/doc/bugs/assistant_on_windows_adding_remote_containing_linux_paths.mdwn
new file mode 100644
index 0000000000..c6b6ee4821
--- /dev/null
+++ b/doc/bugs/assistant_on_windows_adding_remote_containing_linux_paths.mdwn
@@ -0,0 +1,23 @@
+### Please describe the problem.
+
+Internal Server Error
+
+internal error, /home/michele/assistannex is not absolute
+
+### What steps will reproduce the problem?
+
+create a transfer repository on a usb drive (from windows) merge it with a
+repository on linux, try to merge it on another target windows machine
+
+### What version of git-annex are you using? On what operating system?
+
+git-annex version 5.20140128-g29aea74
+
+> I'm not able to follow the steps to reproduce this, but I think
+> I see what the problem is. `isAbsolute` on windows does not think that
+> unix-style path is absolute. Such a path can appear in a remote of a git
+> repository, particularly if part of that repository was set up on a
+> non-Windows system. While the remote won't be usable on Windows with a
+> path like that, git-annex should not choke on the path either.
+> I have fixed the code to deal with this.
+> [[done]] --[[Joey]]
diff --git a/doc/bugs/can__39__t_get.mdwn b/doc/bugs/can__39__t_get.mdwn
new file mode 100644
index 0000000000..42a15e8b65
--- /dev/null
+++ b/doc/bugs/can__39__t_get.mdwn
@@ -0,0 +1,75 @@
+### Please describe the problem.
+
+
+### What steps will reproduce the problem?
+
+[[!format sh """
+$> git annex get 2read/ISNN2010__Tang.pdf
+git-annex: Cannot mix --all or --unused with file names.
+"""]]
+
+### What version of git-annex are you using? On what operating system?
+
+
+[[!format sh """
+$> apt-cache policy git-annex
+git-annex:
+ Installed: 5.20140116
+ Candidate: 5.20140116
+ Version table:
+ *** 5.20140116 0
+ 600 http://debian.lcs.mit.edu/debian/ sid/main amd64 Packages
+ 100 /var/lib/dpkg/status
+"""]]
+
+### 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
+
+$> git annex get 2read/ISNN2010__Tang.pdf
+git-annex: Cannot mix --all or --unused with file names.
+
+but seems to start fetching some load if I do not specify any path and just run 'git annex get'.
+
+There seems to be some screw up:
+
+I have plenty of objects under .git/annex/objects/ (seems largely from
+the directory above), nothing is now reported by unused (with obscure
+msg):
+
+$> du -scmL * 2>/dev/null | tail -1
+1 total
+
+$> du -scm .git/annex/objects
+334 .git/annex/objects
+334 total
+
+$> git annex dropunused all
+git-annex: Map.findMin: empty map has no minimal element
+
+Here is some portion of the history which lead to such a state (there
+was git annex unused somewhere before)
+
+25954 git annex move --unused --to onerussian.com_annex
+25955 git annex dropunused
+25956 git annex dropunused all
+25962 git annex unused
+25963 git log --stat -SSHA256E-s5639442--67691e57cb4d6c51afe838590ad265ba4bea9c291cf52d58ed24f05b70bf33bf.mp3
+25965 git log --stat -SSHA256E-s143042--b4012bf03ed0a387a9e714390efa75f1dd769162cca4c9b77e516732342be3f9.html
+25968 git annex move --unused --to onerussian.com_annex
+25969 git annex dropunused all
+25976 git annex unused
+25978 git br
+25980 git log --stat -Ss741707--7c215090893f1f0c994e2a9ad3088016676464bbad26768841dd08c07295a2fe.pdf.map
+25981 git annex unused
+25982 git annex fsck
+25983 git annex unused
+25984 git annex dropkey
+25985 git log --stat -SSHA256E-s14534131--20de680eedb3e1fb687c9b00c154d978333b61f4ea122c632bdb5bcdbb1553ff.pdf
+25986 git show de3ccae8304efbae4a7a8add49de638f64b821fc
+25991 git annex fsck
+
+# End of transcript or log.
+"""]]
diff --git a/doc/bugs/can__39__t_get/comment_1_ef32287828481c161bd913c9db9052a5._comment b/doc/bugs/can__39__t_get/comment_1_ef32287828481c161bd913c9db9052a5._comment
new file mode 100644
index 0000000000..6530ae3c80
--- /dev/null
+++ b/doc/bugs/can__39__t_get/comment_1_ef32287828481c161bd913c9db9052a5._comment
@@ -0,0 +1,27 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnx8kHW66N3BqmkVpgtXDlYMvr8TJ5VvfY"
+ nickname="Yaroslav"
+ subject="git annex fix starts fixing but then spits bulk of errors"
+ date="2014-01-18T05:42:15Z"
+ content="""
+probably related:
+
+```
+fix books/Мои первые книжки/PDF/Благинина Е.А. - Лодочки (Мои первые книжки) - 1962.pdf ok
+fix books/Мои первые книжки/PDF/Благинина Е.А. - Не мешайте мне трудиться (Мои первые книжки) - 1975.pdf fatal: This operation must be run in a work tree
+ok
+(Recording state in git...)
+
+git-annex: user error (xargs [\"-0\",\"git\",\"--git-dir=/home/yoh/annex/.git\",\"add\",\"--force\",\"--\"] exited 123)
+fatal: This operation must be run in a work tree
+failed
+(Recording state in git...)
+
+git-annex: user error (xargs [\"-0\",\"git\",\"--git-dir=/home/yoh/annex/.git\",\"add\",\"--force\",\"--\"] exited 123)
+fatal: This operation must be run in a work tree
+failed
+(Recording state in git...)
+
+....
+```
+"""]]
diff --git a/doc/bugs/can__39__t_get/comment_2_31fe400f4bac516a5c1101612cb06a54._comment b/doc/bugs/can__39__t_get/comment_2_31fe400f4bac516a5c1101612cb06a54._comment
new file mode 100644
index 0000000000..456bd0342d
--- /dev/null
+++ b/doc/bugs/can__39__t_get/comment_2_31fe400f4bac516a5c1101612cb06a54._comment
@@ -0,0 +1,32 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnx8kHW66N3BqmkVpgtXDlYMvr8TJ5VvfY"
+ nickname="Yaroslav"
+ subject="repair seems to be also confused"
+ date="2014-01-18T05:47:02Z"
+ content="""
+[[[
+$> git annex repair
+Running git fsck ...
+No problems found.
+fatal: '/home/yoh/annex/.git' is outside repository
+Had to delete the .git/annex/index file as it was corrupt.
+No data was lost.
+ok
+
+$> ls
+2enjoy/ 2read/ 2watch/ books/ hardware/ videos/
+2listen/ 2review/ abooks/ docs/ pics/
+
+$> git annex repair
+Running git fsck ...
+No problems found.
+fatal: '/home/yoh/annex/.git' is outside repository
+Had to delete the .git/annex/index file as it was corrupt.
+No data was lost.
+ok
+
+$> git annex get 2read/ISNN2010__Tang.pdf
+git-annex: Cannot mix --all or --unused with file names.
+
+]]]
+"""]]
diff --git a/doc/bugs/can__39__t_get/comment_3_87d123c04815d38abb92f967829c3a23._comment b/doc/bugs/can__39__t_get/comment_3_87d123c04815d38abb92f967829c3a23._comment
new file mode 100644
index 0000000000..b7a7f3bc46
--- /dev/null
+++ b/doc/bugs/can__39__t_get/comment_3_87d123c04815d38abb92f967829c3a23._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnx8kHW66N3BqmkVpgtXDlYMvr8TJ5VvfY"
+ nickname="Yaroslav"
+ subject="could it be part/reason of the problem"
+ date="2014-01-18T06:05:50Z"
+ content="""
+not sure how that happened... definitely not me consciously! ;-) some commands are complaining that \"You cannot run this command in a bare repository\" which I thought is BS since it is not BARE! but then looked into .git/config and it does have core.bare = True ... yikes!..
+
+This repository is also under assistant \"control\".
+
+changing to bare=False seems to start 'get'ing things, git annex repair doesn't produce obscure errors.
+
+git annex fix though now doesn't report any problems -- only 'ok', but none of those files mentioned 'ok' has a working symlink,,, but I guess that is a fluke after many upgrades -- just dropping everything locally and getting needed context after purging .git/annex/objects .
+
+So I guess issue is resolved by discovering that repository was set to 'bare' mode somehow although it was not and seemed like working but not quite
+"""]]
diff --git a/doc/bugs/can__39__t_get/comment_4_b99cff87dbe38f08f888200dfe7e2436._comment b/doc/bugs/can__39__t_get/comment_4_b99cff87dbe38f08f888200dfe7e2436._comment
new file mode 100644
index 0000000000..0d0422fd35
--- /dev/null
+++ b/doc/bugs/can__39__t_get/comment_4_b99cff87dbe38f08f888200dfe7e2436._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.43"
+ subject="comment 4"
+ date="2014-01-18T15:42:59Z"
+ content="""
+git-annex sets core.bare=true for direct mode, but it also then sets annex.direct=true and so does not treat it as a bare mode repository. If you had eg, manually tried to change annex.direct to false, and left it in bare mode, that would explain everything.
+
+> git annex fix though now doesn't report any problems -- only 'ok', but none of those files mentioned 'ok' has a working symlink
+
+That is completely normal behavior; git annex fix does not care if the content is locally present or not; it just checks that the symlinks would point to it if it were present.
+
+(Fixed the partial function in dropunused.)
+"""]]
diff --git a/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files.mdwn b/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files.mdwn
new file mode 100644
index 0000000000..0bd01056a4
--- /dev/null
+++ b/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files.mdwn
@@ -0,0 +1,73 @@
+### Please describe the problem.
+
+Fun one: I have a backup repository created with the assistant. For some reason it's a bare repository, not sure why. It makes my hard drive scream with pain.
+
+### What steps will reproduce the problem?
+
+When I tried `git annex copy --to backup`, I saw this:
+
+[[!format sh """
+[2014-01-29 23:46:03 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","show-ref","git-annex"]
+[2014-01-29 23:46:04 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","show-ref","--hash","refs/heads/g
+[2014-01-29 23:46:11 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..ac42
+[2014-01-29 23:46:12 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..9ab4
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..5795
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..8006
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..320e
+[2014-01-29 23:46:22 EST] chat: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","cat-file","--batch"]
+[2014-01-29 23:46:22 EST] read: git ["config","--null","--list"]
+[2014-01-29 23:46:22 EST] call: git ["--git-dir=/media/c7a29cf9-ad3e-42a8-8dd5-0f5618c218ee/mp3/.git","--work-tree=/med
+[2014-01-29 23:46:22 EST] read: git ["config","--null","--list"]
+[2014-01-29 23:46:22 EST] Detected bad bare repository with
+"""]]
+
+Then this stopped and my hard drive started scratching. It makes this horrible screeching sound because it's quite old, hence the bug title.
+
+It seems that this debug message tries to list all the objects in the filesystem, which in this case is quite large:
+
+[[!format haskell """
+fixBadBare :: Annex ()
+fixBadBare = whenM checkBadBare $ do
+ ks <- getKeysPresent
+ liftIO $ debugM "Init" $ unwords
+ [ "Detected bad bare repository with"
+ , show (length ks)
+ , "objects; fixing"
+ ]
+"""]]
+
+Maybe this could be skipped? It takes forever (7 minutes) to compute that length (21353 objects)...
+
+### What version of git-annex are you using? On what operating system?
+
+5.20140102-gd93f946, provided by joeyh as part of [[bugs/assistant_eats_all_CPU/]].
+
+### Please provide any additional information below.
+
+Here's the complete transcript of that copy:
+
+[[!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-01-29 23:46:03 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","show-ref","git-annex"]
+[2014-01-29 23:46:04 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","show-ref","--hash","refs/heads/g
+[2014-01-29 23:46:11 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..ac42
+[2014-01-29 23:46:12 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..9ab4
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..5795
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..8006
+[2014-01-29 23:46:22 EST] read: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","log","refs/heads/git-annex..320e
+[2014-01-29 23:46:22 EST] chat: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","cat-file","--batch"]
+[2014-01-29 23:46:22 EST] read: git ["config","--null","--list"]
+[2014-01-29 23:46:22 EST] call: git ["--git-dir=/media/c7a29cf9-ad3e-42a8-8dd5-0f5618c218ee/mp3/.git","--work-tree=/med
+[2014-01-29 23:46:22 EST] read: git ["config","--null","--list"]
+[2014-01-29 23:46:22 EST] Detected bad bare repository with 21353 objects; fixing
+[2014-01-29 23:53:06 EST] call: git ["--git-dir=/media/c7a29cf9-ad3e-42a8-8dd5-0f5618c218ee/mp3","config","core.bare","true"]
+[2014-01-29 23:53:06 EST] read: git ["config","--null","--list"]
+[2014-01-29 23:53:06 EST] chat: git ["--git-dir=/media/c7a29cf9-ad3e-42a8-8dd5-0f5618c218ee/mp3","cat-file","--batch"]
+[2014-01-29 23:57:22 EST] call: git ["--git-dir=/srv/mp3/.git","--work-tree=/srv/mp3","config","remote..annex-uuid","c32322fa-8873-4635-8d4c-1dc27977eb6f"]
+[2014-01-29 23:57:22 EST] read: git ["config","--null","--list"]
+# End of transcript or log.
+"""]]
+
+> [[done]] per my comment --[[Joey]]
diff --git a/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files/comment_1_523b80ad81ad49bddfb8855d12d5561d._comment b/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files/comment_1_523b80ad81ad49bddfb8855d12d5561d._comment
new file mode 100644
index 0000000000..a1d8532756
--- /dev/null
+++ b/doc/bugs/detected_bad_bare_repository_with___60__SCREECH__62___files/comment_1_523b80ad81ad49bddfb8855d12d5561d._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 1"
+ date="2014-01-30T18:33:22Z"
+ content="""
+To fix this problem, git-annex has to find all the keys in the repository. This is necessarily an expensive operation when the repository is that large. Printing out the count of them does not take any appreciable additional time.
+
+This is a one-time fix up. Once you let git-annex run and fix your repository, you should not be bothered by it again.
+"""]]
diff --git a/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup.mdwn b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup.mdwn
new file mode 100644
index 0000000000..f574e8b551
--- /dev/null
+++ b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup.mdwn
@@ -0,0 +1,47 @@
+Hi.
+
+trying to manage my collection of digital music files using git-annex. The collection (113 gigs of flac files ripped from my CDs) should be stored on my three different machines and updated on all of them, if I add or change a file on only one of the machines.
+
+### Please describe the problem.
+
+Added a new external USB disk for sneaker transfer via web app, yesterday.
+
+Now for no apparent reason, after startup/login, git-annex would start and quickly suck up all available RAM. This is on a fairly well equipped machine (16G physical RAM, i5-2400), yet "top" tells me that there is one git process that sucks up more than 20G and climbing. It looked like this:
+
+ git --git-dir=/home/user/Sync/Audio/.git --work-tree=/home/user/Sync/Audio -c core.bare=false log refs/heads git-annex..13d365f16ffdb5a393f66362b840d3f21bb4c59c --oneline -n1
+
+The computer then slows down, grinds to halt, becomes unresponsive and it's difficult to even login on the console.
+
+Then, the OOM killer kicks in and kicks the git process, but git-annex quickly starts another which does the same.
+
+### What steps will reproduce the problem?
+
+I don't know what caused it. The symptoms remained after a reboot, "git annex watch --stop" didn't help either, since I'm a dumb web app user, I'm not sure if that's the right command to use anyway.
+
+For now, I have removed git-annex from the system.
+
+### What version of git-annex are you using? On what operating system?
+
+Last installed version: git-annex 5.20140127.1 on Ubuntu 13.10, amd64.
+
+### Please provide any additional information below.
+
+I'm fairly unsure where to look for the cause and what logs to provide you with to help fix this. Just guessing that it could be a symptom, but the daemon.log is full of entries like this:
+
+[[!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
+
+("race detected",ca2cbdb84bcbd4aab895284b16fc72f693fbba90,[4a2e7c1d7d286a4da9e816b20368ce2f9b4177c4],"committing",(ca2cbdb84bcbd4aab895284b16fc72f693fbba90,[ca2cbdb84bcbd4aab895284b16fc72f693fbba90]))
+(Recording state in git...)
+("race detected",28c835634e65ced0e532c1a0e4f34dd0344193bc,[19597be0f49fb859fafa51e006459d5a95e3d005],"committing",(28c835634e65ced0e532c1a0e4f34dd0344193bc,[28c835634e65ced0e532c1a0e4f34dd0344193bc]))
+(Recording state in git...)
+("race detected",1f2b06c7001be38bd9595eb2205c91454597edaa,[398660279436246a698d6bd55eb06998999ed64f],"committing",(1f2b06c7001be38bd9595eb2205c91454597edaa,[1f2b06c7001be38bd9595eb2205c91454597edaa]))
+(Recording state in git...)
+("race detected",4c1510c3db41ff400526d5753c03bddc48f5c37e,[1989177cf24ec9151058ed99f05117e48c239001],"committing",(4c1510c3db41ff400526d5753c03bddc48f5c37e,[4c1510c3db41ff400526d5753c03bddc48f5c37e]))
+(Recording state in git...)
+("race detected",b82f41fcbf24c43fe9f1f9d6fb54ba5ef9ff8de0,[799e4434447b18be63bd097120e1fbf56eac48ce],"committing",(b82f41fcbf24c43fe9f1f9d6fb54ba5ef9ff8de0,[b82f41fcbf24c43fe9f1f9d6fb54ba5ef9ff8de0]))
+(Recording state in git...)
+
+# End of transcript or log.
+"""]]
diff --git a/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_1_b550f292359b44977481bf69abad4012._comment b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_1_b550f292359b44977481bf69abad4012._comment
new file mode 100644
index 0000000000..662141d64a
--- /dev/null
+++ b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_1_b550f292359b44977481bf69abad4012._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkVnM7Ol2kr_jfLg6h_oXpmNdxWHIiL9mk"
+ nickname="Hanno"
+ subject="comment 1"
+ date="2014-01-30T11:18:15Z"
+ content="""
+In case it helps:
+
+ $ grep \"race detected\" daemon.log.5 | wc -l
+ 234986
+
+
+
+"""]]
diff --git a/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_2_76e6c1d4db27bcc1767ba34e13e8211c._comment b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_2_76e6c1d4db27bcc1767ba34e13e8211c._comment
new file mode 100644
index 0000000000..dacaac9421
--- /dev/null
+++ b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_2_76e6c1d4db27bcc1767ba34e13e8211c._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 2"
+ date="2014-01-30T17:39:47Z"
+ content="""
+How many files are in the repository?
+"""]]
diff --git a/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_3_14007c8e927b75c5706e80cc4242fae4._comment b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_3_14007c8e927b75c5706e80cc4242fae4._comment
new file mode 100644
index 0000000000..90101155d5
--- /dev/null
+++ b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_3_14007c8e927b75c5706e80cc4242fae4._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="Hanno"
+ ip="85.183.3.94"
+ subject="comment 3"
+ date="2014-01-31T10:39:47Z"
+ content="""
+The folder contains a bit more than 15000 files (counted with find -type f)
+"""]]
diff --git a/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_4_f3266b74517b421e5310e67818fe3969._comment b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_4_f3266b74517b421e5310e67818fe3969._comment
new file mode 100644
index 0000000000..faaa7ed09a
--- /dev/null
+++ b/doc/bugs/git-annex_sucking_up_all_available_RAM_after_startup/comment_4_f3266b74517b421e5310e67818fe3969._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkVnM7Ol2kr_jfLg6h_oXpmNdxWHIiL9mk"
+ nickname="Hanno"
+ subject="comment 4"
+ date="2014-01-31T23:17:49Z"
+ content="""
+I have no idea if it is related to this problem, but allow me to add that the \"Consistency check\" (that the web app specifically recommended me to activate) makes my computers unreasonably slow immediately after each bootup. This is both at the fairly fast computer at the office and the ok-ish old laptop at home.
+
+Also, the check will kick in and suck up the systems responsiveness right after connecting the external USB sneaker disk, making any regular file transfer to the disk extremely slow (more than once I was stung because I just wanted to quickly move a bigger file to the disk and walk home at the end of an office day but git-annex would go into its check after mounting).
+
+Thanks!
+"""]]
diff --git a/doc/bugs/git-annex_webapp_command_not_found/comment_3_f593752a0c5c60daaacca46ced5ac5d8._comment b/doc/bugs/git-annex_webapp_command_not_found/comment_3_f593752a0c5c60daaacca46ced5ac5d8._comment
new file mode 100644
index 0000000000..531714d5c1
--- /dev/null
+++ b/doc/bugs/git-annex_webapp_command_not_found/comment_3_f593752a0c5c60daaacca46ced5ac5d8._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk4_47QIHYfGlI9aL04LXxOczcYABmmIfA"
+ nickname="Mike"
+ subject="On Opensuse 13.1 - I was able to run git-annex-webapp once. "
+ date="2014-02-01T15:34:50Z"
+ content="""
+As soon as I removed my single repository it never loaded again. I have re-booted. re-installed. I have the package installed it tries to load but doesn't. I have the stand-alone installed it does nothing. Only if I try to execute webapp as superuser does it launch the browser but doesn't execute properly. comes up to some url file://??? when it was working properly i noticed it was opening to locahost url 127.0.0.1/something
+
+Still seems to be running on my desktop machine though. But i did not try to remove the repository from that machine because git-annex does not provide a way to remove repository without actually deleting the files. Evidently Disable and Delete do exactly the same thing.
+
+Any ideas? thanks. Mike
+"""]]
diff --git a/doc/bugs/git-annex_webapp_command_not_found/comment_4_e4ef964274e74cb4a39dc8ecac8ceade._comment b/doc/bugs/git-annex_webapp_command_not_found/comment_4_e4ef964274e74cb4a39dc8ecac8ceade._comment
new file mode 100644
index 0000000000..bc804d98a7
--- /dev/null
+++ b/doc/bugs/git-annex_webapp_command_not_found/comment_4_e4ef964274e74cb4a39dc8ecac8ceade._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk4_47QIHYfGlI9aL04LXxOczcYABmmIfA"
+ nickname="Mike"
+ subject="On Opensuse 13.1 - I was able to run git-annex-webapp once. "
+ date="2014-02-01T15:35:10Z"
+ content="""
+As soon as I removed my single repository it never loaded again. I have re-booted. re-installed. I have the package installed it tries to load but doesn't. I have the stand-alone installed it does nothing. Only if I try to execute webapp as superuser does it launch the browser but doesn't execute properly. comes up to some url file://??? when it was working properly i noticed it was opening to locahost url 127.0.0.1/something
+
+Still seems to be running on my desktop machine though. But i did not try to remove the repository from that machine because git-annex does not provide a way to remove repository without actually deleting the files. Evidently Disable and Delete do exactly the same thing.
+
+Any ideas? thanks. Mike
+"""]]
diff --git a/doc/bugs/ran_once_then_stopped_running_opensuse_13.1.mdwn b/doc/bugs/ran_once_then_stopped_running_opensuse_13.1.mdwn
new file mode 100644
index 0000000000..922b083472
--- /dev/null
+++ b/doc/bugs/ran_once_then_stopped_running_opensuse_13.1.mdwn
@@ -0,0 +1,12 @@
+Installed stand-alone tarball amd64.
+I was able to launch webapp. (on laptop)
+Created a repository to local home directory.
+Then ceated another repository to invite local desktop pc.(this one had all the files i wanted to sync)
+Went to dektop and accepted invitation. But both machines never stopped synching? and nothing really happened.
+so I removed repository on laptop to start fresh.
+But now webapp does nothing. I removed and re-installed a few times but still nothing.
+Only as superuser will the webapp attempt to load but fails because it is super user running.
+As far as version of git-annex... it prompted to upgrade and i think i saw a 5 in there somewhere.
+
+and since it won't load anymore i guess there is no log.
+
diff --git a/doc/bugs/ran_once_then_stopped_running_opensuse_13.1/comment_1_a9daf9e8f968b32f25e236f53ea4b845._comment b/doc/bugs/ran_once_then_stopped_running_opensuse_13.1/comment_1_a9daf9e8f968b32f25e236f53ea4b845._comment
new file mode 100644
index 0000000000..604da40227
--- /dev/null
+++ b/doc/bugs/ran_once_then_stopped_running_opensuse_13.1/comment_1_a9daf9e8f968b32f25e236f53ea4b845._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T19:14:47Z"
+ content="""
+There's a bit of a dearth of information here. I think I need to know:
+
+* What the version is (output of `git annex version`)
+
+* What happens when you run `git annex webapp` (\"does nothing\" is very vague. Does it sit there forever without returning to the prompt? Print an error message? Open a web browser that's not usable somehow?)
+
+You might take a look at the file `~/.config/git-annex/autostart` and remove any repository you deleted from there, although normally git-annex will ignore entries that no longer exist.
+"""]]
diff --git a/doc/bugs/sync_--content_tries_to_copy_content_to_metadata_only_repos.mdwn b/doc/bugs/sync_--content_tries_to_copy_content_to_metadata_only_repos.mdwn
new file mode 100644
index 0000000000..4714eac7a0
--- /dev/null
+++ b/doc/bugs/sync_--content_tries_to_copy_content_to_metadata_only_repos.mdwn
@@ -0,0 +1,34 @@
+### Please describe the problem.
+
+
+### What steps will reproduce the problem?
+
+git annex sync --content
+
+
+### What version of git-annex are you using? On what operating system?
+
+Mac OSX Maverics
+
+git-annex version: 5.20140127
+build flags: Assistant Webapp Pairing Testsuite S3 WebDAV FsEvents XMPP DNS Feeds Quvi TDFA CryptoHash
+key/value backends: SHA256E SHA1E SHA512E SHA224E SHA384E SKEIN256E SKEIN512E SHA256 SHA1 SHA512 SHA224 SHA384 SKEIN256 SKEIN512 WORM URL
+
+### Please provide any additional information below.
+
+[[!format sh """
+copy Books/Paperless - Agile Bits Edition/Paperless Video/5-4 PDFpen for iPad.m4v (to origin...)
+FATAL: suspicious characters loitering about 'git-annex-shell 'recvkey' '/~/users/akraut/annex-home' 'SHA256E-s98445427--5fb5fd6e082eec4a805261764ef982aa8f12d76e07e86a6abb05e7675762ac49.m4v' '--' 'remoteuuid=03ac7aa9-d14c-4b60-adae-02e4a5ec0fa8' 'direct=' 'associatedfile=Books/Paperless - Agile Bits Edition/Paperless Video/5-4 PDFpen for iPad.m4v' '--' dummy rsync --server -v --inplace .'
+rsync: connection unexpectedly closed (0 bytes received so far) [sender]
+rsync error: the --max-delete limit stopped deletions (code 25) at /SourceCache/rsync/rsync-42/rsync/io.c(452) [sender=2.6.9]
+
+ rsync failed -- run git annex again to resume file transfer
+failed
+"""]]
+
+> From the error message, I can see that your origin repository
+> has an annex.uuid set (to "03ac7aa9-d14c-4b60-adae-02e4a5ec0fa8").
+> So, I assume that, if you don't want git-annex sync to use it,
+> you must have remote.origin.annex-ignore set to true. So, I think I fixed
+> this a day or two ago when I made sync --content honor the annex-ignore
+> setting. [[done]] --[[Joey]]
diff --git a/doc/bugs/test_failures_on_window_for_5.20131118.mdwn b/doc/bugs/test_failures_on_window_for_5.20131118.mdwn
index 490bdf2c83..319eae4f1c 100644
--- a/doc/bugs/test_failures_on_window_for_5.20131118.mdwn
+++ b/doc/bugs/test_failures_on_window_for_5.20131118.mdwn
@@ -18,3 +18,5 @@ windows XP, NTFS = 1 FAIL
windows 7, NTFS = 2 FAILs
see attachment for full log of git annex test output
+
+> Reproduced and [[fixed|done]]. --[[Joey]]
diff --git a/doc/bugs/tweaks_to_directory_special_remote_doco.mdwn b/doc/bugs/tweaks_to_directory_special_remote_doco.mdwn
new file mode 100644
index 0000000000..10861b45fb
--- /dev/null
+++ b/doc/bugs/tweaks_to_directory_special_remote_doco.mdwn
@@ -0,0 +1,80 @@
+### Please describe the problem.
+
+I found the discussion in [directory](/special_remotes/directory) quite confusing until I looked at it the right way. Some tweaking of the documentation might help.
+
+### What steps will reproduce the problem?
+
+Possible method - get a newbie to read the page.
+
+### What version of git-annex are you using? On what operating system?
+
+n/a
+
+### Please provide any additional information below.
+
+Below is an untested patch that I think would make the documentation more helpful to me on a first reading.
+
+ Tweaks to doc/special_remotes/directory.mdwn
+
+ * document the 'directory' option (!)
+ * try to make it clearer what is different about this remote,
+ including giving an example of how the directory structure looks.
+ * grammar fix in opening paragraph
+
+ ---
+ doc/special_remotes/directory.mdwn | 16 +++++++++++++++-
+ 1 file changed, 15 insertions(+), 1 deletion(-)
+
+ diff --git a/doc/special_remotes/directory.mdwn b/doc/special_remotes/directory.mdwn
+ index 4d72e8b..7f076b3 100644
+ --- a/doc/special_remotes/directory.mdwn
+ +++ b/doc/special_remotes/directory.mdwn
+ @@ -1,10 +1,12 @@
+ This special remote type stores file contents in directory.
+
+ One use case for this would be if you have a removable drive that
+ -you want to use it to sneakernet files between systems (possibly with
+ +you want to use to sneakernet files between systems (possibly with
+ \[[encrypted|encryption]] contents). Just set up both systems to use
+ the drive's mountpoint as a directory remote.
+
+ +Note that directory remotes have a special directory structure
+ +(by design, the same as the \[[rsync|rsync]] remote).
+ If you just want two copies of your repository with the files "visible"
+ in the tree in both, the directory special remote is not what you want.
+ Instead, you should use a regular `git clone` of your git-annex repository.
+ @@ -14,6 +16,8 @@ Instead, you should use a regular `git clone` of your git-annex repository.
+ These parameters can be passed to `git annex initremote` to configure the
+ remote:
+
+ +* `directory` - The path to directory in which the remote resides
+ +
+ * `encryption` - One of "none", "hybrid", "shared", or "pubkey".
+ See \[[encryption]].
+
+ @@ -31,3 +35,13 @@ Setup example:
+
+ # git annex initremote usbdrive type=directory directory=/media/usbdrive/ encryption=none
+ # git annex describe usbdrive "usb drive on /media/usbdrive/"
+ +
+ +Usage example:
+ + # git annex copy mycoolfile.mp4 --to usbdrive
+ + # ls -aF /media/usbdrive
+ + ./ ../ 42b/ .git/ tmp/
+ + # git annex whereis mycoolfile.mp4
+ + whereis mycoolfile.mp4 (2 copies)
+ + 320053d5-892f-46d2-89f0-d6e9d09e6398 -- here
+ + 6747a48b-fad2-41a7-9033-8d8daa35c5f8 -- usbdrive
+ + ok
+ --
+ 1.8.5.2
+
+
+
+# End of transcript or log.
+
+> Largely applied (except example at the end). I agree these
+> changes make it much clearer, especially adding the missing documentation
+> of the directory parameter. So, [[done]]. Note that this website is a
+> wiki and users like you are welcome to edit pages directly to improve the
+> documentation. --[[Joey]]
diff --git a/doc/copies.mdwn b/doc/copies.mdwn
index 93cbd8ea80..205d2d5b12 100644
--- a/doc/copies.mdwn
+++ b/doc/copies.mdwn
@@ -6,8 +6,8 @@ command. So, git-annex can be configured to try
to keep N copies of a file's content available across all repositories.
(Although [[untrusted_repositories|trust]] don't count toward this total.)
-By default, N is 1; it is configured by annex.numcopies. This default
-can be overridden on a per-file-type basis by the annex.numcopies
+By default, N is 1; it is configured by running `git annex numcopies N`.
+This default can be overridden on a per-file-type basis by the annex.numcopies
setting in `.gitattributes` files. The --numcopies switch allows
temporarily using a different value.
@@ -30,9 +30,3 @@ refuse to do so.
With N=2, in order to drop the file content from Laptop, it would need access
to both USB and Server.
-
-Note that different repositories can be configured with different values of
-N. So just because Laptop has N=2, this does not prevent the number of
-copies falling to 1, when USB and Server have N=1. To avoid this,
-configure it in `.gitattributes`, which is shared between repositories
-using git.
diff --git a/doc/design/assistant/blog/day_45__long_polling/comment_5_b3e41ba77f21e93a4e086483793bf5ce._comment b/doc/design/assistant/blog/day_45__long_polling/comment_5_b3e41ba77f21e93a4e086483793bf5ce._comment
new file mode 100644
index 0000000000..d9886216c9
--- /dev/null
+++ b/doc/design/assistant/blog/day_45__long_polling/comment_5_b3e41ba77f21e93a4e086483793bf5ce._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmz8d2M0lQDYWLSbDQSjYRHfrQkWKgPu60"
+ nickname="Alex"
+ subject="re: long polling"
+ date="2014-01-17T20:27:23Z"
+ content="""
+After poking through git-annex, I had the same realization. I hadn't realized that Yesod (or perhaps more accurately, Warp) is asynchronous above the Application level. I had feared I'd need to write some WAI middleware to accommodate the blocking nature of long polling requests. In retrospect it seems kind of silly: what kind of high-performance webserver doesn't handle requests concurrently?
+
+I do still think there's a pattern worth encapsulating, even if it won't be long until WebSockets and SSE are widespread enough to be developed against without fallbacks.
+"""]]
diff --git a/doc/design/assistant/polls/prioritizing_special_remotes.mdwn b/doc/design/assistant/polls/prioritizing_special_remotes.mdwn
index 505c6e3a03..d934f74fc4 100644
--- a/doc/design/assistant/polls/prioritizing_special_remotes.mdwn
+++ b/doc/design/assistant/polls/prioritizing_special_remotes.mdwn
@@ -6,7 +6,7 @@ locally paired systems, and remote servers with rsync.
Help me prioritize my work: What special remote would you most like
to use with the git-annex assistant?
-[[!poll open=yes 16 "Amazon S3 (done)" 12 "Amazon Glacier (done)" 9 "Box.com (done)" 71 "My phone (or MP3 player)" 23 "Tahoe-LAFS" 10 "OpenStack SWIFT" 31 "Google Drive"]]
+[[!poll open=yes 16 "Amazon S3 (done)" 12 "Amazon Glacier (done)" 9 "Box.com (done)" 71 "My phone (or MP3 player)" 24 "Tahoe-LAFS" 10 "OpenStack SWIFT" 31 "Google Drive"]]
This poll is ordered with the options I consider easiest to build
listed first. Mostly because git-annex already supports them and they
diff --git a/doc/design/assistant/telehash.mdwn b/doc/design/assistant/telehash.mdwn
index 9e1d6f613d..ad692a4d12 100644
--- a/doc/design/assistant/telehash.mdwn
+++ b/doc/design/assistant/telehash.mdwn
@@ -33,7 +33,7 @@ git-annex (assistant) repositories.
* XMPP pairing can also be used for telehash address discovery. (Note that
MITM attacks are possible.) Is it worth keeping XMPP in git-annex just
for this?
-* Telehash addresses of repoitories can be communicated out of band (eg,
+* Telehash addresses of repositories can be communicated out of band (eg,
via an OTR session or gpg signed mail), and pasted into the webapp to
initiate a repository pairing that then proceeds entirely over telehash.
Once both sides do this, the pairing can proceed automatically.
@@ -58,3 +58,33 @@ This might turn out to be easy to split off from git-annex, so `git pull`
and `git push` can be used at the command line to access telehash remotes.
Allows using general git entirely decentralized and with end-to-end
encryption.
+
+## separate daemon?
+
+A `gathd` could contain all the telehash specific code, and git-annex
+communicate with it via a local socket.
+
+Advantages:
+
+* `git annex sync` could also use the running daemon
+* `git-remote-telehash` could use the running daemon
+* c-telehash might end up linked to openssl, which has licence combination
+ problems with git-annex. A separate process not using git-annex's code
+ would avoid this.
+* Allows the daemon to be written in some other language if necessary
+ (for example, if c-telehash development stalls and the nodejs version is
+ already usable)
+* Potentially could be generalized to handle other similar protocols.
+ Or even the xmpp code moved into it. There could even be git-annex native
+ exchange protocols implemented in such a daemon to allow SSH-less
+ transfers.
+* Security holes in telehash would not need to compromise the entire
+ git-annex. gathd could be sandboxed in one way or another.
+
+Disadvantages:
+
+* Adds a memcopy when large files are being transferred through telehash.
+ Unlikely to be a bottleneck.
+* Adds some complexity.
+* What IPC to use on Windows? Might have to make git-annex communicate
+ with it over its stdin/stdout there.
diff --git a/doc/design/external_special_remote_protocol/comment_12_e3029c65d34f78272bc11961ebfd8237._comment b/doc/design/external_special_remote_protocol/comment_12_e3029c65d34f78272bc11961ebfd8237._comment
new file mode 100644
index 0000000000..e8d0dcfe8e
--- /dev/null
+++ b/doc/design/external_special_remote_protocol/comment_12_e3029c65d34f78272bc11961ebfd8237._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm_YXzEdPHzbSGVwtmTR7g1BqDtTnIBB5s"
+ nickname="Matthias"
+ subject="Chunk it"
+ date="2014-01-20T16:22:09Z"
+ content="""
+> TODO: stream the file up/down the pipe, rather than using a temp file
+
+You might want to use chunked transfer, i.e. a series of \"EXPECT 65536\" followed by that many bytes of binary data and an EOF marker (EXPECT-END or EXPECT 0), instead of escaping three characters (newline, NUL, and the escape prefix) and the additional unnecessary tedious per-character processing that would require.
+"""]]
diff --git a/doc/design/preferred_content.mdwn b/doc/design/preferred_content.mdwn
new file mode 100644
index 0000000000..3972b8b583
--- /dev/null
+++ b/doc/design/preferred_content.mdwn
@@ -0,0 +1,21 @@
+The [[preferred_content]] expressions didn't have a design document, but
+it's a small non-turing complete DSL for expressing which objects a
+repository prefers to contain.
+
+One thing that needs to be written down though is the stability analysis
+that must be done of preferred content expressions.
+
+It's important that when a set of repositories all look at one-another's
+preferred content expressions, and copy/move/drop objects to satisfy them,
+they end up at a steady state. So, a given preferred content expression
+should ideally evaluate to the same answer for each key, from the
+perspective of each repository.
+
+The best way to ensure that is the case is to only use terms in preferred
+content expressions that rely on state that is shared between all
+repositories. So, state in the git-annex branch, or the master branch
+(assuming all repositories have master checked out).
+
+Since git is eventually consistent, there might be disagreements about
+which object belongs where, but once consistency is reached, things will
+settle down.
diff --git a/doc/design/roadmap.mdwn b/doc/design/roadmap.mdwn
index 3a28c271e5..8571188006 100644
--- a/doc/design/roadmap.mdwn
+++ b/doc/design/roadmap.mdwn
@@ -8,8 +8,8 @@ Now in the
* Month 2 [[!traillink assistant/disaster_recovery]]
* Month 3 user-driven features and polishing [[todo/direct_mode_guard]] [[assistant/upgrading]]
* Month 4 [[Windows_webapp|assistant/Windows]], Linux arm, [[todo/support_for_writing_external_special_remotes]]
-* **Month 5 user-driven features and polishing**
-* Month 6 get [[assistant/Android]] and Windows out of beta
+* Month 5 user-driven features and polishing
+* **Month 6 get [[assistant/Android]] and Windows out of beta**
* Month 7 user-driven features and polishing
* Month 8 [[!traillink assistant/telehash]]
* Month 9 [[!traillink assistant/gpgkeys]] [[!traillink assistant/sshpassword]]
diff --git a/doc/devblog/day_100__git-annex_sync_--content.mdwn b/doc/devblog/day_100__git-annex_sync_--content.mdwn
new file mode 100644
index 0000000000..f35fbd330e
--- /dev/null
+++ b/doc/devblog/day_100__git-annex_sync_--content.mdwn
@@ -0,0 +1,4 @@
+Spent the day building this new feature, which makes `git annex sync --content`
+do the same synchronization of file contents (to satisfy preferred content
+settings) that the assistant does. The result has not been tested a lot
+yet, but seems to work well.
diff --git a/doc/devblog/day_101__old_mistakes.mdwn b/doc/devblog/day_101__old_mistakes.mdwn
new file mode 100644
index 0000000000..4a37416dc4
--- /dev/null
+++ b/doc/devblog/day_101__old_mistakes.mdwn
@@ -0,0 +1,23 @@
+In order to remove some hackishness in `git annex sync --content`, I
+finally fixed a bad design decision I made back at the very beginning
+(before I really knew haskell) when I built the command seek code, which
+had led to a kind of inversion of control. This took most of a night, but
+it made a lot of code in git-annex clearer, and it makes the command
+seeking code much more flexible in what it can do. Some of the oldest, and
+worst code in git-annex was removed in the process.
+
+Also, I've been reworking the numcopies configuration, to allow for a
+[[todo/preferred_content_numcopies_check]]. That will let the assistant,
+as well as `git annex sync --content` proactively make copies when
+needed in order to satisfy numcopies.
+
+As part of this, `git config annex.numcopies` is deprecated, and there's a
+new `git annex numcopies N` command that sets the numcopies value that will
+be used by any clone of a repository.
+
+I got the preferred content checking of numcopies working too. However,
+I am unsure if checking for per-file .gitattributes annex.numcopies
+settings will make preferred content expressions be, so I have left
+that out for now.
+
+Today's work was sponsored by Josh Taylor.
diff --git a/doc/devblog/day_101__old_mistakes/comment_1_2c6e991efde3296450189b2821f2ccc3._comment b/doc/devblog/day_101__old_mistakes/comment_1_2c6e991efde3296450189b2821f2ccc3._comment
new file mode 100644
index 0000000000..93fb84aa3d
--- /dev/null
+++ b/doc/devblog/day_101__old_mistakes/comment_1_2c6e991efde3296450189b2821f2ccc3._comment
@@ -0,0 +1,17 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawl9sYlePmv1xK-VvjBdN-5doOa_Xw-jH4U"
+ nickname="Richard"
+ subject="comment 1"
+ date="2014-01-21T00:20:34Z"
+ content="""
+Some more details on
+
+* when the old mechanism will stop working
+* how you will ensure interoperability in repo sets which have different versions installed in different places
+* which option weighs more heavily
+
+would be appreciated.
+
+
+Richard
+"""]]
diff --git a/doc/devblog/day_101__old_mistakes/comment_2_524690d69056737dd296e4f7626737d2._comment b/doc/devblog/day_101__old_mistakes/comment_2_524690d69056737dd296e4f7626737d2._comment
new file mode 100644
index 0000000000..9f7ebecf18
--- /dev/null
+++ b/doc/devblog/day_101__old_mistakes/comment_2_524690d69056737dd296e4f7626737d2._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.249"
+ subject="comment 2"
+ date="2014-01-21T02:23:00Z"
+ content="""
+I don't plan to remove .git/config annex.numcopies support. It is 5 lines of code.
+
+A fundamental problem with the .git/config annex.numcopies setting is that it can be inconsistently set between repositories. Therefore, there is no worse potential with interoperability if you use differing versions of git-annex that support and do not support the new global numcopies setting. If this was a concern though, you can use .gitattributes to set annex.numcopies for *, which all recent versions of git-annex support.
+
+The old git/config annex.numcopies setting is overridden as soon as you use `git annex numcopies`. In turn `git annex numcopies` is overridden by any relevant .gitattributes annex.numcopies setting. This is documented on the man page.
+"""]]
diff --git a/doc/devblog/day_102__cleanups.mdwn b/doc/devblog/day_102__cleanups.mdwn
new file mode 100644
index 0000000000..27a1badeaf
--- /dev/null
+++ b/doc/devblog/day_102__cleanups.mdwn
@@ -0,0 +1,10 @@
+Worked on cleaning up and reorganizing all the code that handles numcopies
+settings. Much nicer now. Fixed some bugs.
+
+As expected, making the preferred content numcopies check look at
+.gitattributes slows it down significantly. So, exposed both the slow and
+accurate check and a faster version that ignores .gitattributes.
+
+Also worked on the test suite, removing dependencies between tests.
+This will let tasty-rerun be used later to run only previously failing
+tests.
diff --git a/doc/devblog/day_103__unused.mdwn b/doc/devblog/day_103__unused.mdwn
new file mode 100644
index 0000000000..affb4e532e
--- /dev/null
+++ b/doc/devblog/day_103__unused.mdwn
@@ -0,0 +1,34 @@
+A big missing peice of the assistant is doing something about the content
+of old versions of files, and deleted files. In direct mode, editing or
+deleting a file necessarily loses its content from the local repository,
+but the content can still hang around in other repositories. So, the
+assistant needs to do something about that to avoid eating up disk space
+unnecessarily.
+
+I built on recent work, that lets preferred content expressions be matched
+against keys with no associated file. This means that I can run unused keys
+through all the machinery in the assistant that handles file transfers, and
+they'll end being moved to whatever repository wants them. To control which
+repositories do want to retain unused files, and which not, I added a
+`unused` keyword to preferred content expressions. Client repositories and
+transfer repositories do not want to retain unused files, but backup etc
+repos do.
+
+One nice thing about this `unused` preferred content implementation is that
+it doesn't slow down normal matching of preferred content expressions at
+all. Can you guess why not? See [[!commit 4b55afe9e92c045d72b78747021e15e8dfc16416]]
+
+So, the assistant will run `git annex unused` on a daily basis, and
+cause unused files to flow to repositories that want them. But what if no
+repositories do? To guard against filling up the local disk, there's
+a `annex.expireunused` configuration setting, that can cause old unused
+files to be deleted by the assistant after a number of days.
+
+I made the assistant check if there seem to be a lot of unused files piling
+up. (1000+, or 10% of disk used by them, or more space taken by unused files
+than is free.) If so, it'll pop up an alert to nudge the user to configure
+annex.expireunused.
+
+Still need to build the UI to configure that, and test all of this.
+
+Today's work was sponsored by Samuel Tardieu.
diff --git a/doc/devblog/day_104__unused_II.mdwn b/doc/devblog/day_104__unused_II.mdwn
new file mode 100644
index 0000000000..7dc01c5fdd
--- /dev/null
+++ b/doc/devblog/day_104__unused_II.mdwn
@@ -0,0 +1,7 @@
+Built the UI to manage unused files.
+
+[[!img assistant/unused.png]]
+
+Testing yesterday's work, I found several problems that prevented the
+assistant from moving unused files around, and fixed them. It seems to be
+working pretty well now.
diff --git a/doc/devblog/day_104__unused_II/comment_1_a693a56123497a39c30cbd35b8e35bce._comment b/doc/devblog/day_104__unused_II/comment_1_a693a56123497a39c30cbd35b8e35bce._comment
new file mode 100644
index 0000000000..a4893f63ab
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_1_a693a56123497a39c30cbd35b8e35bce._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm7AuSfii_tCkLyspL6Mr0ATlO6OxLNYOo"
+ nickname="Georg"
+ subject="state of windows"
+ date="2014-01-28T10:29:41Z"
+ content="""
+Any idea when this stuff will end in the windows build? I am currently fiddling around with git-annex on windows (btw: great work on that so far!) and the unused files config would be highly valueable to me, since I want to mostly use it to push files out to my server from my work machine or my windows tablet, while preventing to clog up too much space. And since I am lazy, I would love to leave the house keeping to git-annex ;)
+
+An additional question on the windows build: which of the backends can actually make use of windows proxy settings? I guess if webdav was in the list of supported backends, it would work fine, since it is only http, but since it is missing, which of the others would work through just a standard configured squid proxy? For my work machine this is the only way to reach the outside world, doing https to my web server.
+"""]]
diff --git a/doc/devblog/day_104__unused_II/comment_2_9833fb9daa50bc838cc46ca2f6c16580._comment b/doc/devblog/day_104__unused_II/comment_2_9833fb9daa50bc838cc46ca2f6c16580._comment
new file mode 100644
index 0000000000..eeaef05bf2
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_2_9833fb9daa50bc838cc46ca2f6c16580._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 2"
+ date="2014-01-28T20:58:32Z"
+ content="""
+AFAICS, the Windows build does include WebDAV support.
+
+I don't know about Windows proxy stuff. If it requires the program to do something, git-annex almost certianly does not do it.
+"""]]
diff --git a/doc/devblog/day_104__unused_II/comment_3_873a882ec1ddc3be473473cb224a9040._comment b/doc/devblog/day_104__unused_II/comment_3_873a882ec1ddc3be473473cb224a9040._comment
new file mode 100644
index 0000000000..96b870627f
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_3_873a882ec1ddc3be473473cb224a9040._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm7AuSfii_tCkLyspL6Mr0ATlO6OxLNYOo"
+ nickname="Georg"
+ subject="comment 3"
+ date="2014-01-29T08:22:13Z"
+ content="""
+well, at least in the assistant there is no selection to add a webdav repository - only box.com, rsync.net, S3, remote ssh, and the archives on glazier or internet archive. It is the binary version from 16th this month. I thought it was still excluded due to the compiler crashes you wrote about, because it doesn't show up in the webapp as option. I was scratching my head anyway about that windows build, because there was nothing about setting up encryption in the configuration in the webapp.
+
+Proxy support on Windows is kinda like proxy support on linux when you pull the proxy from gnome settings - just it is pulled from the registry. I don't know how Haskell HTTP client libraries handle it, only know it for Python - there the client libraries usually grab proxy settings automatically from the system configuration.
+
+Another option which could work for me to get through our firewall at work would be ssh - I can use ssh with proxy commands to reach the outside, but didn't yet find the used ssh configs on the windows git-annex installation - it doesn't use the one in ~/.ssh, I added my proxy commands there, but that isn't used.
+"""]]
diff --git a/doc/devblog/day_104__unused_II/comment_4_5ef1bb4d69cf7206f7ca0e542abad6bd._comment b/doc/devblog/day_104__unused_II/comment_4_5ef1bb4d69cf7206f7ca0e542abad6bd._comment
new file mode 100644
index 0000000000..adf3293ffe
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_4_5ef1bb4d69cf7206f7ca0e542abad6bd._comment
@@ -0,0 +1,13 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm7AuSfii_tCkLyspL6Mr0ATlO6OxLNYOo"
+ nickname="Georg"
+ subject="comment 4"
+ date="2014-01-29T08:26:19Z"
+ content="""
+Oh, just noticed in the console window of the assistant:
+
+ssh-keygen: /home/xgwsbae/.ssh/known_hosts: No such file or directory
+ssh-keygen: /home/xgwsbae/.ssh/known_hosts: No such file or directory
+
+Home directory is C:/Users/xgwsbae/ (git bash gives /c/Users/xgwsbae in $HOME) ... looks like something got confuzzled between Windows and Unix there.
+"""]]
diff --git a/doc/devblog/day_104__unused_II/comment_5_1964bfce4887c9c0828fd7f54f5b4f6b._comment b/doc/devblog/day_104__unused_II/comment_5_1964bfce4887c9c0828fd7f54f5b4f6b._comment
new file mode 100644
index 0000000000..12849438c6
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_5_1964bfce4887c9c0828fd7f54f5b4f6b._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 5"
+ date="2014-01-29T17:58:26Z"
+ content="""
+Some things (not git-annex) default to /home/$USER when appropriate env vars are not set. There is a bug open about that, [[bugs/assistant_using_the_incorrect_path_on_windows?]], although I don't know what it makes sense for git-annex to do to deal with it.
+
+box.com *is* a webdav repository. It is the only webdav repository the webapp currently supports setting up, although you can configure any webdav remote you like at the command line and the assistant will then be able to use it.
+
+Will be curious to hear if the http-conduit library used for webdav supports proxies. If not, that would certianly seem a good place to file a bug. Unofrtunately, git-annex uses 2 or 3 other http stacks in other places too.
+"""]]
diff --git a/doc/devblog/day_104__unused_II/comment_6_0ed4023c9c249024fe0454fc5bab3b14._comment b/doc/devblog/day_104__unused_II/comment_6_0ed4023c9c249024fe0454fc5bab3b14._comment
new file mode 100644
index 0000000000..d900dc5117
--- /dev/null
+++ b/doc/devblog/day_104__unused_II/comment_6_0ed4023c9c249024fe0454fc5bab3b14._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm7AuSfii_tCkLyspL6Mr0ATlO6OxLNYOo"
+ nickname="Georg"
+ subject="comment 6"
+ date="2014-01-30T10:52:09Z"
+ content="""
+Well, according to the hackage documentation of http conduit it seems it at least supports proxies when youre code gives it the proxy host and port.
+
+But the link about the problem with environment settings helped me to get around my immediate problem by just running annex from the git bash (which is prefereably to me most of the time anyway). So I could set up my annex on my work machine and just tunnel out with ProxyCommand via our ssh gateway. Yay!
+"""]]
diff --git a/doc/devblog/day_105__locking.mdwn b/doc/devblog/day_105__locking.mdwn
new file mode 100644
index 0000000000..b41056bb44
--- /dev/null
+++ b/doc/devblog/day_105__locking.mdwn
@@ -0,0 +1,30 @@
+With yesterday's release, I'm pretty much done with the month's work. Since
+there was no particular goal this month, it's been a grab bag of features
+and bugfixes. Quite a lot of them in this last release.
+
+I'll be away the next couple of days.. But got a start today on the next
+part of the roadmap, which is planned to be all about Windows and Android
+porting. Today, it was all about lock files, mostly on Windows.
+
+Lock files on Windows are horrific. I especially like that programs that
+want to open a file, for any reason, are encouraged in the official
+documentation to retry repeatedly if it fails, because some other
+random program, like a virus checker, might have opened the file first.
+
+Turns out Windows does support a shared file read mode. This was
+just barely enough for me to implement both shared and exclusive
+file locking a-la-flock.
+
+Couldn't avoid a busy wait in a few places that block on a lock.
+Luckily, these are few, and the chances the lock will be taken for a long
+time is small. (I did think about trying to watch the file for close events
+and detect when the lock was released that way, but it seemed much too
+complicated and hard to avoid races.)
+
+Also, Windows only seems to support mandatory locks, while all locking in
+git-annex needs to be advisory locks. Ie, git-annex's locking shouldn't
+prevent a program from opening an annexed file! To work around that,
+I am using dedicated lock files on Windows.
+
+Also switched direct mode's annexed object locking to use dedicated lock
+files. AFAICS, this was pretty well broken in direct mode before.
diff --git a/doc/devblog/day_106__catching_up.mdwn b/doc/devblog/day_106__catching_up.mdwn
new file mode 100644
index 0000000000..86e7acbaec
--- /dev/null
+++ b/doc/devblog/day_106__catching_up.mdwn
@@ -0,0 +1,5 @@
+While I've not been blogging over what amounted to a long weekend, looking
+over the changelog, there were quite a few things done. Mostly various
+improvements and fixes to `git annex sync --content`.
+
+Today, got the test suite to pass on Windows 100% again.
diff --git a/doc/devblog/day_107__TDD.mdwn b/doc/devblog/day_107__TDD.mdwn
new file mode 100644
index 0000000000..0ae41f0d64
--- /dev/null
+++ b/doc/devblog/day_107__TDD.mdwn
@@ -0,0 +1,10 @@
+A more test driven day than usual. Yesterday I noticed a test case was
+failing on Windows in a way not related to what it was intended to test,
+and fixed the test case to not fail.. But knew I'd need to get to the
+bottom of what broke it eventually.
+
+Digging into that today, I eventually (after rather a long time stuck)
+determined the bug involved automatic conflict resolution, but only
+happened on systems without symlink support. This let me reproduce it on
+FAT outside Windows and do some fast TDD iterations in a much less
+unwieldly environment and fix the bug.
diff --git a/doc/devblog/day_108__new_use_for_location_tracking.mdwn b/doc/devblog/day_108__new_use_for_location_tracking.mdwn
new file mode 100644
index 0000000000..cf0d3e0964
--- /dev/null
+++ b/doc/devblog/day_108__new_use_for_location_tracking.mdwn
@@ -0,0 +1,20 @@
+Added a new feature that started out with me wanting a way to undo a
+`git-annex drop`, but turned into something rather more powerful. The `--in`
+option can now be told to match files that were in a repository at some
+point in the past. For example, `git annex get --in=here@{yesterday}` will
+get any files that have been dropped over the past day.
+
+While git-annex's location tracking info is stored in git and so versioned,
+very little of it makes use of past versions of the location tracking info
+(only `git annex log`). I'm happy to have finally found a use for it!
+
+OB Windows porting: Fixed a bug in the symlink calculation code.
+Sounds simple; took 2 hours!
+
+Also various bug triage; updated git version on OSX; forwarded bug about
+DAV-0.6 being broken upstream; fixed a bug with initremote in
+encryption=pubkey mode. Backlog is 65 messages.
+
+---
+
+Today's work was sponsored by Brock Spratlen.
diff --git a/doc/devblog/day_109__elimintating_absNormPath.mdwn b/doc/devblog/day_109__elimintating_absNormPath.mdwn
new file mode 100644
index 0000000000..a15cb7f093
--- /dev/null
+++ b/doc/devblog/day_109__elimintating_absNormPath.mdwn
@@ -0,0 +1,18 @@
+git-annex has been using MissingH's `absNormPath` forever, but that's
+not very maintained and doesn't work on Windows. I've been
+wanting to get rid of it for some time, and finally did today, writing a
+`simplifyPath` that does the things git-annex needs and will work with all
+the Windows filename craziness, and takes advantage of the more modern
+System.FilePath to be quite a simple peice of code. A QuickCheck test found
+no important divergences from absNormPath. A good first step to making
+git-annex not depend on MissingH at all.
+
+That fixed one last Windows bug that was disabled in the test suite:
+`git annex add ..\subdir\file` will now work.
+
+I am re-installing the Android autobuilder for 2 reasons: I noticed I had
+accidentially lost a patch to make a library use the Android SSL cert directory,
+and also a new version of GHC is very near to release and so it makes sense
+to update.
+
+Down to 38 messages in the backlog.
diff --git a/doc/devblog/day_110__release_prep.mdwn b/doc/devblog/day_110__release_prep.mdwn
new file mode 100644
index 0000000000..12ba78a4fd
--- /dev/null
+++ b/doc/devblog/day_110__release_prep.mdwn
@@ -0,0 +1,25 @@
+Last night I tracked down and fixed a bug in the DAV library that has been
+affecting WebDAV remotes. I've been deploying the fix for that today,
+including to the android and arm autobuilders. While I finished a clean
+reinstall of the android autobuilder, I ran into problems getting a clean
+reinstall of the arm autobuilder (some type mismatch error building
+yesod-core), so manually fixed its DAV for now.
+
+The WebDAV fix and other recent fixes makes me want to make a release soon,
+probably Monday.
+
+ObWindows: Fixed git-annex to not crash when run on Windows
+in a git repository that has a remote with a unix-style path
+like "/foo/bar". Seems that not everything aggrees on whether such a path
+is absolute; even sometimes different parts of the same library disagree!
+
+[[!format haskell """
+import System.FilePath.Windows
+
+prop_windows_is_sane :: Bool
+prop_windows_is_sane = isAbsolute upath || ("C:\\STUFF" > upath /= upath)
+ where upath = "/foo/bar"
+"""]]
+
+Perhaps more interestingly, I've been helping dxtrish port git-annex to
+OpenBSD and it seems most of the way there.
diff --git a/doc/devblog/day_94__leaks.mdwn b/doc/devblog/day_94__leaks.mdwn
index bd3b9f9d44..3aa4e1552c 100644
--- a/doc/devblog/day_94__leaks.mdwn
+++ b/doc/devblog/day_94__leaks.mdwn
@@ -7,6 +7,6 @@ have gotten them all fixed:
Before: [[bugs/import_memleak_from_the_assistant/leakbefore.png]]
After: [[bugs/import_memleak_from_the_assistant/leakafter.png]]
-Also fixed a bug in `git annex add` when the disk was completely full. It
-could sometimes in that situation move the file from the work tree to
+Also fixed a bug in `git annex add` when the disk was completely full.
+In that situation, it could sometimes move the file from the work tree to
.git/annex/objects and fail to put the symlink in place.
diff --git a/doc/devblog/day_99__catching_up_again.mdwn b/doc/devblog/day_99__catching_up_again.mdwn
new file mode 100644
index 0000000000..118a21f8d2
--- /dev/null
+++ b/doc/devblog/day_99__catching_up_again.mdwn
@@ -0,0 +1,19 @@
+Activity has been a bit low again this week. It seems to make sense to do
+weekly releases currently (rather than bi-monthly), and Thursday's
+release had only one new feature (Tahoe LAFS) and a bunch of bug fixes.
+
+Looks like git-annex will get back into Debian testing soon, after various
+fixes to make it build on all architectures again, and then the
+backport can be updated again too.
+
+I have been struggling with a problem with the OSX builds, which fail with
+a SIGKILL on some machines. It seems that homebrew likes to agressively
+optimise things it builds, and while I have had some success with its
+`--build-bottle` option, something in the gnutls stack used for XMPP is
+still over-optimised. Waiting to hear back from Kevin on cleaning up some
+optimised system libraries on the OSX host I use. (Is there some way to make
+a clean chrooot on OSX that can be accessed by a non-root user?)
+
+Today I did some minor work involving the --json switch, and also
+a small change (well, under 300 line diff) allowing
+--all to be mixed with options like --copies and --in.
diff --git a/doc/devblog/day_99__catching_up_again/comment_1_b871bf0606dc29be9b8c2e5dc150f708._comment b/doc/devblog/day_99__catching_up_again/comment_1_b871bf0606dc29be9b8c2e5dc150f708._comment
new file mode 100644
index 0000000000..933de78737
--- /dev/null
+++ b/doc/devblog/day_99__catching_up_again/comment_1_b871bf0606dc29be9b8c2e5dc150f708._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkq2cjugiSvKWiWmcah3CPBqviQV_cin9I"
+ nickname="Yury"
+ subject="The world of Mac"
+ date="2014-01-19T14:13:55Z"
+ content="""
+I think that there is nothing fundamental about Mac OS X, which would prevent one from making a clean chroot that would work for non-root users. For instance, I believe that jailkit has been reported to work just fine. The problem is that you'll have to rebuild most of the stuff you need from scratch, which is very tedious. Might be easier to find instances where Homebrew has something like -march=native added to the $CFLAGS (not that I particularly fancy Homebrew of all 'missing' package managers on OS X).
+
+Anyways, it sounds like I'm going to get a Mac Mini donated sometime soon and I'm curious as to what would be the best way to make use of it for the CI system...
+"""]]
diff --git a/doc/devblog/day_99__catching_up_again/comment_2_c8363d47223e7bb899420e800bde3e27._comment b/doc/devblog/day_99__catching_up_again/comment_2_c8363d47223e7bb899420e800bde3e27._comment
new file mode 100644
index 0000000000..fb2377845d
--- /dev/null
+++ b/doc/devblog/day_99__catching_up_again/comment_2_c8363d47223e7bb899420e800bde3e27._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnE6kFAbud1LWrQuyX76yMYnUjHt9tR-A8"
+ nickname="Leonardo"
+ subject="Chroots"
+ date="2014-01-21T13:52:29Z"
+ content="""
+How about simply having sshd inside the chroot?
+"""]]
diff --git a/doc/forum/Can_Not_Sync_to_Git_Repo/comment_12_b4f8be428a08db01dbd004e1f06dcffd._comment b/doc/forum/Can_Not_Sync_to_Git_Repo/comment_12_b4f8be428a08db01dbd004e1f06dcffd._comment
new file mode 100644
index 0000000000..883ae6d96f
--- /dev/null
+++ b/doc/forum/Can_Not_Sync_to_Git_Repo/comment_12_b4f8be428a08db01dbd004e1f06dcffd._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://cstork.org/"
+ nickname="Chris Stork"
+ subject="Bug fix confirmed"
+ date="2014-01-30T15:29:56Z"
+ content="""
+Thank you, Joey!
+FYI, my repo was automatically converted to version 5 and put on the annex/direct/master branch.
+As Joey mentioned, this might only apply to my bug.
+"""]]
diff --git a/doc/forum/Can__39__t_get_jabber_working/comment_4_259741e146906ff70540390bdfe07002._comment b/doc/forum/Can__39__t_get_jabber_working/comment_4_259741e146906ff70540390bdfe07002._comment
new file mode 100644
index 0000000000..005759caf9
--- /dev/null
+++ b/doc/forum/Can__39__t_get_jabber_working/comment_4_259741e146906ff70540390bdfe07002._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawlm_3m5gLhML9bHbZ8FpJ-HBZhWaRfFeO8"
+ nickname="Corey"
+ subject="Same bug? OSX 10.9.1"
+ date="2014-01-23T23:38:32Z"
+ content="""
+… using Chrome. Connection to 127.0.0.1:XXXXX interrupted when setting up Jabber.
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces.mdwn b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces.mdwn
new file mode 100644
index 0000000000..70a573ff47
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces.mdwn
@@ -0,0 +1,20 @@
+I have a repository at rsync.net, even though following files are shown as unused I can not drop them.
+
+Running unused,
+
+ git annex unused --from cloud
+ unused cloud (checking for unused data...) (checking annex/direct/master...)
+ Some annexed data on cloud is not used by any files:
+ NUMBER KEY
+ 1 SHA256E-s4189547--43aef42540e7f50fc454ab3a2ce4aa28a13b57cccff725359cea0470eb88704b. Bir.mp3
+ 2 SHA256E-s853765--c0964d3af493d78b7b8393a2aefdd8c290390a03c8cb5cccdcac4647c0fc52a0. 1.jpg
+ 3 SHA256E-s8706267--e34988b70048a512ad0f431a2a91fa7dd553f96c2bd6caca0bcef928bdfafb93. 3.mp3
+ (To see where data was previously used, try: git log --stat -S'KEY')
+
+ To remove unwanted data: git-annex dropunused --from cloud NUMBER
+
+show these then running,
+
+ git annex dropunused 1-3 --force
+
+reports ok for each drop operation but rerunning git annex unused --from cloud still shows these three files as unused. I am using git-annex on mac os x (current dmg) on a direct repo. I have similar problems dropping files on the current repo even though I drop unused they still show up as unused.
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_1_b909ed9f474601587b2adad7ad4f674d._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_1_b909ed9f474601587b2adad7ad4f674d._comment
new file mode 100644
index 0000000000..fa41b59a7d
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_1_b909ed9f474601587b2adad7ad4f674d._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="doubt this has anything to do with spaces"
+ date="2014-02-08T17:44:45Z"
+ content="""
+If you want to drop the files from the remote, you need to also pass the --from option to dropunused. Otherwise, it defaults to dropping any of the unused files that are present in the local repository.
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_2_b2735a6e03db3f77a87a0f7d87347685._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_2_b2735a6e03db3f77a87a0f7d87347685._comment
new file mode 100644
index 0000000000..5f5694c00f
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_2_b2735a6e03db3f77a87a0f7d87347685._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8"
+ nickname="Hamza"
+ subject="comment 2"
+ date="2014-02-08T18:30:47Z"
+ content="""
+I tried with/without --from still does not drop the files.
+
+ git annex dropunused --from cloud 1-3 --force
+ dropunused 1 (from cloud...) (gpg) ok
+ dropunused 2 (from cloud...) ok
+ dropunused 3 (from cloud...) ok
+ (Recording state in git...)
+
+still running unused shows the files as unused.
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_3_dd82a0cd698b0688ff08f0462af0275f._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_3_dd82a0cd698b0688ff08f0462af0275f._comment
new file mode 100644
index 0000000000..86e3bd2c1c
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_3_dd82a0cd698b0688ff08f0462af0275f._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 3"
+ date="2014-02-08T19:17:46Z"
+ content="""
+Ok, you're right and this *does* involve spaces. Some bug in the unused log parser.
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_4_bbebb1d0dc5fbc1f6a0bb75b47bd4986._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_4_bbebb1d0dc5fbc1f6a0bb75b47bd4986._comment
new file mode 100644
index 0000000000..6459ee8d7c
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_4_bbebb1d0dc5fbc1f6a0bb75b47bd4986._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 4"
+ date="2014-02-08T19:28:18Z"
+ content="""
+Fixed in git.
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_5_106c271d5174342055910bf57c0a34c5._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_5_106c271d5174342055910bf57c0a34c5._comment
new file mode 100644
index 0000000000..4ad4d6f8b5
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_5_106c271d5174342055910bf57c0a34c5._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8"
+ nickname="Hamza"
+ subject="comment 5"
+ date="2014-02-08T19:46:49Z"
+ content="""
+Are the files dropped on the rsync repo? Or are they gonna be dropped when fix propagates to dmg build?
+"""]]
diff --git a/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_6_3a2d3cc3e018beaf2eb44b86ce7e1a7f._comment b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_6_3a2d3cc3e018beaf2eb44b86ce7e1a7f._comment
new file mode 100644
index 0000000000..fbd9ed55c0
--- /dev/null
+++ b/doc/forum/Can_not_Drop_Unused_Files_With_Spaces/comment_6_3a2d3cc3e018beaf2eb44b86ce7e1a7f._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.163"
+ subject="comment 6"
+ date="2014-02-08T19:49:11Z"
+ content="""
+You will need to upgrade git-annex to the next autobuild or an upcoming release to get the fix.
+"""]]
diff --git a/doc/forum/Can_not_drop_unused_file.mdwn b/doc/forum/Can_not_drop_unused_file.mdwn
new file mode 100644
index 0000000000..8ec48eb14f
--- /dev/null
+++ b/doc/forum/Can_not_drop_unused_file.mdwn
@@ -0,0 +1,14 @@
+I have encrypted directory remote on a usb drive over time it accumulated some unused files. I would like to drop them running,
+
+ git annex --unused --from external
+
+returns a list of unused files when I try to drop them with,
+
+
+ git annex dropunused --force --from external 1-XX
+
+I get,
+
+ dropunused XX (from external...) failed
+
+I can not seem to get rid of these files.
diff --git a/doc/forum/Can_not_drop_unused_file/comment_1_cea83dfdf4cdb4f6efb3f2b33a39a51f._comment b/doc/forum/Can_not_drop_unused_file/comment_1_cea83dfdf4cdb4f6efb3f2b33a39a51f._comment
new file mode 100644
index 0000000000..4a6eacc510
--- /dev/null
+++ b/doc/forum/Can_not_drop_unused_file/comment_1_cea83dfdf4cdb4f6efb3f2b33a39a51f._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.68"
+ subject="comment 1"
+ date="2014-01-18T22:39:37Z"
+ content="""
+One reason it might fail (especially if it's not printing any useful message beyond \"(failed)\") is if it thought the file was present in the repositort, but something has happened to it.
+
+So, I suggest you try:
+
+git annex fsck --from external
+
+Followed by dropping again.
+
+If that doesn't help, I'd recommend stracing the dropping of one of the unused files, and see what's going wrong toward the end.
+"""]]
diff --git a/doc/forum/Can_not_drop_unused_file/comment_2_ed1543cff5e6e81ca18c43b716ca8199._comment b/doc/forum/Can_not_drop_unused_file/comment_2_ed1543cff5e6e81ca18c43b716ca8199._comment
new file mode 100644
index 0000000000..321e107615
--- /dev/null
+++ b/doc/forum/Can_not_drop_unused_file/comment_2_ed1543cff5e6e81ca18c43b716ca8199._comment
@@ -0,0 +1,42 @@
+[[!comment format=mdwn
+ username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8"
+ nickname="Hamza"
+ subject="comment 2"
+ date="2014-01-19T23:56:17Z"
+ content="""
+I've tried,
+
+ git annex fsck --from external
+
+and
+
+ git annex fsck --all --from external
+
+did not solve the problem. Running,
+
+ strace git annex dropunused 1 --from external --force
+
+tail of strace produces,
+
+ clone(child_stack=0, flags=CLONE_CHILD_CLEARTID|CLONE_CHILD_SETTID|SIGCHLD, child_tidp
+ tr=0x7f3a8d6d8a10) = 5746
+ rt_sigaction(SIGINT, {0x4e1fb0, [INT], SA_RESTORER|SA_RESTART, 0x7f3a8c8b60b0}, {SIG_D
+ FL, [], 0}, 8) = 0
+ rt_sigaction(SIGHUP, {0x4e1fb0, [HUP], SA_RESTORER|SA_RESTART, 0x7f3a8c8b60b0}, {SIG_D
+ FL, [], 0}, 8) = 0
+ rt_sigaction(SIGTERM, {0x4e1fb0, [TERM], SA_RESTORER|SA_RESTART, 0x7f3a8c8b60b0}, {SIG
+ _DFL, [], 0}, 8) = 0
+ rt_sigaction(SIGQUIT, {0x4e1fb0, [QUIT], SA_RESTORER|SA_RESTART, 0x7f3a8c8b60b0}, {SIG
+ _DFL, [], 0}, 8) = 0
+ rt_sigaction(SIGPIPE, {0x4e1fb0, [PIPE], SA_RESTORER|SA_RESTART, 0x7f3a8c8b60b0}, {SIG
+ _DFL, [], 0}, 8) = 0
+ close(5) = 0
+ read(4, \"\", 1) = 0
+ close(4) = 0
+ wait4(5746, dropunused 1 (from external...) (gpg) failed
+ git-annex: dropunused: 1 failed
+ [{WIFEXITED(s) && WEXITSTATUS(s) == 1}], 0, NULL) = 5746
+ --- SIGCHLD (Child exited) @ 0 (0) ---
+ exit_group(1) = ?
+
+"""]]
diff --git a/doc/forum/Can_not_drop_unused_file/comment_3_0c9c9c0ed557af4845a67434c21bb4bc._comment b/doc/forum/Can_not_drop_unused_file/comment_3_0c9c9c0ed557af4845a67434c21bb4bc._comment
new file mode 100644
index 0000000000..8a1ecfdd24
--- /dev/null
+++ b/doc/forum/Can_not_drop_unused_file/comment_3_0c9c9c0ed557af4845a67434c21bb4bc._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.68"
+ subject="comment 3"
+ date="2014-01-20T16:33:27Z"
+ content="""
+I see you're using encryption. That could have something to do with the problem. Which type of encryption was used for this special remote? encryption=shared or one of the other options?
+
+Look through the whole strace output for attempts to access the directory special remote and show those. Or put up the full strace somewhere.
+"""]]
diff --git a/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads.mdwn b/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads.mdwn
new file mode 100644
index 0000000000..8de9cc7692
--- /dev/null
+++ b/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads.mdwn
@@ -0,0 +1,3 @@
+I want to upload and download more than one file at a time to and from the various remotes.
+
+How do I do that?
diff --git a/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads/comment_1_d5559994ee45a5c185a55c9a4d824aa4._comment b/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads/comment_1_d5559994ee45a5c185a55c9a4d824aa4._comment
new file mode 100644
index 0000000000..41999cf0e9
--- /dev/null
+++ b/doc/forum/How_does_one_change_the_number_of_simultaneous_uploads/comment_1_d5559994ee45a5c185a55c9a4d824aa4._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T19:12:10Z"
+ content="""
+This is not currently supported. See [[todo/Slow_transfer_for_a_lot_of_small_files.]]
+
+ You can click on the button next to individual files in the transfer queue to force concurrent transfers.
+
+
+"""]]
diff --git a/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__.mdwn b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__.mdwn
new file mode 100644
index 0000000000..91d7a886b6
--- /dev/null
+++ b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__.mdwn
@@ -0,0 +1,40 @@
+I have one Annex meant to be kept in sync across two computers by the assistant. These computers can't connect directly, so I use a transfer repository (at rsync.net) and xmpp. Recently the two repositories have started to diverge: files added here do not appear there and vice versa, files modified here are not updated there and vice versa. It may be related to this bug: [[bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport/]] since one of the two installed versions of git-annex is 5.20140117~bpo70+1, but I do not know whether the divergence started the day I upgraded to this version.
+
+I tried this:
+
+ git-annex fsck --from rsync.net_annex
+
+on both machines. No error is reported, but files are missing here and there and files differ here and there.
+
+I stopped the assistant on both machines and tried to sync with:
+
+ git-annex sync
+
+and got:
+
+ commit
+ ok
+ pull 'XXX'
+ fatal: Unable to find remote helper for 'xmpp'
+ failed
+ push 'XXX'
+ Pushing to XXX failed
+ (non-fast-forward problems can be solved by setting receive.denyNonFastforwards to false in the remote's git config)
+ failed
+ git-annex: sync: 2 failed
+
+where 'XXX' stands for my jabber account. I then tried:
+
+ git-annex sync rsync.net_annex
+
+but got:
+
+ git-annex: cannot sync special remotes: rsync.net_annex
+
+
+
+This situation is unfortunate because the user is not made aware of anything failing. The assistant is running, the webapp shows files being uploaded to the transfer repository, but the two repositories are actually diverging.
+
+How can I synchronize these two repositories?
+
+Thanks,
diff --git a/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_1_1c913395f076ee203caaab057da8afbe._comment b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_1_1c913395f076ee203caaab057da8afbe._comment
new file mode 100644
index 0000000000..7bf4585054
--- /dev/null
+++ b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_1_1c913395f076ee203caaab057da8afbe._comment
@@ -0,0 +1,13 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnNqLKszWk9EoD4CDCqNXJRIklKFBCN1Ao"
+ nickname="maurizio"
+ subject="downgrading is not an easy option"
+ date="2014-01-30T05:44:48Z"
+ content="""
+In order to check whether this is related to [[https://git-annex.branchable.com/bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport/]] I tried to downgrade git-annex to the previous version that was available on wheezy-backports (git-annex_4.20131106~bpo70+1_i386.deb) but then I get:
+
+ git-annex: Repository version 5 is not supported. Upgrade git-annex.
+ failed
+
+
+"""]]
diff --git a/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_2_081793c52bf15c74a7f48a67c49ff818._comment b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_2_081793c52bf15c74a7f48a67c49ff818._comment
new file mode 100644
index 0000000000..8d4d49a778
--- /dev/null
+++ b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_2_081793c52bf15c74a7f48a67c49ff818._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnNqLKszWk9EoD4CDCqNXJRIklKFBCN1Ao"
+ nickname="maurizio"
+ subject="clean up"
+ date="2014-01-31T19:55:30Z"
+ content="""
+ok, now that git-annex has been updated to 5.20140117~bpo70+2 things start flowing again, so it was actually caused by [[http://git-annex.branchable.com/bugs/Jabber__47__xmpp_not_supported_on_Debian_Wheezy_backport/]]. Now there is a certain number of files called 'filename.variant.06b8' for instance. That is a bit messy.
+
+I do not know wheter/how it would be possible to inform the user that something is going wrong, but certainely it would be better to avoid failing completely silently.
+
+It would be useful if the webapp could give more precise information about the files the assistant is manipulating. For instance: \"now uploading file 'bla', updating version last uploaded from 'remote' on 'date'\".
+"""]]
diff --git a/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_3_f8e0376beb486cf8ce52384ff511ecf2._comment b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_3_f8e0376beb486cf8ce52384ff511ecf2._comment
new file mode 100644
index 0000000000..99bfbba0a8
--- /dev/null
+++ b/doc/forum/How_to_solve__problem_with_diverging_repositories_handled_by_the_assistant__63__/comment_3_f8e0376beb486cf8ce52384ff511ecf2._comment
@@ -0,0 +1,11 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 3"
+ date="2014-02-07T19:07:11Z"
+ content="""
+Normally the webapp will tell you whenever it fails to sync with a remote. However, in this case, it had XMPP support compiled right out of it, so had no idea that remote even existed, and never tried to sync with it, so had no failure to report.
+
+
+The \".variant\" files are because you must have made files with the same names in the 2 repositories while they were disconnected.
+"""]]
diff --git a/doc/forum/Limit_file_revision_history.mdwn b/doc/forum/Limit_file_revision_history.mdwn
deleted file mode 100644
index 0e68ebb6d3..0000000000
--- a/doc/forum/Limit_file_revision_history.mdwn
+++ /dev/null
@@ -1,22 +0,0 @@
-Hi, I am assuming to use git-annex-assistant for two usecases, but I would like to ask about the options or planed roadmap for dropped/removed files from the repository.
-
-Usecases:
-
-1. sync working directory between laptop, home computer, work komputer
-2. archive functionality for my photograps
-
-Both usecases have one common factor. Some files might become obsolate and in long time frame nobody is interested to keep their revisions. Let's assume photographs. Usuall workflow I take is to import all photograps to filesystem, then assess (select) the good ones I want to keep and then process them what ever way.
-
-Problem with git-annex(-assistant) I have is that it start to revision all of the files at the time they are added to directory. This is welcome at first but might be an issue if you are used to put 80% of the size of your imported files to trash.
-
-I am aware of what git-annex is not. I have been reading documentation for "git-annex drop" and "unused" options including forums. I do understand that I am actually able to delete all revisions of the file if I will drop it, remove it and if I will run git annex unused 1..###. (on all synced repositories).
-
-I actually miss the option to have above process automated/replicated to the other synced repositories.
-
-I would formulate the 'use case' requirements for git-annex as:
-
-* command to drop an file including revisions from all annex repositories? (for example like moving a file to /trash folder) that will schedulle it's deletition)
-* option to keep like max. 10 last revisions of the file?
-* option to keep only previous revisions if younger than 6 months from now?
-
-Finally, how to specify a feature request for git-annex?
diff --git a/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning.mdwn b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning.mdwn
new file mode 100644
index 0000000000..e7062ff29c
--- /dev/null
+++ b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning.mdwn
@@ -0,0 +1,20 @@
+I have a git annex repository which I use to store versioned binaries in a regular git repository. We also use submodules in the repository (the sources of the versioned binaries) but the binaries are not in the submodules. This has worked great for us.
+
+Recently, there have been a number of changes (I got a new laptop, moved to fedora 20, renamed the repository, etc...) that happened at once. Now when I checkout a clean working version of the repository and then run git annex get . and then do an unlock and a lock on the file I get the "Locking this file would discard any changes you have made to it. Use 'git annex add' to stage your changes. (Or, use --force to override)" warning.
+
+I have tried to isolate this as much as possible but can't find what caused this. On a co-worker's laptop it seems to work fine so far. A clean repository didn't fix it. An old repository didn't fix it (though I recall it working there previously on this laptop). It did work and just stopped recently.
+
+ $ git annex version
+ git-annex version: 5.20140107
+ build flags: Assistant Inotify DBus Quvi TDFA
+ key/value backends: SHA256E SHA1E SHA512E SHA224E SHA384E SHA256 SHA1 SHA512 SHA224 SHA384 WORM URL
+ remote types: git gcrypt bup directory rsync web glacier hook external
+ local repository version: 5
+ supported repository version: 5
+ upgrade supported from repository versions: 0 1 2 4
+
+ $ git annex lock --debug --verbose vendors/unittest-xml-reporting-1.5.0.tar.gz # (some names changed to protect the innocent)
+ [2014-02-05 12:54:45 IST] read: git ["--git-dir=/home/user/loppa_deuce/loppa/.git","--work-tree=/home/user/loppa_deuce/loppa","diff","--name-only","--diff-filter=T","-z","--","vendors/unittest-xml-reporting-1.5.0.tar.gz"]
+ [2014-02-05 12:54:45 IST] chat: git ["--git-dir=/home/user/loppa_deuce/loppa/.git","--work-tree=/home/user/loppa_deuce/loppa","cat-file","--batch"]
+ [2014-02-05 12:54:45 IST] read: git ["--git-dir=/home/user/loppa_deuce/loppa/.git","--work-tree=/home/user/loppa_deuce/loppa","diff","--name-only","--diff-filter=T","-z","--cached","--","vendors/unittest-xml-reporting-1.5.0.tar.gz"]
+ lock vendors/unittest-xml-reporting-1.5.0.tar.gz git-annex: Locking this file would discard any changes you have made to it. Use 'git annex add' to stage your changes. (Or, use --force to override)
diff --git a/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_1_25a04c7345f5b626aa71524603c833ed._comment b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_1_25a04c7345f5b626aa71524603c833ed._comment
new file mode 100644
index 0000000000..84f556d654
--- /dev/null
+++ b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_1_25a04c7345f5b626aa71524603c833ed._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmfVOIl06X7NKio-NBYZ-cfw5LFVqHMX8o"
+ nickname="Daniel"
+ subject="Hash is the same"
+ date="2014-02-05T11:13:12Z"
+ content="""
+I forgot to mention that I also checked the hash of the file to make sure that nothing changed the file and nothing changed. Just quick unlock/lock triggers it.
+"""]]
diff --git a/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_2_7146a3c69749b9b1001fffc6e7a8bcda._comment b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_2_7146a3c69749b9b1001fffc6e7a8bcda._comment
new file mode 100644
index 0000000000..cc5e853169
--- /dev/null
+++ b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_2_7146a3c69749b9b1001fffc6e7a8bcda._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmfVOIl06X7NKio-NBYZ-cfw5LFVqHMX8o"
+ nickname="Daniel"
+ subject="New git-annex package to blame"
+ date="2014-02-05T14:23:40Z"
+ content="""
+I downgraded my git-annex version, rechecked out the repository and now everything works.
+ $ git annex version
+ git-annex version: 4.20130827
+ build flags: Assistant Inotify
+
+"""]]
diff --git a/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_3_fd39e6ceffd9bf0709658c34945d8699._comment b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_3_fd39e6ceffd9bf0709658c34945d8699._comment
new file mode 100644
index 0000000000..5b23df8707
--- /dev/null
+++ b/doc/forum/Locking_and_then_unlocking_a_file_results_in_file_changed_warning/comment_3_fd39e6ceffd9bf0709658c34945d8699._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 3"
+ date="2014-02-06T17:05:45Z"
+ content="""
+Recent versions of git-annex have tried to extend the --force option to be needed in any operation that can possibly cause data loss. This includes locking a file, since that throws away any changes.
+
+Note that `git annex lock` does not check if the file is unmodified. For a few reasons including
+
+* some backends don't include a checksum
+* it would be expensive to check a checksum
+* the file could get modified after or during a checksum check, and those modifications would be missed
+
+If you are sure you want to throw away any changes, use --force as suggested. If not, use `git annex add $file`, and assuming you're using a checksumming backend, it will notice the file has not changed and do what you want `git annex lock $file` to have done in this case.
+"""]]
diff --git a/doc/forum/Remote_server_only_for_the_git_repository.mdwn b/doc/forum/Remote_server_only_for_the_git_repository.mdwn
new file mode 100644
index 0000000000..12f4c5c78f
--- /dev/null
+++ b/doc/forum/Remote_server_only_for_the_git_repository.mdwn
@@ -0,0 +1,3 @@
+Hi, I'm using git-annex 5.2014012 with the webapp and I've added two repositories: a remote server and a box.com account. When I add a file it is uploaded properly to both remotes as you would expect.
+
+The problem is that I would like the files to only be uploaded to box.com, and the remote server only store the git repository. Is there any way of saying to git-annex to not sync files to a remote server?
diff --git a/doc/forum/Remote_server_only_for_the_git_repository/comment_1_d4d8d8cfebf9a98ca8878c5684d5bb50._comment b/doc/forum/Remote_server_only_for_the_git_repository/comment_1_d4d8d8cfebf9a98ca8878c5684d5bb50._comment
new file mode 100644
index 0000000000..c97184cb82
--- /dev/null
+++ b/doc/forum/Remote_server_only_for_the_git_repository/comment_1_d4d8d8cfebf9a98ca8878c5684d5bb50._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://me.yahoo.com/a/FHnTlSBo1eCGJRwueeKeB6.RCaPbGMPr5jxx8A--#ce0d8"
+ nickname="Hamza"
+ subject="comment 1"
+ date="2014-02-06T13:30:33Z"
+ content="""
+You can tell git-annex to ignore the repo (assuming git repo is called origin)
+
+ git config remote.origin.annex-ignore true
+"""]]
diff --git a/doc/forum/Remote_server_only_for_the_git_repository/comment_2_a62dec8ab98ac7bd65059a9e425a01e2._comment b/doc/forum/Remote_server_only_for_the_git_repository/comment_2_a62dec8ab98ac7bd65059a9e425a01e2._comment
new file mode 100644
index 0000000000..d02994628c
--- /dev/null
+++ b/doc/forum/Remote_server_only_for_the_git_repository/comment_2_a62dec8ab98ac7bd65059a9e425a01e2._comment
@@ -0,0 +1,9 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawk9nck8WX8-ADF3Fdh5vFo4Qrw1I_bJcR8"
+ nickname="Jon Ander"
+ subject="comment 2"
+ date="2014-02-07T11:36:32Z"
+ content="""
+Thanks, that seams to be exactly what I need.
+Any change of adding this option to the webapp?
+"""]]
diff --git a/doc/forum/Usecase:_Tree_of_files_on_a_remote_SMB_server_that_i_need_to_leave_there__44____while_also_cloning_and_syncing_too./comment_5_a06e8c9b4e30c1cd6cbed40d2db50abc._comment b/doc/forum/Usecase:_Tree_of_files_on_a_remote_SMB_server_that_i_need_to_leave_there__44____while_also_cloning_and_syncing_too./comment_5_a06e8c9b4e30c1cd6cbed40d2db50abc._comment
new file mode 100644
index 0000000000..321fa9c53f
--- /dev/null
+++ b/doc/forum/Usecase:_Tree_of_files_on_a_remote_SMB_server_that_i_need_to_leave_there__44____while_also_cloning_and_syncing_too./comment_5_a06e8c9b4e30c1cd6cbed40d2db50abc._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://launchpad.net/~timo-linux"
+ nickname="Tim O'Callaghan"
+ subject="Still have not found a reasonable solution for this myself."
+ date="2014-02-03T14:34:14Z"
+ content="""
+And it seems i'm not the only one, So I'd like to bump the topic.
+
+Can someone at least tell me if it is possible with annex/annex-gui or not?
+"""]]
diff --git a/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__.mdwn b/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__.mdwn
new file mode 100644
index 0000000000..870f8913eb
--- /dev/null
+++ b/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__.mdwn
@@ -0,0 +1 @@
+I want to add an existing repository using the assistant. Is that the way?
diff --git a/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__/comment_1_d844cfe5f9907a766e871b64d68966c2._comment b/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__/comment_1_d844cfe5f9907a766e871b64d68966c2._comment
new file mode 100644
index 0000000000..0c70448895
--- /dev/null
+++ b/doc/forum/What_happens_when_in_the_git-annex_assistant_you___34__Add_another_local_repository__34___on_an_existing_repository__63__/comment_1_d844cfe5f9907a766e871b64d68966c2._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T19:03:30Z"
+ content="""
+Sure, you can use that menu item. If you try it out and enter in the path of a repository, you'll see that it offers to either let you combine the two repositories together, or leave them as two unconnected repositories with different files managed by the assistant.
+"""]]
diff --git a/doc/forum/__91__NEED_HELP__93___manual_ssh_remote_setup_with_shared_key/comment_1_811cab17410ba6e07ae7af3249cd98df._comment b/doc/forum/__91__NEED_HELP__93___manual_ssh_remote_setup_with_shared_key/comment_1_811cab17410ba6e07ae7af3249cd98df._comment
new file mode 100644
index 0000000000..7a6eafa7a7
--- /dev/null
+++ b/doc/forum/__91__NEED_HELP__93___manual_ssh_remote_setup_with_shared_key/comment_1_811cab17410ba6e07ae7af3249cd98df._comment
@@ -0,0 +1,14 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T19:28:00Z"
+ content="""
+Sorry for the delay getting to this post.
+
+The lack of jabber support on Windows makes this a bit hard to set up. You instead need to make a git repository some place that both the Windows and Linux machines can both connect to. Once git-annex on both systems is syncing with that common git repository, the Windows system will learn about the encrypted remotes you have set up, and then `git annex enableremote` will be able to use them with no problem.
+
+Of course, if you don't trust your ssh server where you already made an encrypted remote, you may not want to store a un-encrypted git repository on it, and since Windows also doesn't support encrypted git repositories yet, you'd be sort of out of luck. (For now; Windows support is being improved.)
+
+OTOH, if you just set up that encrypted rsync remote on the ssh server because the ssh server didn't have git-annex installed on it, you can easily also put a git repository on the ssh server, and the combination will be enough to let you sync between the 2 machines.
+"""]]
diff --git a/doc/forum/alternativeto.net___34__Like__34__.mdwn b/doc/forum/alternativeto.net___34__Like__34__.mdwn
new file mode 100644
index 0000000000..e725950218
--- /dev/null
+++ b/doc/forum/alternativeto.net___34__Like__34__.mdwn
@@ -0,0 +1,3 @@
+When I went to alternativeto.net I noticed that SpiderOak is a featured application. I decided to search git-annex and see how "Like"-ed it is in comparison... there were 0 "Like"-s.
+
+I suggest going to http://alternativeto.net/software/git-annex/ and "Like" git-annex.
diff --git a/doc/forum/do_not_use_git-annex_inside_your_Dropbox/comment_1_5a1dc9da6e6861829e321446ec7991ee._comment b/doc/forum/do_not_use_git-annex_inside_your_Dropbox/comment_1_5a1dc9da6e6861829e321446ec7991ee._comment
new file mode 100644
index 0000000000..d5da4f0005
--- /dev/null
+++ b/doc/forum/do_not_use_git-annex_inside_your_Dropbox/comment_1_5a1dc9da6e6861829e321446ec7991ee._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="sascha"
+ ip="2a02:8108:5c0:3ec:615a:1ac3:c7b9:a3a9"
+ subject="so how can i keep in sync a dropbox subfolder with a usbdrive"
+ date="2014-01-24T04:32:38Z"
+ content="""
+my usecase is i want to be able to be working on other computers on files that i have on my thumb-usb-drive. Back home i want to sync changes back to the subfolder of my local Dropbox-directory. Any suggestions?
+"""]]
diff --git a/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_2_b25ca7520ff7e339ec887a379d5100ee._comment b/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_2_b25ca7520ff7e339ec887a379d5100ee._comment
new file mode 100644
index 0000000000..c0a13cfa46
--- /dev/null
+++ b/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_2_b25ca7520ff7e339ec887a379d5100ee._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawmNvX8PQVP5sLzQ78sKpB6VeH3Fu8HvZ5g"
+ nickname="Jeff"
+ subject="comment 2"
+ date="2014-01-26T04:29:09Z"
+ content="""
+I've actually been having a pretty tough time with it. Could you point me in the right direction? There's not any Haskell infrastructure on Arch ARM yet so I'd either be compiling the whole Haskell Platform or cross-compiling on x86_64 right?
+Thanks
+Jeff
+"""]]
diff --git a/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_3_eda0e90c1285396b1ab20ecc04ea6e29._comment b/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_3_eda0e90c1285396b1ab20ecc04ea6e29._comment
new file mode 100644
index 0000000000..5c8f96ac32
--- /dev/null
+++ b/doc/forum/git-annex_on_archlinuxarm__44___armv6/comment_3_eda0e90c1285396b1ab20ecc04ea6e29._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.46"
+ subject="comment 3"
+ date="2014-01-26T17:59:52Z"
+ content="""
+Well, yes, the first step will be getting a ghc for the architecture, and then it's just a matter of following [[install/cabal]]
+"""]]
diff --git a/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied.mdwn b/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied.mdwn
new file mode 100644
index 0000000000..3bb2fe1768
--- /dev/null
+++ b/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied.mdwn
@@ -0,0 +1,59 @@
+I just spend an hour to understand why the following command did not do anything:
+
+ $ git annex copy --to someremote SomeDirectory
+
+With SomeDirectory containing a lot of file that are not in the someremote repository.
+I just realized that the annex from which I run the command did not contain those files either.
+
+I then did
+
+ $ git annex get SomeDirectory
+
+So that now the git annex copy command correctly copies the files to the someremote remote.
+
+I hope I won't fall into that trap again, but I think it is very annoying not to know why nothing happened.
+
+Wouldn't it be great if the git annex copy command would indicate why some file are not copied, like:
+
+ $ git annex copy --to someremote SomeDirectory
+ Cannot copy SomeFile1 since it is not present in here, (hint: run git annex get first)
+ Cannot copy SomeFile2 since it is not present in here, (hint: run git annex get first)
+ Cannot copy SomeFile3 since it is not present in here, (hint: run git annex get first)
+ ...
+
+May be this kind of information could be provided if the verbose flag is set.
+
+Another awesome (totally subjectively speaking) way of doing it could be to get the file before copying it
+
+ $ git annex copy --to someremote SomeDirectory
+ Cannot copy SomeFile1 since it is not present in here, attempting getting it first
+ get SomeFile1 (from someotherremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+ copy SomeFile1 (checking someremote...) (to someremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+ Cannot copy SomeFile2 since it is not present in here, attempting getting it first
+ get SomeFile2 (from someotherremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+ copy SomeFile2 (checking someremote...) (to someremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+ Cannot copy SomeFile3 since it is not present in here, attempting getting it first
+ get SomeFile3 (from someotherremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+ copy SomeFile3 (checking someremote...) (to someremote...)
+ SHA256E-s109353088--71734pq1p4qo6qs1p156r48s2290q7p61p1658029p103591nrs1rr708s064p59
+ 12,615,808 100% 161.27kB/s 0:01:16 (xfr#1, to-chk=0/1)
+ ok
+
+We could also specify from which remote to get the file with
+
+ $ git annex copy --to someremote --from someotherremote SomeDirectory
diff --git a/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied/comment_1_75445fc0e01ee99bae1c1f5a60e314bc._comment b/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied/comment_1_75445fc0e01ee99bae1c1f5a60e314bc._comment
new file mode 100644
index 0000000000..15373be70d
--- /dev/null
+++ b/doc/forum/git_annex_copy_more_informative_about_why_some_files_are_not_copied/comment_1_75445fc0e01ee99bae1c1f5a60e314bc._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 1"
+ date="2014-02-02T21:13:21Z"
+ content="""
+I think that this behavior of git-annex is quite useful once you get used to it. It can sometimes trip up new users, but new users would not know about some --explain switch that made it say why it skipped each file. So, I consider this a documentation issue, and I've added a section to the walkthrough to help users learn about it:
+
+
+
+As far as copy --from --to, it has been suggested before; I think there is even a todo about it somewhere, but such remote-to-remote transfers are expensive and I would hope it would not normally be used.
+"""]]
diff --git a/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes.mdwn b/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes.mdwn
new file mode 100644
index 0000000000..cab2ec0c6b
--- /dev/null
+++ b/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes.mdwn
@@ -0,0 +1,5 @@
+I have created two git-annexes (one on my laptop and one on my work pc) The are using nearly the same files with some files existing only on the pc but not on the laptop as they are too large for the laptop. How do I get the two into sync. I found the manual in the tips section but that will create normal git-annexes with all files linked only. However, I would like to have my exiting file structure unchanged (the way the assistant does it by default)
+
+any ideas?
+
+Gregor
diff --git a/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes/comment_1_7bd0edaf2352293678f0942aaa885d13._comment b/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes/comment_1_7bd0edaf2352293678f0942aaa885d13._comment
new file mode 100644
index 0000000000..4b3b095c33
--- /dev/null
+++ b/doc/forum/howto_to_link_to_existing_direct_mode_git-annexes/comment_1_7bd0edaf2352293678f0942aaa885d13._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="71.80.94.56"
+ subject="comment 1"
+ date="2014-02-07T19:11:00Z"
+ content="""
+The webapp will help you do this, go to Add Another Repository -> Share With Your Other Devices.
+"""]]
diff --git a/doc/forum/ssh__95__exchange__95__identification:_read:_Connection_reset_by_peer/comment_3_9b1911ae6468d09dae74ab1a60d2757b._comment b/doc/forum/ssh__95__exchange__95__identification:_read:_Connection_reset_by_peer/comment_3_9b1911ae6468d09dae74ab1a60d2757b._comment
new file mode 100644
index 0000000000..59f0f9f96f
--- /dev/null
+++ b/doc/forum/ssh__95__exchange__95__identification:_read:_Connection_reset_by_peer/comment_3_9b1911ae6468d09dae74ab1a60d2757b._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnPgn611P6ym5yyL0BS8rUzO0_ZKRldMt0"
+ nickname="Samuel"
+ subject="What are those ?"
+ date="2014-01-31T07:37:49Z"
+ content="""
+Hi,
+
+Could you please indicate what other means of file encryption systems you have in mind?
+
+The others I know are at a partition level (cryptsetup, LUKS) and are less pratical to setup than a simple encfs.
+"""]]
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index 4f802f4e38..4e672f6089 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -23,7 +23,7 @@ revision control.
When a file is annexed, its content is moved into a key-value store, and
a symlink is made that points to the content. These symlinks are checked into
-git and versioned like regular files. You can move them around, delete
+git and versioned like regular files. You can move them around, delete
them, and so on. Pushing to another git repository will make git-annex
there aware of the annexed file, and it can be used to retrieve its
content from the key-value store.
@@ -54,7 +54,7 @@ content from the key-value store.
# COMMONLY USED COMMANDS
-Like many git commands, git-annex can be passed a path that
+Like many git commands, git-annex can be passed a path that
is either a file or a directory. In the latter case it acts on all relevant
files in the directory. When no path is specified, most git-annex commands
default to acting on all relevant files in the current directory (and
@@ -78,7 +78,7 @@ subdirectories).
* `drop [path ...]`
- Drops the content of annexed files from this repository.
+ Drops the content of annexed files from this repository.
git-annex will refuse to drop content if it cannot verify it is
safe to do so. This can be overridden with the `--force` switch.
@@ -86,7 +86,7 @@ subdirectories).
To drop content from a remote, specify `--from`.
* `move [path ...]`
-
+
When used with the `--from` option, moves the content of annexed files
from the specified repository to the current one.
@@ -111,13 +111,13 @@ subdirectories).
Similar to `git status --short`, displays the status of the files in the
working tree. Shows files that are not checked into git, files that
- have been deleted, and files that have been modified.
- Particulary useful in direct mode.
+ have been deleted, and files that have been modified.
+ Particularly useful in direct mode.
* `unlock [path ...]`
Normally, the content of annexed files is protected from being changed.
- Unlocking a annexed file allows it to be modified. This replaces the
+ Unlocking an annexed file allows it to be modified. This replaces the
symlink for each specified file with a copy of the file's content.
You can then modify it and `git annex add` (or `git commit`) to inject
it back into the annex.
@@ -139,25 +139,29 @@ subdirectories).
the default is to sync with all remotes. Or specify `--fast` to sync with
the remotes with the lowest annex-cost value.
- The sync process involves first committing all local changes
+ The sync process involves first committing all local changes,
then fetching and merging the `synced/master` and the `git-annex` branch
- from the remote repositories and finally pushing the changes back to
+ from the remote repositories, and finally pushing the changes back to
those branches on the remote repositories. You can use standard git
commands to do each of those steps by hand, or if you don't want to
worry about the details, you can use sync.
- Merge conflicts are automatically resolved by sync. When two conflicting
+ Merge conflicts are automatically handled by sync. When two conflicting
versions of a file have been committed, both will be added to the tree,
under different filenames. For example, file "foo" would be replaced
with "foo.somekey" and "foo.otherkey".
Note that syncing with a remote will not update the remote's working
tree with changes made to the local repository. However, those changes
- are pushed to the remote, so can be merged into its working tree
+ are pushed to the remote, so they can be merged into its working tree
by running "git annex sync" on the remote.
- Note that sync does not transfer any file contents from or to the remote
- repositories.
+ With the `--content` option, the contents of annexed files in the work
+ tree will also be uploaded and downloaded from remotes. By default,
+ this tries to get each annexed file that the local repository does not
+ yet have, and then copies each file to every remote that it is syncing with.
+ This behavior can be overridden by configuring the preferred content of
+ a repository. See see PREFERRED CONTENT below.
* `merge`
@@ -212,7 +216,7 @@ subdirectories).
addurl can be used both to add new files, or to add urls to existing files.
When quvi is installed, urls are automatically tested to see if they
- are on a video hosting site, and the video is downloaded instead.
+ point to a video hosting site, and the video is downloaded instead.
* `rmurl file url`
@@ -221,7 +225,7 @@ subdirectories).
* `import [path ...]`
Moves files from somewhere outside the git working copy, and adds them to
- the annex. Individual files to import can be specified.
+ the annex. Individual files to import can be specified.
If a directory is specified, the entire directory is imported.
git annex import /media/camera/DCIM/*
@@ -285,7 +289,7 @@ subdirectories).
files that it does not match will instead be added with `git add`.
To not daemonize, run with `--foreground` ; to stop a running daemon,
- run with `--stop`
+ run with `--stop`.
* `assistant`
@@ -293,7 +297,7 @@ subdirectories).
Typically started at boot, or when you log in.
With the `--autostart` option, the assistant is started in any repositories
- it has created. These are listed in `~/.config/git-annex/autostart`
+ it has created. These are listed in `~/.config/git-annex/autostart`.
* `webapp`
@@ -319,7 +323,7 @@ subdirectories).
It's useful, but not mandatory, to initialize each new clone
of a repository with its own description. If you don't provide one,
- one will be generated.
+ one will be generated using the username, hostname and the path.
* `describe repository description`
@@ -331,7 +335,7 @@ subdirectories).
* `initremote name [param=value ...]`
- Creates a new special remote, and adds it to `.git/config`.
+ Creates a new special remote, and adds it to `.git/config`.
The remote's configuration is specified by the parameters. Different
types of special remotes need different configuration values. The
@@ -340,7 +344,7 @@ subdirectories).
All special remotes support encryption. You can either specify
`encryption=none` to disable encryption, or specify
`encryption=hybrid keyid=$keyid ...` to specify a GPG key id (or an email
- address associated with a key.)
+ address associated with a key).
There are actually three schemes that can be used for management of the
encryption keys. When using the encryption=hybrid scheme, additional
@@ -368,7 +372,7 @@ subdirectories).
which may be a different repository than the one in which it was
originally created with the initremote command.
- The name of the remote is the same name used when originally
+ The name of the remote is the same name used when originally
creating that remote with "initremote". Run "git annex enableremote"
with no parameters to get a list of special remote names.
@@ -381,7 +385,7 @@ subdirectories).
the as the encryption scheme cannot be changed once a special remote
has been created.)
- The GPG keys that an encrypted special remote is encrypted to can be
+ The GPG keys that an encrypted special remote is encrypted with can be
changed using the keyid+= and keyid-= parameters. These respectively
add and remove keys from the list. However, note that removing a key
does NOT necessarily prevent the key's owner from accessing data
@@ -399,6 +403,20 @@ subdirectories).
keyid+= and keyid-= with such remotes should be used with care, and
make little sense except in cases like the revoked key example above.
+* `numcopies [N]`
+
+ Tells git-annex how many copies it should preserve of files, over all
+ repositories. The default is 1.
+
+ Run without a number to get the current value.
+
+ When git-annex is asked to drop a file, it first verifies that the
+ required number of copies can be satisfied amoung all the other
+ repositories that have a copy of the file.
+
+ This can be overridden on a per-file basis by the annex.numcopies setting
+ in .gitattributes files.
+
* `trust [repository ...]`
Records that a repository is trusted to not unexpectedly lose
@@ -417,7 +435,7 @@ subdirectories).
* `dead [repository ...]`
- Indicates that the repository has been irretrevably lost.
+ Indicates that the repository has been irretrievably lost.
(To undo, use semitrust.)
* `group repository groupname`
@@ -601,7 +619,7 @@ subdirectories).
finds files in the current directory and its subdirectories.
By default, only lists annexed files whose content is currently present.
- This can be changed by specifying file matching options. To list all
+ This can be changed by specifying matching options. To list all
annexed files, present or not, specify `--include "*"`. To list all
annexed files whose content is not present, specify `--not --in=here`
@@ -632,7 +650,7 @@ subdirectories).
`--since`, `--after`, `--until`, `--before`, and `--max-count` can be specified.
They are passed through to git log. For example, `--since "1 month ago"`
- To generate output suitable for the gource visualisation program,
+ To generate output suitable for the gource visualization program,
specify `--gource`.
* `info [directory ...]`
@@ -643,7 +661,7 @@ subdirectories).
To only show the data that can be gathered quickly, use `--fast`.
When a directory is specified, shows a differently formatted info
- display for that directory. In this mode, all of the file matching
+ display for that directory. In this mode, all of the matching
options can be used to filter the files that will be included in
the information.
@@ -652,6 +670,7 @@ subdirectories).
Then run:
git annex info --fast . --not --in here
+
* `version`
Shows the version of git-annex, as well as repository version information.
@@ -757,7 +776,7 @@ subdirectories).
For example, the location a key's value is stored (in indirect mode)
can be looked up by running:
-
+
git annex examinekey --format='.git/annex/objects/${hashdirmixed}${key}/${key}'
* `fromkey key file`
@@ -773,10 +792,6 @@ subdirectories).
This can be used to drop content for arbitrary keys, which do not need
to have a file in the git repository pointing at them.
- Example:
-
- git annex dropkey SHA1-s10-7da006579dd64330eb2456001fd01948430572f2
-
* `transferkey`
This plumbing-level command is used to request a single key be
@@ -803,6 +818,8 @@ subdirectories).
This runs git-annex's built-in test suite.
+ There are several parameters, provided by Haskell's tasty test framework.
+
* `xmppgit`
This command is used internally to perform git pulls over XMPP.
@@ -817,13 +834,13 @@ subdirectories).
* `--fast`
- Enables less expensive, but also less thorough versions of some commands.
+ Enable less expensive, but also less thorough versions of some commands.
What is avoided depends on the command.
* `--auto`
- Enables automatic mode. Commands that get, drop, or move file contents
- will only do so when needed to help satisfy the setting of annex.numcopies,
+ Enable automatic mode. Commands that get, drop, or move file contents
+ will only do so when needed to help satisfy the setting of numcopies,
and preferred content configuration.
* `--all`
@@ -839,6 +856,10 @@ subdirectories).
Operate on all data that has been determined to be unused by
a previous run of `git-annex unused`.
+* `--key=key`
+
+ Operate on only the specified key.
+
* `--quiet`
Avoid the default verbose display of what is done; only show errors
@@ -852,8 +873,8 @@ subdirectories).
Rather than the normal output, generate JSON. This is intended to be
parsed by programs that use git-annex. Each line of output is a JSON
- object. Note that json output is only usable with some git-annex commands,
- like info and find.
+ object. Note that JSON output is only usable with some git-annex commands,
+ like info, find, and whereis.
* `--debug`
@@ -878,8 +899,8 @@ subdirectories).
* `--numcopies=n`
- Overrides the `annex.numcopies` setting, forcing git-annex to ensure the
- specified number of copies exist.
+ Overrides the numcopies setting, forcing git-annex to ensure the
+ specified number of copies exist.
Note that setting numcopies to 0 is very unsafe.
@@ -891,7 +912,7 @@ subdirectories).
Note that git-annex may continue running a little past the specified
time limit, in order to finish processing a file.
- Also, note that if the time limit prevents git-annex from doing all it
+ Also, note that if the time limit prevents git-annex from doing all it
was asked to, it will exit with a special code, 101.
* `--trust=repository`
@@ -912,7 +933,7 @@ subdirectories).
Be careful using this, especially if you or someone else might have recently
removed a file from Glacier. If you try to drop the only other copy of the
- file, and this switch is enabled, you could lose data!
+ file, and this switch is enabled, you could lose data!
* `--backend=name`
@@ -937,9 +958,9 @@ subdirectories).
* `-c name=value`
- Used to override git configuration settings. May be specified multiple times.
+ Overrides git configuration settings. May be specified multiple times.
-# FILE MATCHING OPTIONS
+# MATCHING OPTIONS
These options can all be specified multiple times, and can be combined to
limit which files git-annex acts on.
@@ -959,6 +980,8 @@ file contents are present at either of two repositories.
--exclude='*.mp3' --exclude='subdir/*'
+ Note that this will not match anything when using --all or --unused.
+
* `--include=glob`
Skips files not matching the glob pattern. (Same as `--not --exclude`.)
@@ -966,6 +989,8 @@ file contents are present at either of two repositories.
--include='*.mp3' --or --include='*.ogg'
+ Note that this will not skip anything when using --all or --unused.
+
* `--in=repository`
Matches only files that git-annex believes have their contents present
@@ -976,6 +1001,19 @@ file contents are present at either of two repositories.
or the UUID or description of a repository. For the current repository,
use `--in=here`
+* `--in=repository@{date}`
+
+ Matches files currently in the work tree whose content was present in
+ the repository on the given date.
+
+ The date is specified in the same syntax documented in
+ gitrevisions(7). Note that this uses the reflog, so dates far in the
+ past cannot be queried.
+
+ For example, you might need to run `git annex drop .` to temporarily
+ free up disk space. The next day, you can get back the files you dropped
+ using `git annex get . --in=here@{yesterday}`
+
* `--copies=number`
Matches only files that git-annex believes to have the specified number
@@ -997,6 +1035,17 @@ file contents are present at either of two repositories.
copies, on remotes in the specified group. For example,
`--copies=archive:2`
+* `--lackingcopies=number`
+
+ Matches only files that git-annex believes need the specified number or
+ more additional copies to be made in order to satisfy their numcopies
+ settings.
+
+* `--approxlackingcopies=number`
+
+ Like lackingcopies, but does not look at .gitattributes annex.numcopies
+ settings. This makes it significantly faster.
+
* `--inbackend=name`
Matches only files whose content is stored using the specified key-value
@@ -1020,35 +1069,39 @@ file contents are present at either of two repositories.
Matches files that the preferred content settings for the repository
make it want to get. Note that this will match even files that are
- already present, unless limited with eg, `--not --in .`
+ already present, unless limited with e.g., `--not --in .`
+
+ Note that this will not match anything when using --all or --unused.
* `--want-drop`
Matches files that the preferred content settings for the repository
make it want to drop. Note that this will match even files that have
- already been dropped, unless limited with eg, `--in .`
+ already been dropped, unless limited with e.g., `--in .`
+
+ Note that this will not match anything when using --all or --unused.
* `--not`
- Inverts the next file matching option. For example, to only act on
+ Inverts the next matching option. For example, to only act on
files with less than 3 copies, use `--not --copies=3`
* `--and`
- Requires that both the previous and the next file matching option matches.
+ Requires that both the previous and the next matching option matches.
The default.
* `--or`
- Requires that either the previous, or the next file matching option matches.
+ Requires that either the previous, or the next matching option matches.
* `-(`
- Opens a group of file matching options.
+ Opens a group of matching options.
* `-)`
- Closes a group of file matching options.
+ Closes a group of matching options.
# PREFERRED CONTENT
@@ -1058,7 +1111,7 @@ using `git annex vicfg` or `git annex wanted`.
They are used by the `--auto` option, and by the git-annex assistant.
The preferred content settings are similar, but not identical to
-the file matching options specified above, just without the dashes.
+the matching options specified above, just without the dashes.
For example:
exclude=archive/* and (include=*.mp3 or smallerthan=1mb)
@@ -1076,7 +1129,7 @@ built-in preferred content expression developed for that group.
The git-annex assistant daemon can be configured to run scheduled jobs.
This is similar to cron and anacron (and you can use them if you prefer),
but has the advantage of being integrated into git-annex, and so being able
-to eg, fsck a repository on a removable drive when the drive gets
+to e.g., fsck a repository on a removable drive when the drive gets
connected.
The scheduled jobs can be configured using `git annex vicfg` or
@@ -1104,12 +1157,6 @@ Here are all the supported configuration settings.
A unique UUID for this repository (automatically set).
-* `annex.numcopies`
-
- Number of copies of files to keep across all repositories. (default: 1)
-
- Note that setting numcopies to 0 is very unsafe.
-
* `annex.backends`
Space-separated list of names of the key-value backends to use.
@@ -1138,6 +1185,17 @@ Here are all the supported configuration settings.
annex.largefiles = largerthan=100kb and not (include=*.c or include=*.h)
+* `annex.numcopies`
+
+ This is a deprecated setting. You should instead use the
+ `git annex numcopies` command to configure how many copies of files
+ are kept acros all repositories.
+
+ This config setting is only looked at when `git annex numcopies` has
+ never been configured.
+
+ Note that setting numcopies to 0 is very unsafe.
+
* `annex.queuesize`
git-annex builds a queue of git commands, in order to combine similar
@@ -1158,14 +1216,15 @@ Here are all the supported configuration settings.
* `annex.bloomaccuracy`
Adjusts the accuracy of the bloom filter used by
- `git annex unused`. The default accuracy is 1000 --
+ `git annex unused`. The default accuracy is 1000 --
1 unused file out of 1000 will be missed by `git annex unused`. Increasing
the accuracy will make `git annex unused` consume more memory;
run `git annex info` for memory usage numbers.
* `annex.sshcaching`
- By default, git-annex caches ssh connections
+ By default, git-annex caches ssh connections using ssh's
+ ControlMaster and ControlPersist settings
(if built using a new enough ssh). To disable this, set to `false`.
* `annex.alwayscommit`
@@ -1183,6 +1242,19 @@ Here are all the supported configuration settings.
to close it. On Mac OSX, when not using direct mode this defaults to
1 second, to work around a bad interaction with software there.
+* `annex.expireunused`
+
+ Controls what the assistant does about unused file contents
+ that are stored in the repository.
+
+ The default is `false`, which causes
+ all old and unused file contents to be retained, unless the assistant
+ is able to move them to some other repository (such as a backup repository).
+
+ Can be set to a time specification, like "7d" or "1m", and then
+ file contents that have been known to be unused for a week or a
+ month will be deleted.
+
* `annex.fscknudge`
When set to false, prevents the webapp from reminding you when using
@@ -1238,7 +1310,7 @@ Here are all the supported configuration settings.
* `remote..annex-cost-command`
If set, the command is run, and the number it outputs is used as the cost.
- This allows varying the cost based on eg, the current network. The
+ This allows varying the cost based on e.g., the current network. The
cost-command can be any shell command line.
* `remote..annex-start-command`
@@ -1297,11 +1369,16 @@ Here are all the supported configuration settings.
configured by the trust and untrust commands. The value can be any of
"trusted", "semitrusted" or "untrusted".
-* `remote..availability`
+* `remote..annex-availability`
Can be used to tell git-annex whether a remote is LocallyAvailable
or GloballyAvailable. Normally, git-annex determines this automatically.
+* `remote..annex-bare`
+
+ Can be used to tell git-annex if a remote is a bare repository
+ or not. Normally, git-annex determines this automatically.
+
* `remote..annex-ssh-options`
Options to use when using ssh to talk to this remote.
@@ -1312,6 +1389,21 @@ Here are all the supported configuration settings.
to or from this remote. For example, to force ipv6, and limit
the bandwidth to 100Kbyte/s, set it to `-6 --bwlimit 100`
+* `remote..annex-rsync-upload-options`
+
+ Options to use when using rsync to upload a file to a remote.
+
+ These options are passed after other applicable rsync options,
+ so can be used to override them. For example, to limit upload bandwidth
+ to 10Kbye/s, set `--bwlimit 10`.
+
+* `remote..annex-rsync-download-options`
+
+ Options to use when using rsync to download a file from a remote.
+
+ These options are passed after other applicable rsync options,
+ so can be used to override them.
+
* `remote..annex-rsync-transport`
The remote shell to use to connect to the rsync remote. Possible
@@ -1335,11 +1427,12 @@ Here are all the supported configuration settings.
precedence over the default GnuPG configuration, which is otherwise
used.)
-* `annex.ssh-options`, `annex.rsync-options`, `annex.bup-split-options`,
- `annex.gnupg-options`
+* `annex.ssh-options`, `annex.rsync-options`,
+ `annex.rsync-upload-options`, `annex.rsync-download-options`,
+ `annex.bup-split-options`, `annex.gnupg-options`
- Default ssh, rsync, wget/curl, bup, and GnuPG options to use if a
- remote does not have specific options.
+ Default options to use if a remote does not have more specific options
+ as described above.
* `annex.web-options`
@@ -1369,8 +1462,16 @@ Here are all the supported configuration settings.
In the command line, %url is replaced with the url to download,
and %file is replaced with the file that it should be saved to.
- Note that both these values will automatically be quoted, since
- the command is run in a shell.
+
+* `annex.secure-erase-command`
+
+ This can be set to a command that should be run whenever git-annex
+ removes the content of a file from the repository.
+
+ In the command line, %file is replaced with the file that should be
+ erased.
+
+ For example, to use the wipe command, set it to `wipe -f %file`
* `remote..rsyncurl`
@@ -1423,7 +1524,7 @@ Here are all the supported configuration settings.
It is set to "true" if this is a gcrypt remote.
If the gcrypt remote is accessible over ssh and has git-annex-shell
- available to manage it, it's set to "shell"
+ available to manage it, it's set to "shell".
* `remote..hooktype`, `remote..externaltype`
@@ -1443,10 +1544,12 @@ but the SHA256E backend for ogg files:
The numcopies setting can also be configured on a per-file-type basis via
the `annex.numcopies` attribute in `.gitattributes` files. This overrides
-any value set using `annex.numcopies` in `.git/config`.
-For example, this makes two copies be needed for wav files:
+other numcopies settings.
+For example, this makes two copies be needed for wav files and 3 copies
+for flac files:
*.wav annex.numcopies=2
+ *.flac annex.numcopies=3
Note that setting numcopies to 0 is very unsafe.
@@ -1466,11 +1569,11 @@ to start the git-annex assistant in.
# SEE ALSO
-Most of git-annex's documentation is available on its web site,
+Most of git-annex's documentation is available on its web site,
If git-annex is installed from a package, a copy of its documentation
-should be included, in, for example, `/usr/share/doc/git-annex/`
+should be included, in, for example, `/usr/share/doc/git-annex/`.
# AUTHOR
@@ -1478,4 +1581,4 @@ Joey Hess
-Warning: Automatically converted into a man page by mdwn2man. Edit with care
+Warning: Automatically converted into a man page by mdwn2man. Edit with care.
diff --git a/doc/how_it_works.mdwn b/doc/how_it_works.mdwn
index 0acf205652..69e5256e3a 100644
--- a/doc/how_it_works.mdwn
+++ b/doc/how_it_works.mdwn
@@ -6,13 +6,14 @@ You do not need to read this page to get started with using git-annex. The
Still reading? Ok. Git's man page calls it "a stupid content
tracker". With git-annex, git is instead "a stupid filename and metadata"
-tracker. The contents of large files are not stored in git, only the
+tracker. The contents of annexed files are not stored in git, only the
names of the files and some other metadata remain there.
The contents of the files are kept by git-annex in a distributed key/value
store consisting of every clone of a given git repository. That's a fancy
way to say that git-annex stores the actual file content somewhere under
-`.git/annex/`. (See [[internals]] for details.)
+`.git/annex/`. (See [[internals]] for details and note that in
+[[direct_mode]] the file contents are left in the work tree.)
That was the values; what about the keys? Well, a key is calculated for a
given file when it's first added into git-annex. Normally this uses a hash
diff --git a/doc/how_it_works/comment_2_2a8ce5859040d815e6234fc18f5f1961._comment b/doc/how_it_works/comment_2_2a8ce5859040d815e6234fc18f5f1961._comment
new file mode 100644
index 0000000000..cc16f465d0
--- /dev/null
+++ b/doc/how_it_works/comment_2_2a8ce5859040d815e6234fc18f5f1961._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawm4cjowB3PaZP00vEr255d1GdUBikE9Qdg"
+ nickname="Matthew"
+ subject="clarification about what is moved / stored and where"
+ date="2014-02-10T12:53:44Z"
+ content="""
+Just to support Nigel's comment; it's good to be precise and clear about what happens to the files from the start.
+I've sent a similar suggestion to the mailing list.
+
+"""]]
diff --git a/doc/install/Windows.mdwn b/doc/install/Windows.mdwn
index 3a8c4e72a0..66df7921e3 100644
--- a/doc/install/Windows.mdwn
+++ b/doc/install/Windows.mdwn
@@ -1,18 +1,18 @@
-git-annex has recently been ported to Windows!
+git-annex now does Windows!
* First, [install git](http://git-scm.com/downloads)
* Then, [install git-annex](https://downloads.kitenet.net/git-annex/windows/current/)
-This port is in an early state. While it works well enough to use
-git-annex, many things will not work. See [[todo/windows_support]] for
-current status.
+This port is now in reasonably good shape for command-line use of
+git-annex. The assistant and webapp are still in an early state.
+See [[todo/windows_support]] for current status.
The autobuilder is not currently able to run the test suite, so
testing git-annex on Windows is up to you! To check that the build of
git-annex works in your Windows system, you are encouraged to run the test
suite before using git-annex on real data. After installation, run `git
annex test`. There will be a lot of output; the important thing is that it
-should end with "All tests ok".
+should end with "All tests passed".
## autobuilds
diff --git a/doc/install/fromscratch.mdwn b/doc/install/fromscratch.mdwn
index 7f78da5378..2c8bf4b714 100644
--- a/doc/install/fromscratch.mdwn
+++ b/doc/install/fromscratch.mdwn
@@ -25,9 +25,9 @@ quite a lot.
* [extensible-exceptions](http://hackage.haskell.org/package/extensible-exceptions)
* [feed](http://hackage.haskell.org/package/feed)
* [async](http://hackage.haskell.org/package/async)
-* Optional haskell stuff, used by the [[assistant]] and its webapp
* [stm](http://hackage.haskell.org/package/stm)
(version 2.3 or newer)
+* Optional haskell stuff, used by the [[assistant]] and its webapp
* [hinotify](http://hackage.haskell.org/package/hinotify)
(Linux only)
* [dbus](http://hackage.haskell.org/package/dbus)
diff --git a/doc/internals.mdwn b/doc/internals.mdwn
index d95ab3f5ef..1cf0cf5051 100644
--- a/doc/internals.mdwn
+++ b/doc/internals.mdwn
@@ -56,8 +56,11 @@ space and then the description, followed by a timestamp. Example:
e605dca6-446a-11e0-8b2a-002170d25c55 laptop timestamp=1317929189.157237s
26339d22-446b-11e0-9101-002170d25c55 usb disk timestamp=1317929330.769997s
-If there are multiple lines for the same uuid, the one with the most recent
-timestamp wins. git-annex union merges this and other files.
+## `numcopies.log`
+
+Records the global numcopies setting.
+
+The file format is simply a timestamp followed by a number.
## `remote.log`
diff --git a/doc/internals/hashing/comment_1_9153e4f4f9335e524cf1b96a51bef41f._comment b/doc/internals/hashing/comment_1_9153e4f4f9335e524cf1b96a51bef41f._comment
new file mode 100644
index 0000000000..075bedfcec
--- /dev/null
+++ b/doc/internals/hashing/comment_1_9153e4f4f9335e524cf1b96a51bef41f._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnlotDRSLW2JVXY3SLSwhrcHteqUHhTtoY"
+ nickname="Péter"
+ subject="comment 1"
+ date="2014-01-31T00:45:47Z"
+ content="""
+The correct old hash value for the empty file SHA256E-s0--e3b0c44298fc1c149afbf4c8996fb92427ae41e4649b934ca495991b7852b855 is pX/ZJ .
+
+The text describes the old hash value computation incorrectly, because it doesn't mention that 1 bit is skipped between each group of 5 bits. See the sample implementation in display_32bits_as_dir in https://github.com/joeyh/git-annex/blob/master/Locations.hs
+"""]]
diff --git a/doc/news/version_4.20131106~bpo70+1.mdwn b/doc/news/version_4.20131106~bpo70+1.mdwn
deleted file mode 100644
index b6a28b778b..0000000000
--- a/doc/news/version_4.20131106~bpo70+1.mdwn
+++ /dev/null
@@ -1,19 +0,0 @@
-git-annex 4.20131106~bpo70+1 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
- * Backport is now built against git 1.8.4, also now available in backports.
- * Improve local pairing behavior when two computers both try to start
- the pairing process separately.
- * sync: Work even when the local git repository is new and empty,
- with no master branch.
- * gcrypt, bup: Fix bug that prevented using these special remotes
- with encryption=pubkey.
- * Fix enabling of gcrypt repository accessed over ssh;
- git-annex-shell gcryptsetup had a bug that caused it to fail
- with permission denied.
- * Fix zombie process that occurred when switching between repository
- views in the webapp.
- * map: Work when there are gcrypt remotes.
- * Fix build w/o webapp.
- * Fix exception handling bug that could cause .git/annex/index to be used
- for git commits outside the git-annex branch. Known to affect git-annex
- when used with the git shipped with Ubuntu 13.10."""]]
\ No newline at end of file
diff --git a/doc/news/version_5.20131213.mdwn b/doc/news/version_5.20131213.mdwn
deleted file mode 100644
index d44e08eedc..0000000000
--- a/doc/news/version_5.20131213.mdwn
+++ /dev/null
@@ -1,32 +0,0 @@
-git-annex 5.20131213 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
- * Avoid using git commit in direct mode, since in some situations
- it will read the full contents of files in the tree.
- * assistant: Batch jobs are now run with ionice and nocache, when
- those commands are available.
- * assistant: Run transferkeys as batch jobs.
- * Automatically fix up bad bare repositories created by
- versions 5.20131118 through 5.20131127.
- * rsync special remote: Fix fallback mode for rsync remotes that
- use hashDirMixed. Closes: #[731142](http://bugs.debian.org/731142)
- * copy --from, get --from: When --force is used, ignore the
- location log and always try to get the file from the remote.
- * Deal with box.com changing the url of their webdav endpoint.
- * Android: Fix SRV record lookups for XMPP to use android getprop
- command to find DNS server, since there is no resolv.conf.
- * import: Add --skip-duplicates option.
- * lock: Require --force. Closes: #[731606](http://bugs.debian.org/731606)
- * import: better handling of overwriting an existing file/directory/broken
- link when importing
- * Windows: assistant and webapp work! (very experimental)
- * Windows: Support annex.diskreserve.
- * Fix bad behavior in Firefox, which was caused by an earlier fix to
- bad behavior in Chromium.
- * repair: Improve repair of git-annex index file.
- * repair: Remove damaged git-annex sync branches.
- * status: Ignore new files that are gitignored.
- * Fix direct mode's handling when modifications to non-annexed files
- are pulled from a remote. A bug prevented the files from being updated
- in the work tree, and this caused the modification to be reverted.
- * OSX: Remove ssh and ssh-keygen from dmg as they're included in OSX by
- default."""]]
\ No newline at end of file
diff --git a/doc/news/version_5.20131221.mdwn b/doc/news/version_5.20131221.mdwn
deleted file mode 100644
index 00b73218d0..0000000000
--- a/doc/news/version_5.20131221.mdwn
+++ /dev/null
@@ -1,21 +0,0 @@
-git-annex 5.20131221 released with [[!toggle text="these changes"]]
-[[!toggleable text="""
- * assistant: Fix OSX-specific bug that caused the startup scan to try to
- follow symlinks to other directories, and add their contents to the annex.
- * assistant: Set StrictHostKeyChecking yes when creating ssh remotes,
- and add it to the configuration for any ssh remotes previously created
- by the assistant. This avoids repeated prompts by ssh if the host key
- changes, instead syncing with such a remote will fail. Closes: #[732602](http://bugs.debian.org/732602)
- * Fix test suite to cover lock --force change.
- * Add plumbing-level lookupkey and examinekey commands.
- * find --format: Added hashdirlower, hashdirmixed, keyname, and mtime
- format variables.
- * assistant: Always batch changes found in startup scan.
- * An armel Linux standalone build is now available, which includes the
- webapp.
- * Programs from Linux and OSX standalone builds can now be symlinked
- into a directory in PATH as an alternative installation method, and will
- use readlink to find where the build was unpacked.
- * Include man pages in Linux and OSX standalone builds.
- * Linux standalone build now includes its own glibc and forces the linker to
- use it, to remove dependence on the host glibc."""]]
\ No newline at end of file
diff --git a/doc/news/version_5.20140116/comment_1_a5e85a3258ae8a241674dda4172b3e94._comment b/doc/news/version_5.20140116/comment_1_a5e85a3258ae8a241674dda4172b3e94._comment
new file mode 100644
index 0000000000..172753a768
--- /dev/null
+++ b/doc/news/version_5.20140116/comment_1_a5e85a3258ae8a241674dda4172b3e94._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://launchpad.net/~maestro-alubia"
+ nickname="maestro-alubia"
+ subject="Sources?"
+ date="2014-01-22T19:00:05Z"
+ content="""
+Where can I find the sources tarball? It is not at the usual places http://hackage.haskell.org/package/git-annex or http://hdiff.luite.com/packages/archive/git-annex/
+"""]]
diff --git a/doc/news/version_5.20140116/comment_2_016ef01507edd6baa26c6c9a90f35ed7._comment b/doc/news/version_5.20140116/comment_2_016ef01507edd6baa26c6c9a90f35ed7._comment
new file mode 100644
index 0000000000..07378711dc
--- /dev/null
+++ b/doc/news/version_5.20140116/comment_2_016ef01507edd6baa26c6c9a90f35ed7._comment
@@ -0,0 +1,10 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.249"
+ subject="comment 2"
+ date="2014-01-22T20:25:44Z"
+ content="""
+Something seems to have prevented the upload getting onto hackage. I have re-run the upload in case that helps.
+
+But, you can always get the source by `git clone git://git-annex.branchable.com/` or see the install link in the sidebar.
+"""]]
diff --git a/doc/news/version_5.20140116/comment_3_e4b6899c3b12fc260806ba8d36df6158._comment b/doc/news/version_5.20140116/comment_3_e4b6899c3b12fc260806ba8d36df6158._comment
new file mode 100644
index 0000000000..a88367f29a
--- /dev/null
+++ b/doc/news/version_5.20140116/comment_3_e4b6899c3b12fc260806ba8d36df6158._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://launchpad.net/~maestro-alubia"
+ nickname="maestro-alubia"
+ subject="comment 3"
+ date="2014-01-22T21:20:31Z"
+ content="""
+Thanks, it worked! I needed the source tarball for an updated Gentoo ebuild.
+"""]]
diff --git a/doc/news/version_5.20140127.mdwn b/doc/news/version_5.20140127.mdwn
new file mode 100644
index 0000000000..7c5748f35b
--- /dev/null
+++ b/doc/news/version_5.20140127.mdwn
@@ -0,0 +1,41 @@
+git-annex 5.20140127 released with [[!toggle text="these changes"]]
+[[!toggleable text="""
+ * sync --content: New option that makes the content of annexed files be
+ transferred. Similar to the assistant, this honors any configured
+ preferred content expressions.
+ * Remove --json option from commands not supporting it.
+ * status: Support --json.
+ * list: Fix specifying of files to list.
+ * Allow --all to be mixed with matching options like --copies and --in
+ (but not --include and --exclude).
+ * numcopies: New command, sets global numcopies value that is seen by all
+ clones of a repository.
+ * The annex.numcopies git config setting is deprecated. Once the numcopies
+ command is used to set the global number of copies, any annex.numcopies
+ git configs will be ignored.
+ * assistant: Make the prefs page set the global numcopies.
+ * Add lackingcopies, approxlackingcopies, and unused to
+ preferred content expressions.
+ * Client, transfer, incremental backup, and archive repositories
+ now want to get content that does not yet have enough copies.
+ * Client, transfer, and source repositories now do not want to retain
+ unused file contents.
+ * assistant: Checks daily for unused file contents, and when possible
+ moves them to a repository (such as a backup repository) that
+ wants to retain them.
+ * assistant: annex.expireunused can be configured to cause unused
+ file contents to be deleted after some period of time.
+ * webapp: Nudge user to see if they want to expire old unused file
+ contents when a lot of them seem to be piling up in the repository.
+ * repair: Check git version at run time.
+ * assistant: Run the periodic git gc in batch mode.
+ * added annex.secure-erase-command config option.
+ * Optimise non-bare http remotes; no longer does a 404 to the wrong
+ url every time before trying the right url. Needs annex-bare to be
+ set to false, which is done when initially probing the uuid of a
+ http remote.
+ * webapp: After upgrading a git repository to git-annex, fix
+ bug that made it temporarily not be synced with.
+ * whereis: Support --all.
+ * All commands that support --all also support a --key option,
+ which limits them to acting on a single key."""]]
\ No newline at end of file
diff --git a/doc/news/version_5.20140127/comment_1_776574c242235d9256da287048e38dc0._comment b/doc/news/version_5.20140127/comment_1_776574c242235d9256da287048e38dc0._comment
new file mode 100644
index 0000000000..da9672e19f
--- /dev/null
+++ b/doc/news/version_5.20140127/comment_1_776574c242235d9256da287048e38dc0._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="EskildHustvedt"
+ ip="80.202.103.101"
+ subject="comment 1"
+ date="2014-01-28T19:48:27Z"
+ content="""
+Could you kick the standalone builder? No standalone build for this release yet.
+"""]]
diff --git a/doc/news/version_5.20140127/comment_2_aea5d528f3e0fdc81d0ea83d65f48812._comment b/doc/news/version_5.20140127/comment_2_aea5d528f3e0fdc81d0ea83d65f48812._comment
new file mode 100644
index 0000000000..88a884aa07
--- /dev/null
+++ b/doc/news/version_5.20140127/comment_2_aea5d528f3e0fdc81d0ea83d65f48812._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="209.250.56.199"
+ subject="comment 2"
+ date="2014-01-28T21:51:32Z"
+ content="""
+I forgot to update all the builds for this release, until just now.
+"""]]
diff --git a/doc/not/comment_12_a0ef1a045257659f0f8722e4987e0ccc._comment b/doc/not/comment_12_a0ef1a045257659f0f8722e4987e0ccc._comment
new file mode 100644
index 0000000000..3f9aa2087e
--- /dev/null
+++ b/doc/not/comment_12_a0ef1a045257659f0f8722e4987e0ccc._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkRtPz8CAz_1sBR0Rf-b8OlQQ49v9JxOIE"
+ nickname="John"
+ subject="re: Not an backup"
+ date="2014-02-05T10:45:45Z"
+ content="""
+@joeyh.name But if I set numcopies=2 it won't let me drop the file right? I don't think we are mean to directly modify the archive; but if we do would git-annex detect the corruption and discourage us from dropping the other file?
+"""]]
diff --git a/doc/not/comment_13_c5c20576388f18daba3af913b44fb001._comment b/doc/not/comment_13_c5c20576388f18daba3af913b44fb001._comment
new file mode 100644
index 0000000000..38c96f7073
--- /dev/null
+++ b/doc/not/comment_13_c5c20576388f18daba3af913b44fb001._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 13"
+ date="2014-02-06T17:00:59Z"
+ content="""
+Yes, git-annex ensures your configured [[numcopies|copies]] is met before dropping a file.
+"""]]
diff --git a/doc/preferred_content.mdwn b/doc/preferred_content.mdwn
index 40364011e9..6d1acfb0f3 100644
--- a/doc/preferred_content.mdwn
+++ b/doc/preferred_content.mdwn
@@ -3,20 +3,22 @@ data always exist, and leaves it up to you to use commands like `git annex
get` and `git annex drop` to move the content to the repositories you want
to contain it. But sometimes, it can be good to have more fine-grained
control over which repositories prefer to have which content. Configuring
-this allows `git annex get --auto`, `git annex drop --auto`, etc to do
-smarter things.
+this allows the git-annex assistant as well as
+`git annex get --auto`, `git annex drop --auto`, `git annex sync --content`,
+etc to do smarter things.
Preferred content settings can be edited using `git
annex vicfg`, or viewed and set at the command line with `git annex wanted`.
-Each repository can have its own settings, and other repositories may also
-try to honor those settings. So there's no local `.git/config` setting it.
+Each repository can have its own settings, and other repositories will
+try to honor those settings when interacting with it.
+So there's no local `.git/config` for preferred content settings.
The idea is that you write an expression that files are matched against.
If a file matches, it's preferred to have its content stored in the
repository. If it doesn't, it's preferred to drop its content from
the repository (if there are enough copies elsewhere).
-The expressions are very similar to the file matching options documented
+The expressions are very similar to the matching options documented
on the [[git-annex]] man page. At the command line, you can use those
options in commands like this:
@@ -109,9 +111,9 @@ any repository that can will back it up.)
### client
All content is preferred, unless it's for a file in a "archive" directory,
-which has reached an archive repository.
+which has reached an archive repository, or is unused.
-`((exclude=*/archive/* and exclude=archive/*) or (not (copies=archive:1 or copies=smallarchive:1))) or (not copies=semitrusted+:1)`
+`(((exclude=*/archive/* and exclude=archive/*) or (not (copies=archive:1 or copies=smallarchive:1))) and not unused) or roughlylackingcopies=1`
### transfer
@@ -138,27 +140,27 @@ will be added later.
All content is preferred.
-`include=*`
+`include=* or unused`
### incremental backup
Only prefers content that's not already backed up to another backup
or incremental backup repository.
-`(include=* and (not copies=backup:1) and (not copies=incrementalbackup:1)) or (not copies=semitrusted+:1)`
+`((include=* or unused) and (not copies=backup:1) and (not copies=incrementalbackup:1)) or approxlackingcopies=1`
### small archive
Only prefers content that's located in an "archive" directory, and
only if it's not already been archived somewhere else.
-`((include=*/archive/* or include=archive/*) and not (copies=archive:1 or copies=smallarchive:1)) or (not copies=semitrusted+:1)`
+`((include=*/archive/* or include=archive/*) and not (copies=archive:1 or copies=smallarchive:1)) or approxlackingcopies=1`
### full archive
All content is preferred, unless it's already been archived somewhere else.
-`(not (copies=archive:1 or copies=smallarchive:1)) or (not copies=semitrusted+:1)`
+`(not (copies=archive:1 or copies=smallarchive:1)) or approxlackingcopies=1`
Note that if you want to archive multiple copies (not a bad idea!),
you should instead configure all your archive repositories with a
diff --git a/doc/special_remotes/directory.mdwn b/doc/special_remotes/directory.mdwn
index 4d72e8beee..b79cf75441 100644
--- a/doc/special_remotes/directory.mdwn
+++ b/doc/special_remotes/directory.mdwn
@@ -1,10 +1,12 @@
This special remote type stores file contents in directory.
One use case for this would be if you have a removable drive that
-you want to use it to sneakernet files between systems (possibly with
+you want to use to sneakernet files between systems (possibly with
[[encrypted|encryption]] contents). Just set up both systems to use
the drive's mountpoint as a directory remote.
+Note that directory remotes have a special directory structure
+(by design, the same as the \[[rsync|rsync]] remote).
If you just want two copies of your repository with the files "visible"
in the tree in both, the directory special remote is not what you want.
Instead, you should use a regular `git clone` of your git-annex repository.
@@ -14,6 +16,10 @@ Instead, you should use a regular `git clone` of your git-annex repository.
These parameters can be passed to `git annex initremote` to configure the
remote:
+* `directory` - The path to the directory where the files should be stored
+ for the remote. The directory must already exist. Typically this will
+ be an empty directory, or a directory already used as a directory remote.
+
* `encryption` - One of "none", "hybrid", "shared", or "pubkey".
See [[encryption]].
diff --git a/doc/special_remotes/xmpp.mdwn b/doc/special_remotes/xmpp.mdwn
index 86f6a7c0bc..0f1c93b253 100644
--- a/doc/special_remotes/xmpp.mdwn
+++ b/doc/special_remotes/xmpp.mdwn
@@ -31,7 +31,7 @@ Provider|Status|Type|Notes
[[jabber.org|http://jabber.org]]|Working|[[Isode M-Link|http://www.isode.com/products/m-link.html]]
-|Working|[[Prosody|http://prosody.im/]]|No providers tested.
-|Working|[[Metronome|http://www.lightwitch.org/]]|No providers tested.
--|[[Failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/]]|ejabberd|[[Authentication bug|https://support.process-one.net/browse/EJAB-1632]]: Fixed in debian unstable with version 2.1.10-5
+-|[[Failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/]]|ejabberd|[[Authentication bug|https://support.process-one.net/browse/EJAB-1632]]: Fixed in debian unstable (>= 2.1.10-5) and stable (>=2.1.10-4+deb7u1)
-|[[Failing|http://git-annex.branchable.com/forum/XMPP_authentication_failure/#comment-4ce5aeabd12ca3016290b3d8255f6ef1]]|jabberd14|No further information
"""]]
List of providers: [[http://xmpp.net/]]
diff --git a/doc/sync.mdwn b/doc/sync.mdwn
index 37b2b1b459..0250d2fef0 100644
--- a/doc/sync.mdwn
+++ b/doc/sync.mdwn
@@ -36,3 +36,9 @@ The workflow for using `git annex sync` is simple:
* Run `git annex sync` to save the changes.
* Next time you're working on a different clone of that repository,
run `git annex sync` to update it.
+
+Note that by default, `git annex sync` only synchronises the git
+repositories, but does not transfer the content of annexed files. If you
+want to fully synchronise two repositories content,
+you can use `git annex sync --content`. You can also configure
+[[preferred_content]] settings to make only some content be synced.
diff --git a/doc/sync/comment_10_2cd8ab86f498d6f676f859b552f831eb._comment b/doc/sync/comment_10_2cd8ab86f498d6f676f859b552f831eb._comment
new file mode 100644
index 0000000000..da4d019654
--- /dev/null
+++ b/doc/sync/comment_10_2cd8ab86f498d6f676f859b552f831eb._comment
@@ -0,0 +1,8 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawkI9AR8BqG4RPw_Ov2lnDCJWMuM6WMRobQ"
+ nickname="Dav"
+ subject="Sorry to just be getting back..."
+ date="2014-01-26T22:51:28Z"
+ content="""
+The URLs in question in this case were read-only github https URLs. In any case, my problems are solved by what you've already suggested. I think a less error-sounding response to read-only https repos sounds nice!
+"""]]
diff --git a/doc/tips/Shamir_secret_sharing_and_git-annex.mdwn b/doc/tips/Shamir_secret_sharing_and_git-annex.mdwn
new file mode 100644
index 0000000000..df19f68b8e
--- /dev/null
+++ b/doc/tips/Shamir_secret_sharing_and_git-annex.mdwn
@@ -0,0 +1,21 @@
+Combining git-annex with [Shamir secret sharing](http://en.wikipedia.org/wiki/Shamir%27s_Secret_Sharing)
+is an useful way to securely back up highly sensitive files,
+such as a gpg key or bitcoin wallet.
+
+Shamir secret sharing creates N shares of a file, of which any M can be
+used to reconstitute the original file. Anyone who has less than M shares
+cannot tell anything about the original file, other than its size.
+
+Where git-annex comes in is as a way to manage these shares. They can be
+added to the annex, and then git-annex used to move one share to each clone
+of the repository. Since git-annex keeps track of where each file is
+stored, this can aid later finding the shares again when they're needed, as
+well as making ongoing management of the shares easier.
+
+Note that this conveniece comes at a price: Any attacker who gets a copy
+of the git repository can use it to figure out where the shares are
+located. While this is not a crippling flaw, and can be worked around, it
+needs to be considered when implementing this technique.
+
+Here is an example of this method being used for a ~/.gnupg directory:
+
diff --git a/doc/tips/migrating_two_seperate_disconnected_directories_to_git_annex.mdwn b/doc/tips/migrating_two_seperate_disconnected_directories_to_git_annex.mdwn
index 1209d12173..8f078c78b0 100644
--- a/doc/tips/migrating_two_seperate_disconnected_directories_to_git_annex.mdwn
+++ b/doc/tips/migrating_two_seperate_disconnected_directories_to_git_annex.mdwn
@@ -18,7 +18,7 @@ Start with `marcos`, with the complete directory:
git init
git annex init
git annex add .
- git commit -m"git annex yay"
+ git commit -m "git annex yay"
This will checksum all files and add them to the `git-annex` branch of the git repository. Wait for this process to complete.
diff --git a/doc/tips/setup_a_public_repository_on_a_web_site/comment_3_a6698218f15c598c9b32e0af850133bf._comment b/doc/tips/setup_a_public_repository_on_a_web_site/comment_3_a6698218f15c598c9b32e0af850133bf._comment
new file mode 100644
index 0000000000..05894c73e9
--- /dev/null
+++ b/doc/tips/setup_a_public_repository_on_a_web_site/comment_3_a6698218f15c598c9b32e0af850133bf._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawnRRUUZo3W7pAoRoST8P_l0PtUBhvYuzDg"
+ nickname="Lyle"
+ subject="web storage"
+ date="2014-01-17T22:59:27Z"
+ content="""
+Is there a low cost web hosting solution that would support a public git-annex repo relatively simply with simple access to download the public files.
+
+I figure I could set up an Amazon EC2 micro instance and mount an s3 share, hosting the git-annex remote, but this is a lot of overhead for something that dropbox does with 1 click \"share dropbox link\"?
+
+Any suggestions would be great!
+"""]]
diff --git a/doc/tips/using_gitolite_with_git-annex/comment_18_f1a180d5cf65b7a870a13ddb4f76d00d._comment b/doc/tips/using_gitolite_with_git-annex/comment_18_f1a180d5cf65b7a870a13ddb4f76d00d._comment
new file mode 100644
index 0000000000..882478f5b6
--- /dev/null
+++ b/doc/tips/using_gitolite_with_git-annex/comment_18_f1a180d5cf65b7a870a13ddb4f76d00d._comment
@@ -0,0 +1,21 @@
+[[!comment format=mdwn
+ username="https://www.google.com/accounts/o8/id?id=AItOawll4Kgp7nMuOKdB0FfbcYZ3KRq7HCS0Slc"
+ nickname="Laura"
+ subject="Using Gitolite 3.2"
+ date="2014-01-17T20:14:16Z"
+ content="""
+Adding:
+
+ 'git-annex-shell' =>1,
+
+To the .gitolite.rc file resulted in the \"FATAL: suspicous characters loitering about 'git-annex-shell 'configlist' '/~/testing''...
+
+
+Gitolite source code (https://github.com/sitaramc/gitolite/commit/b1d3c0571409b7c6279fc6a77253c3bc262ab425#diff-79a3701e9e2cee0ea1316451c21a3fec) requires this entry:
+
+'git-annex-shell ua'
+
+
+
+
+"""]]
diff --git a/doc/tips/using_the_web_as_a_special_remote.mdwn b/doc/tips/using_the_web_as_a_special_remote.mdwn
index 706ae2951d..62ef58b694 100644
--- a/doc/tips/using_the_web_as_a_special_remote.mdwn
+++ b/doc/tips/using_the_web_as_a_special_remote.mdwn
@@ -34,7 +34,7 @@ With the result that it will hang onto files:
Could only verify the existence of 0 out of 1 necessary copies
Also these untrusted repositories may contain the file:
00000000-0000-0000-0000-000000000001 -- web
- (Use --force to override this check, or adjust annex.numcopies.)
+ (Use --force to override this check, or adjust numcopies.)
failed
## attaching urls to existing files
diff --git a/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync.mdwn b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync.mdwn
index 93ccc083d3..d3e20b6db4 100644
--- a/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync.mdwn
+++ b/doc/todo/A_really_simple_way_to_pair_devices_like_bittorent_sync.mdwn
@@ -5,3 +5,5 @@ First I thought with xmpp I can sync files without ssh/rsync or other remote acc
It would be just great to have some means to sync files without cloud just the two device. Without the ssh / rsync jut share some secret and the devices do the rest. :-o
Anyway thanks for hearing. I'm looking forward to know more about git-annex. Thank you for that sw. =-<>-=
+
+> [[design/assistant/telehash]] --[[Joey]]
diff --git a/doc/todo/Enhancement:_git_annex_whereis_KEY.mdwn b/doc/todo/Enhancement:_git_annex_whereis_KEY.mdwn
new file mode 100644
index 0000000000..604bc5566e
--- /dev/null
+++ b/doc/todo/Enhancement:_git_annex_whereis_KEY.mdwn
@@ -0,0 +1,19 @@
+### Please describe the problem.
+
+Great work on git annex! One possible enhancement occured to me: It would be very useful though if the "whereis" command would support looking up the location of files by arbitrary keys. This way one could inspect the location of old content which is not currently checked-out in the tree.
+
+In a related vein, the "unused" command could report old filenames or describe the associated commits. Tracking old versions is a great feature of your git-based approach, but currently, tasks such as pruning selected content seem unwiedly. Though I might be missing existing solutions. You can easily "cut-off" the history by forcing a drop of all unused content. It would be cool if one could somehow "address" old versions by filename and commit/date and selectively drop just these. The same could go for the "whereis" command, where one could e.g. query which remote holds content which was stored under some filename at some specific date.
+
+Thanks Cheers!
+
+> I agree that it's useful to run whereis on a specific key. This can
+> now be done using `git annex whereis --key KEY`
+> [[done]] --[[Joey]]
+>
+> To report old filenames, unused would have to search back through the
+> contents of symlinks in old versions of the repo, to find symlinks that
+> referred to a key. The best way I know how to do that is `git log -S$KEY`,
+> which is what unused suggests you use. But this is slow --
+> searching for a single key in one of my repos takes 25 seconds.
+> That's why it doesn't do it for you.
+>
diff --git a/doc/todo/Limit_file_revision_history.mdwn b/doc/todo/Limit_file_revision_history.mdwn
new file mode 100644
index 0000000000..48b44dea2c
--- /dev/null
+++ b/doc/todo/Limit_file_revision_history.mdwn
@@ -0,0 +1,117 @@
+Hi, I am assuming to use git-annex-assistant for two usecases, but I would like to ask about the options or planed roadmap for dropped/removed files from the repository.
+
+Usecases:
+
+1. sync working directory between laptop, home computer, work komputer
+2. archive functionality for my photograps
+
+Both usecases have one common factor. Some files might become obsolate and
+in long time frame nobody is interested to keep their revisions. Let's
+assume photographs. Usuall workflow I take is to import all photograps to
+filesystem, then assess (select) the good ones I want to keep and then
+process them what ever way.
+
+Problem with git-annex(-assistant) I have is that it start to revision all
+of the files at the time they are added to directory. This is welcome at
+first but might be an issue if you are used to put 80% of the size of your
+imported files to trash.
+
+I am aware of what git-annex is not. I have been reading documentation for
+"git-annex drop" and "unused" options including forums. I do understand
+that I am actually able to delete all revisions of the file if I will drop
+it, remove it and if I will run git annex unused 1..###. (on all synced
+repositories).
+
+I actually miss the option to have above process automated/replicated to the other synced repositories.
+
+I would formulate the 'use case' requirements for git-annex as:
+
+* command to drop an file including revisions from all annex repositories?
+ (for example like moving a file to /trash folder) that will schedulle
+ it's deletition)
+* option to keep like max. 10 last revisions of the file?
+* option to keep only previous revisions if younger than 6 months from now?
+
+Finally, how to specify a feature request for git-annex?
+
+> By moving it here ;-) --[[Joey]]
+
+> So, let's spec out a design.
+>
+> * Add preferred content terminal to configure whether a repository wants
+> to hang on to unused content. Simply `unused`.
+> (It cannot include a timestamp, because there's
+> no way repos can agree on about when a key became unused.) **done**
+> * In order to quickly match that terminal, the Annex monad will need
+> to keep a Set of unused Keys. This should only be loaded on demand.
+> **done**
+> NB: There is some potential for a great many unused Keys to cause
+> memory usage to balloon.
+> * Client repositories will end their preferred content with
+> `and (not unused)`. Transfer repositories too, because typically
+> only client repos connect to them, and so otherwise unused files
+> would build up there. Backup repos would want unused files. I
+> think that archive repos would too. **done**
+> * Make the assistant check for unused files periodically. Exactly
+> how often may need to be tuned, but once per day seems reasonable
+> for most repos. Note that the assistant could also notice on the
+> fly when files are removed and mark their keys as unused if that was
+> the last associated file. (Only currently possible in direct mode.)
+> **done**
+> * After scanning for unused files, it makes sense for the
+> assistant to queue transfers of unused files to any remotes that
+> do want them (eg, backup remotes). If the files can successfully be
+> sent to a remote, that will lead to them being dropped locally as
+> they're not wanted.
+> * Add a git config setting like annex.expireunused=7d. This causes
+> *deletion* of unused files after the specified time period if they are
+> not able to be moved to a repo that wants them.
+> (The default should be annex.expireunused=false.)
+> * How to detect how long a file has been unused? We can't look at the
+> time stamp of the object; we could use the mtime of the .map file,
+> that that's direct mode only and may be replaced with a database
+> later. Seems best to just keep a unused log file with timestamps.
+> **done**
+> * After the assistant scans for unused files, if annex.expireunused
+> is not set, and there is some significant quantity of unused files
+> (eg, more than 1000, or more than 1 gb, or more than the amount of
+> remaining free disk space),
+> it can pop up a webapp alert asking to configure it. **done**
+> * Webapp interface to configure annex.expireunused. Reasonable values
+> are no expiring, or any number of days. **done**
+>
+> [[done]] This does not cover every use case that was requested.
+> But I don't see a cheap way to ensure it keeps eg the past 10 versions of
+> a file. I guess that if you care about that, you leave
+> annex.expireunused=false, and set up a backup repository where the unused
+> files will be moved to.
+>
+> Note that since the assistant uses direct mode by default, old versions
+> of modififed files are not guaranteed to be retained. But they very well
+> might be. For example, if a file is replicated to 2 clients, and one
+> client directly edits it, or deletes it, it loses the old version,
+> but the other client will still be storing that old version.
+>
+> ## Stability analysis for unused in preferred content expressions
+>
+> This is tricky, because two repos that are otherwise entirely
+> in sync may have differing opinons about whether a key is unused,
+> depending on when each last scanned for unused keys.
+>
+> So, this preferred content terminal is *not stable*.
+> It may be possible to write preferred content expressions
+> that constantly moved such keys around without reaching a steady state.
+>
+> Example:
+>
+> A and B are clients directly connected, and both also connected
+> to BACKUP.
+>
+> A deletes F. B syncs with A, and runs unused check; decides F
+> is unused. B sends F to BACKUP. B will then think A doesn't want F,
+> and will drop F from A. Next time A runs a full transfer scan, it will
+> *not* find F (because the file was deleted!). So it won't get F back from
+> BACKUP.
+>
+> So, it looks like the fact that unused files are not going to be
+> looked for on the full transfer scan seems to make this work out ok.
diff --git a/doc/todo/Provide_a___34__git_annex_satisfy__95__num__95__copies__34___command.mdwn b/doc/todo/Provide_a___34__git_annex_satisfy__95__num__95__copies__34___command.mdwn
index 20046785ad..cbd01181fa 100644
--- a/doc/todo/Provide_a___34__git_annex_satisfy__95__num__95__copies__34___command.mdwn
+++ b/doc/todo/Provide_a___34__git_annex_satisfy__95__num__95__copies__34___command.mdwn
@@ -7,3 +7,10 @@ for i in `git remote`; do git copy -to $i --auto; done
The use case is this:
I have a very large repo (300.000 files) in three places. Now I want the fastest possible way to ensure, that every file exists in annex.numcopies. This should scan every file one time and then get it or copy it to other repos as needed. Right now, I make one "git annex get --auto" in every repo, which is is a waste of time, since most of the files never change anyway!
+> Now `git annex sync --content` does effectivly just what the shown for
+> loop does. [[done]]
+>
+> The only difference is that copy --auto proactively downloads otherwise
+> unwanted files to satisfy numcopies, and sync --content does not.
+> We need a [[preferred_content_numcopies_check]] to solve that.
+> --[[Joey]]
diff --git a/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn b/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn
index d48b4426f3..ae0894955a 100644
--- a/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn
+++ b/doc/todo/__96__git_annex_sync_--auto__96___or___96__git_annex_auto__96___--_synchronize_symlinks__44___tracking_info__44___and_actual_data.mdwn
@@ -1,3 +1,6 @@
-As per DebConf13: Introduce a one-shot command to synchronize everything, including data, with the other remotes.
+As per DebConf13: Introduce a one-shot command to synchronize everything,
+including data, with the other remotes.
Especially useful for the debconf annex.
+
+> [[done]]; `git annex sync --content` --[[Joey]]
diff --git a/doc/todo/git_annex_get___60__file__62___should_verify_file_hash.mdwn b/doc/todo/git_annex_get___60__file__62___should_verify_file_hash.mdwn
index f680729ac8..fd93554ece 100644
--- a/doc/todo/git_annex_get___60__file__62___should_verify_file_hash.mdwn
+++ b/doc/todo/git_annex_get___60__file__62___should_verify_file_hash.mdwn
@@ -30,3 +30,5 @@ M.
# End of transcript or log.
"""]]
+
+> [[duplicate|done]] of [[checksum_verification_on_transfer]] --[[Joey]]
diff --git a/doc/todo/http_git_annex_404_retry.mdwn b/doc/todo/http_git_annex_404_retry.mdwn
index 38ab860bbd..69680f0a18 100644
--- a/doc/todo/http_git_annex_404_retry.mdwn
+++ b/doc/todo/http_git_annex_404_retry.mdwn
@@ -14,3 +14,5 @@ always avoid this 404 problem.
directory hashing, but that's been discussed elsewhere.)
--[[Joey]]
+
+[[done]]
diff --git a/doc/todo/openwrt_package.txt b/doc/todo/openwrt_package.txt
new file mode 100644
index 0000000000..70a4ae03fb
--- /dev/null
+++ b/doc/todo/openwrt_package.txt
@@ -0,0 +1,6 @@
+hi
+
+recently i have installed openwrt on my mikrotik routerboard. i am verry suprised how well it works. it lacks git-annex package. openwrt has git and i can install it.
+
+how can i build one on a mips arch ?
+is it possible to build multiple architecture standalone binaries ?
diff --git a/doc/todo/openwrt_package/comment_1_100d76109e04bc43979775d71b4152ac._comment b/doc/todo/openwrt_package/comment_1_100d76109e04bc43979775d71b4152ac._comment
new file mode 100644
index 0000000000..78029694a5
--- /dev/null
+++ b/doc/todo/openwrt_package/comment_1_100d76109e04bc43979775d71b4152ac._comment
@@ -0,0 +1,12 @@
+[[!comment format=mdwn
+ username="http://joeyh.name/"
+ ip="206.74.132.139"
+ subject="comment 1"
+ date="2014-02-06T17:26:58Z"
+ content="""
+I would be quite happy if someone took care of adding git-annex to openwrt.
+
+I don't have time to personally handle packaging for different linux distributions myself. What I could do is add mips builds of git-annex to the existing standalone linux builds. These would need to be built the same way the arm builds are done, using a Debian chroot and qemu to run tools from it. This is rather a lot of work for me to set up, and I don't know if I'd have to do it for both little and big endian mips.
+
+Also, it seems that Debian does not currently have a working haskell toolchain for mips. Which may well mean that ghc is not in a working state on mips at all.
+"""]]
diff --git a/doc/todo/preferred_content_numcopies_check.mdwn b/doc/todo/preferred_content_numcopies_check.mdwn
new file mode 100644
index 0000000000..2e007460f7
--- /dev/null
+++ b/doc/todo/preferred_content_numcopies_check.mdwn
@@ -0,0 +1,86 @@
+The assistant and git annex sync --content do not try to proactively
+download content that is not otherwise wanted in order to get numcopies
+satisfied. (Unlike get --auto, which does take numcopies into account.)
+
+Should these automated systems try to proactively satisfy numcopies? I
+don't feel they should. It could result in surprising results. For example,
+a transfer repository, which is of limited size, could start being filled
+up with lots of content that all clients have, just because numcopies was
+set to a larger number than the total number of clients. Another example,
+a source repository on eg an Android phone, should never have content in it
+that was not created on that device.
+
+However, it would make sense for some specific
+types of repositories to proactively get content to satisfy numcopies.
+Currently some types of repositories use "or (not copies=semitrusted+:1)",
+to ensure that if the only copy of a file is on a dead repository, they
+will try to get that file before the repo goes away. This is done
+by client repositories, and backup, and archive. Probably the same set
+would make sense to proactively satisfy numcopies.
+
+So, a new type of preferred content expression is called for. Such as, for
+example, "numcopiesneeded=1". Which indicates that at least 1 more copy
+is needed to satifsy numcopies.
+
+(Note that it should only count semittrusted and higher trust
+level repos as satisfying numcopies.)
+
+But, preferred content expressions can only operate on info stored in the
+git repo, or they will fail to be stable. Ie, repo A needs to be able to
+calculate whether a file is preferred content by repo B and get the same
+result as when repo B calculates that.
+
+numcopies is currently configured in 3 places:
+
+* .git/config `annex.numcopies` (global, stored only locally)
+* .gitattributes `annex.numcopies` (per file, stored in git repo)
+* --numcopies (not relevant)
+
+So, need to add a global numcopies setting that is stored in the git repo.
+That could either be a file in the git-annex branch, or just
+`* annex.numcopies=2` in the toplevel .gitattributes. Note that the
+assistant needs to be able to query and set it, which I think argues
+against using .gitattributes for it. Also arguing against that is that the
+.git/config numcopies valie applies even to objects with no file in the
+work tree, which gitattributes settings do not.
+
+Conclusion:
+
+* Add to the git-annex branch a numcopies file that holds the global
+ numcopies default if present. **done**
+* Modify the assistant to use it when configuring numcopies. **done**
+* To deprecate .git/config's annex.numcopies, only make it take effect
+ when there is no numcopies file in the git-annex branch. **done**
+* Add "numcopiesneeded=N" preferred content expression using the git-annex
+ branch numcopies setting, overridden by any .gitattributes numcopies setting
+ for a particular file. It should ignore the other ways to specify
+ numcopies, particularly git config annex.numcopies. **done**
+* Make the repo groups that currently end with "or (not copies=semitrusted+:1)"
+ to instead end with "or numcopiesneeded=1" **done**
+* See if "numcopiesneeded=N" can check .gitattributes without getting
+ a lot slower. If now, perhaps add a "numcopiesneededaccurate=N" that
+ checks it. **done**
+
+[[done]]
+
+## Stability analysis
+
+If a remote prefers eg, "blah or numcopiesneeded=1", and
+file $foo does not match blah, but needs more copies, then then the
+expression will match.
+
+So, git-annex will get $foo, adding a copy. Which means that the
+numcopiesneeded=1 will no longer match, so the file is no longer wanted
+now that it has been downloaded.
+
+Now there are two cases for what can happen:
+
+* git-annex tries to drop $foo, but fails because it cannot find enough
+ other copies
+* git-annex copies $foo to some other remote that wants it, and then
+ manages to drop $foo from the local remote.
+
+This seems ok. Files flow through repos and they act like transfer
+repos when there are not enough copies.
+
+--[[Joey]]
diff --git a/doc/todo/separate_rsync_bwlimit_options_for_upload_and_download.mdwn b/doc/todo/separate_rsync_bwlimit_options_for_upload_and_download.mdwn
new file mode 100644
index 0000000000..2b93ad2d6d
--- /dev/null
+++ b/doc/todo/separate_rsync_bwlimit_options_for_upload_and_download.mdwn
@@ -0,0 +1,4 @@
+The bandwidth for upload and download are often different. It would be useful to have different settings for upload and download limits.
+As it is, I have to keep changing annex-rsync-options options between uploads and downloads.
+
+> [[done]] --[[Joey]]
diff --git a/doc/todo/windows_support.mdwn b/doc/todo/windows_support.mdwn
index fea8241cc4..ae27ac46b6 100644
--- a/doc/todo/windows_support.mdwn
+++ b/doc/todo/windows_support.mdwn
@@ -6,9 +6,10 @@ now! --[[Joey]]
* Does not work with Cygwin's build of git (that git does not consistently
support use of DOS style paths, which git-annex uses on Windows).
Must use Msysgit.
-* rsync special remotes are known buggy.
-* Bad file locking, it's probably not safe to run more than one git-annex
- process at the same time on Windows.
+* rsync special remotes with a rsyncurl of a local directory are known
+ let r = if inr1 then r1 else r2
+ buggy. (git-annex tells rsync C:foo and it thinks it means a remote host
+ named C...)
* Ssh connection caching does not work on Windows, so `git annex get`
has to connect twice to the remote system over ssh per file, which
is much slower than on systems supporting connection caching.
diff --git a/doc/todo/wishlist:_git_annex_put_--_same_as_get__44___but_for_defaults.mdwn b/doc/todo/wishlist:_git_annex_put_--_same_as_get__44___but_for_defaults.mdwn
index 9cd56749e8..e1dc89a96f 100644
--- a/doc/todo/wishlist:_git_annex_put_--_same_as_get__44___but_for_defaults.mdwn
+++ b/doc/todo/wishlist:_git_annex_put_--_same_as_get__44___but_for_defaults.mdwn
@@ -15,3 +15,6 @@ My main reason for not wanting to use copy --to is that I need to specify the re
mr push
to do the right thing all by itself.
+
+> I feel that the new `git annex sync --content` is pretty close to what's
+> requested here. [[done]] --[[Joey]]
diff --git a/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote.mdwn b/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote.mdwn
index 297047e064..fe32f7dd77 100644
--- a/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote.mdwn
+++ b/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote.mdwn
@@ -1,3 +1,9 @@
When adding a Remote server through the webapp, it set-up a specific SSH key for later sync.
However, when the remote has been set-up manually, then later gets the assistant thrown at it, there doesn't appear to be a way to create and deploy such a key. This option could be offered in, e.g., the settings of the repo in the webapp.
+
+> I feel this is out of scope for the assistant. If the user is able to
+> manually add a git remote at the command line, then they should be able
+> to configure ssh keys too. I don't want to complicate the assistant with
+> a lot of code that tries to deal with half-configured things the user
+> manually set up. [[wontfix|done]] --[[Joey]]
diff --git a/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote/comment_1_13737dc99aa877b309f7ebe44ecbafee._comment b/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote/comment_1_13737dc99aa877b309f7ebe44ecbafee._comment
new file mode 100644
index 0000000000..d8e3f93372
--- /dev/null
+++ b/doc/todo/wishlist__91__webapp__93__:_add_an_option_to_install__SSH_key_on_remote/comment_1_13737dc99aa877b309f7ebe44ecbafee._comment
@@ -0,0 +1,16 @@
+[[!comment format=mdwn
+ username="http://olivier.mehani.name/"
+ nickname="olivier-mehani"
+ subject="comment 1"
+ date="2014-01-22T13:08:21Z"
+ content="""
+Hum, fair enough. The webapp might not be the best target. However, there might already be some logic to deploy the key, only not exposed in any UI (web or CLI).
+
+However, I was under the impression that the key thath git-annex installs remotely is also limited to running git-annex-related tasks (using the command option; I cannot find any example in my configurations at the moment), rather than providing a generic login shell which happens to be used for git-annex.
+
+The command to run on the remote server did not seem to be trivial (this is what I'm currently bumping against), and I guess there already are a few functions which create and install the authorized_files entry. Maybe providing, e.g., a
+
+ git-annex installkey REMOTE
+
+command, automating only this key-setup step for the user, would be good?
+"""]]
diff --git a/doc/walkthrough.mdwn b/doc/walkthrough.mdwn
index f401524f51..94c31e4772 100644
--- a/doc/walkthrough.mdwn
+++ b/doc/walkthrough.mdwn
@@ -15,6 +15,7 @@ A walkthrough of the basic features of git-annex.
walkthrough/modifying_annexed_files
walkthrough/using_ssh_remotes
walkthrough/moving_file_content_between_repositories
+ walkthrough/quiet_please:_When_git-annex_seems_to_skip_files
walkthrough/using_tags_and_branches
walkthrough/unused_data
walkthrough/fsck:_verifying_your_data
diff --git a/doc/walkthrough/adding_files.mdwn b/doc/walkthrough/adding_files.mdwn
index d1b5a04f77..b014c3ee70 100644
--- a/doc/walkthrough/adding_files.mdwn
+++ b/doc/walkthrough/adding_files.mdwn
@@ -7,5 +7,6 @@
# git commit -a -m added
When you add a file to the annex and commit it, only a symlink to
-the annexed content is committed. The content itself is stored in
-git-annex's backend.
+the content is committed to git. The content itself is stored in
+git-annex's backend, `.git/annex/` (or in [[direct_mode]] the file
+is left as-is).
diff --git a/doc/walkthrough/fsck:_verifying_your_data.mdwn b/doc/walkthrough/fsck:_verifying_your_data.mdwn
index d036332fb3..62e15b6fa5 100644
--- a/doc/walkthrough/fsck:_verifying_your_data.mdwn
+++ b/doc/walkthrough/fsck:_verifying_your_data.mdwn
@@ -2,7 +2,7 @@ You can use the fsck subcommand to check for problems in your data. What
can be checked depends on the key-value [[backend|backends]] you've used
for the data. For example, when you use the SHA1 backend, fsck will verify
that the checksums of your files are good. Fsck also checks that the
-annex.numcopies setting is satisfied for all files.
+[[numcopies|copies]] setting is satisfied for all files.
# git annex fsck
fsck some_file (checksum...) ok
diff --git a/doc/walkthrough/quiet_please:_When_git-annex_seems_to_skip_files.mdwn b/doc/walkthrough/quiet_please:_When_git-annex_seems_to_skip_files.mdwn
new file mode 100644
index 0000000000..188ca634ba
--- /dev/null
+++ b/doc/walkthrough/quiet_please:_When_git-annex_seems_to_skip_files.mdwn
@@ -0,0 +1,27 @@
+One behavior of git-annex is sometimes confusing at first, but it turns out
+to be useful once you get to know it.
+
+ # git annex drop *
+ #
+
+Why didn't git-annex seem to do anything despite being asked to drop all the
+files? Because it checked them all, and none of them are present.
+
+Most git-annex commands will behave this way when they're able to quickly
+check that nothing needs to be done about a file.
+
+Running a git-annex command without specifying any file name will
+make git-annex look for files in the current directory and its
+subdirectories. So, we can add all new files to the annex easily:
+
+ # echo hi > subdir/subsubdir/newfile
+ # git annex add
+ add subdir/subsubdir/newfile ok
+
+When doing this kind of thing, having nothing shown for files
+that it doesn't need to act on is useful because it prevents swamping
+you with output. You only see the files it finds it does need to act on.
+
+So remember: If git-annex seems to not do anything when you tell it to, it's
+not being lazy -- It's checked that nothing needs to be done to get to the
+state you asked for!
diff --git a/doc/walkthrough/removing_files:_When_things_go_wrong.mdwn b/doc/walkthrough/removing_files:_When_things_go_wrong.mdwn
index 2d3c0cde08..ccd2d197f5 100644
--- a/doc/walkthrough/removing_files:_When_things_go_wrong.mdwn
+++ b/doc/walkthrough/removing_files:_When_things_go_wrong.mdwn
@@ -10,12 +10,12 @@ you'll see something like this.
Try making some of these repositories available:
58d84e8a-d9ae-11df-a1aa-ab9aa8c00826 -- portable USB drive
ca20064c-dbb5-11df-b2fe-002170d25c55 -- backup SATA drive
- (Use --force to override this check, or adjust annex.numcopies.)
+ (Use --force to override this check, or adjust numcopies.)
failed
drop other.iso (unsafe)
Could only verify the existence of 0 out of 1 necessary copies
No other repository is known to contain the file.
- (Use --force to override this check, or adjust annex.numcopies.)
+ (Use --force to override this check, or adjust numcopies.)
failed
Here you might --force it to drop `important_file` if you [[trust]] your backup.
diff --git a/doc/walkthrough/syncing.mdwn b/doc/walkthrough/syncing.mdwn
index 0c8d525597..57fe47db05 100644
--- a/doc/walkthrough/syncing.mdwn
+++ b/doc/walkthrough/syncing.mdwn
@@ -15,13 +15,13 @@ Let's look at what the sync command does in more detail:
push laptop
ok
-After you run sync, the repository will be updated with all changes made to
-its remotes, and any changes in the repository will be pushed out to its
-remotes, where a sync will get them. This is especially useful when using
-git in a distributed fashion, without a
-[[central bare repository|tips/centralized_git_repository_tutorial]]. See
-[[sync]] for details.
+After you run sync, the git repository will be updated with all changes
+made to its remotes, and any changes in the git repository will be pushed
+out to its remotes, where a sync will get them. This is especially useful
+when using git in a distributed fashion, without a [[central bare
+repository|tips/centralized_git_repository_tutorial]]. See [[sync]] for
+details.
-Note that syncing only syncs the metadata about your files that is stored
-in git. It does not sync the contents of files, that are managed by
-git-annex.
+By default `git annex sync` only syncs the metadata about your
+files that is stored in git. It does not sync the contents of files, that
+are managed by git-annex. To do that, you can use `git annex sync --content`
diff --git a/git-annex.cabal b/git-annex.cabal
index a759e00a94..7f5a5158f4 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -1,5 +1,5 @@
Name: git-annex
-Version: 5.20140117
+Version: 5.20140210
Cabal-Version: >= 1.8
License: GPL-3
Maintainer: Joey Hess
@@ -93,7 +93,7 @@ Executable git-annex
extensible-exceptions, dataenc, SHA, process, json,
base (>= 4.5 && < 4.9), monad-control, MonadCatchIO-transformers,
IfElse, text, QuickCheck >= 2.1, bloomfilter, edit-distance, process,
- SafeSemaphore, uuid, random, dlist, unix-compat, async
+ SafeSemaphore, uuid, random, dlist, unix-compat, async, stm (>= 2.3)
CC-Options: -Wall
GHC-Options: -Wall
Extensions: PackageImports
@@ -114,7 +114,8 @@ Executable git-annex
CPP-Options: -DWITH_CLIBS
if flag(TestSuite)
- Build-Depends: tasty, tasty-hunit, tasty-quickcheck
+ Build-Depends: tasty (>= 0.7), tasty-hunit, tasty-quickcheck, tasty-rerun,
+ optparse-applicative
CPP-Options: -DWITH_TESTSUITE
if flag(TDFA)
@@ -131,11 +132,11 @@ Executable git-annex
-- Not yet available for backport.
--if flag(WebDAV)
- -- Build-Depends: DAV (>= 0.3), http-conduit, xml-conduit, http-types
+ -- Build-Depends: DAV ((>= 0.3 && < 0.6) || > 0.6),
+ -- http-conduit, xml-conduit, http-types
-- CPP-Options: -DWITH_WEBDAV
if flag(Assistant) && ! os(solaris)
- Build-Depends: stm (>= 2.3)
CPP-Options: -DWITH_ASSISTANT
if flag(Assistant)
diff --git a/git-annex.hs b/git-annex.hs
index 0f45f53ebc..198a1f4e6e 100644
--- a/git-annex.hs
+++ b/git-annex.hs
@@ -10,8 +10,8 @@
import System.Environment
import System.FilePath
-import qualified GitAnnex
-import qualified GitAnnexShell
+import qualified CmdLine.GitAnnex
+import qualified CmdLine.GitAnnexShell
#ifdef WITH_TESTSUITE
import qualified Test
#endif
@@ -20,15 +20,15 @@ main :: IO ()
main = run =<< getProgName
where
run n
- | isshell n = go GitAnnexShell.run
- | otherwise = go GitAnnex.run
+ | isshell n = go CmdLine.GitAnnexShell.run
+ | otherwise = go CmdLine.GitAnnex.run
isshell n = takeFileName n == "git-annex-shell"
go a = do
ps <- getArgs
#ifdef WITH_TESTSUITE
- if ps == ["test"]
- then Test.main
- else a ps
+ case ps of
+ ("test":ps') -> Test.main ps'
+ _ -> a ps
#else
a ps
#endif
diff --git a/standalone/android/haskell-patches/certificate_1.3.7-0001-support-Android-cert-store.patch b/standalone/android/haskell-patches/certificate_1.3.7-0001-support-Android-cert-store.patch
new file mode 100644
index 0000000000..5f772bfdfe
--- /dev/null
+++ b/standalone/android/haskell-patches/certificate_1.3.7-0001-support-Android-cert-store.patch
@@ -0,0 +1,37 @@
+From 3779c75175e895f94b21341ebd6361e9d6af54fd Mon Sep 17 00:00:00 2001
+From: Joey Hess
+Date: Thu, 9 May 2013 12:36:23 -0400
+Subject: [PATCH] support Android cert store
+
+Android puts it in a different place and has only hashed files.
+See https://github.com/vincenthz/hs-certificate/issues/19
+---
+ System/Certificate/X509/Unix.hs | 5 +++--
+ 1 file changed, 3 insertions(+), 2 deletions(-)
+
+diff --git a/System/Certificate/X509/Unix.hs b/System/Certificate/X509/Unix.hs
+index 8463465..74e9503 100644
+--- a/System/Certificate/X509/Unix.hs
++++ b/System/Certificate/X509/Unix.hs
+@@ -35,7 +35,8 @@ import qualified Control.Exception as E
+ import Data.Char
+
+ defaultSystemPath :: FilePath
+-defaultSystemPath = "/etc/ssl/certs/"
++defaultSystemPath = "/system/etc/security/cacerts/"
++--defaultSystemPath = "/etc/ssl/certs/"
+
+ envPathOverride :: String
+ envPathOverride = "SYSTEM_CERTIFICATE_PATH"
+@@ -47,7 +48,7 @@ listDirectoryCerts path = (map (path >) . filter isCert <$> getDirectoryConten
+ && isDigit (s !! 9)
+ && (s !! 8) == '.'
+ && all isHexDigit (take 8 s)
+- isCert x = (not $ isPrefixOf "." x) && (not $ isHashedFile x)
++ isCert x = (not $ isPrefixOf "." x)
+
+ getSystemCertificateStore :: IO CertificateStore
+ getSystemCertificateStore = makeCertificateStore . concat <$> (getSystemPath >>= listDirectoryCerts >>= mapM readCertificates)
+--
+1.8.2.rc3
+
diff --git a/standalone/android/haskell-patches/gnuidn_fix-build-with-new-base.patch b/standalone/android/haskell-patches/gnuidn_fix-build-with-new-base.patch
deleted file mode 100644
index ff9d8f2458..0000000000
--- a/standalone/android/haskell-patches/gnuidn_fix-build-with-new-base.patch
+++ /dev/null
@@ -1,50 +0,0 @@
-From afdec6c9e66211a0ac8419fffe191b059d1fd00c Mon Sep 17 00:00:00 2001
-From: foo
-Date: Sun, 22 Sep 2013 17:24:33 +0000
-Subject: [PATCH] fix build with new base
-
----
- Data/Text/IDN/IDNA.chs | 1 +
- Data/Text/IDN/Punycode.chs | 1 +
- Data/Text/IDN/StringPrep.chs | 1 +
- 3 files changed, 3 insertions(+)
-
-diff --git a/Data/Text/IDN/IDNA.chs b/Data/Text/IDN/IDNA.chs
-index ed29ee4..dbb4ba5 100644
---- a/Data/Text/IDN/IDNA.chs
-+++ b/Data/Text/IDN/IDNA.chs
-@@ -31,6 +31,7 @@ import Foreign
- import Foreign.C
-
- import Data.Text.IDN.Internal
-+import System.IO.Unsafe
-
- #include
- #include
-diff --git a/Data/Text/IDN/Punycode.chs b/Data/Text/IDN/Punycode.chs
-index 24b5fa6..4e62555 100644
---- a/Data/Text/IDN/Punycode.chs
-+++ b/Data/Text/IDN/Punycode.chs
-@@ -32,6 +32,7 @@ import Data.List (unfoldr)
- import qualified Data.ByteString as B
- import qualified Data.Text as T
-
-+import System.IO.Unsafe
- import Foreign
- import Foreign.C
-
-diff --git a/Data/Text/IDN/StringPrep.chs b/Data/Text/IDN/StringPrep.chs
-index 752dc9e..5e9fd84 100644
---- a/Data/Text/IDN/StringPrep.chs
-+++ b/Data/Text/IDN/StringPrep.chs
-@@ -39,6 +39,7 @@ import qualified Data.ByteString as B
- import qualified Data.Text as T
- import qualified Data.Text.Encoding as TE
-
-+import System.IO.Unsafe
- import Foreign
- import Foreign.C
-
---
-1.7.10.4
-
diff --git a/standalone/android/haskell-patches/libxml-sax_text-dep.patch b/standalone/android/haskell-patches/libxml-sax_text-dep.patch
new file mode 100644
index 0000000000..c9b4fdb78b
--- /dev/null
+++ b/standalone/android/haskell-patches/libxml-sax_text-dep.patch
@@ -0,0 +1,25 @@
+From d4c861dbdee34cb2434085b9ece62c416d4cad79 Mon Sep 17 00:00:00 2001
+From: androidbuilder
+Date: Sat, 8 Feb 2014 17:19:37 +0000
+Subject: [PATCH] text dependency
+
+---
+ libxml-sax.cabal | 2 +-
+ 1 file changed, 1 insertion(+), 1 deletion(-)
+
+diff --git a/libxml-sax.cabal b/libxml-sax.cabal
+index 60dba81..d6883bd 100644
+--- a/libxml-sax.cabal
++++ b/libxml-sax.cabal
+@@ -35,7 +35,7 @@ library
+ build-depends:
+ base >= 4.1 && < 5.0
+ , bytestring >= 0.9
+- , text >= 0.7 && < 0.12
++ , text
+ , xml-types >= 0.3 && < 0.4
+
+ exposed-modules:
+--
+1.7.10.4
+
diff --git a/standalone/android/haskell-patches/network-protocol-xmpp_text-dapendency.patch b/standalone/android/haskell-patches/network-protocol-xmpp_text-dapendency.patch
new file mode 100644
index 0000000000..7987818372
--- /dev/null
+++ b/standalone/android/haskell-patches/network-protocol-xmpp_text-dapendency.patch
@@ -0,0 +1,25 @@
+From 8f124aad6d04abba5729af21ba3b50944f165d4b Mon Sep 17 00:00:00 2001
+From: androidbuilder
+Date: Sat, 8 Feb 2014 17:20:41 +0000
+Subject: [PATCH] text dependency
+
+---
+ network-protocol-xmpp.cabal | 2 +-
+ 1 file changed, 1 insertion(+), 1 deletion(-)
+
+diff --git a/network-protocol-xmpp.cabal b/network-protocol-xmpp.cabal
+index 2500075..d709a15 100644
+--- a/network-protocol-xmpp.cabal
++++ b/network-protocol-xmpp.cabal
+@@ -36,7 +36,7 @@ library
+ , libxml-sax >= 0.7 && < 0.8
+ , monads-tf >= 0.1 && < 0.2
+ , network >= 2.2
+- , text >= 0.10 && < 0.12
++ , text
+ , transformers >= 0.2
+ , xml-types >= 0.3 && < 0.4
+
+--
+1.7.10.4
+
diff --git a/standalone/android/haskell-patches/system-filepath_cross-build.patch b/standalone/android/haskell-patches/system-filepath_cross-build.patch
new file mode 100644
index 0000000000..430e8f99fa
--- /dev/null
+++ b/standalone/android/haskell-patches/system-filepath_cross-build.patch
@@ -0,0 +1,25 @@
+From 9345a1ad95cc263f99ef124c7a386fb5aaa5405b Mon Sep 17 00:00:00 2001
+From: androidbuilder
+Date: Fri, 7 Feb 2014 22:18:12 +0000
+Subject: [PATCH] fix
+
+---
+ system-filepath.cabal | 2 +-
+ 1 file changed, 1 insertion(+), 1 deletion(-)
+
+diff --git a/system-filepath.cabal b/system-filepath.cabal
+index d5fbbdd..efdf9ca 100644
+--- a/system-filepath.cabal
++++ b/system-filepath.cabal
+@@ -6,7 +6,7 @@ license-file: license.txt
+ author: John Millikin
+ maintainer: John Millikin
+ copyright: John Millikin 2010-2012
+-build-type: Custom
++build-type: Simple
+ cabal-version: >= 1.6
+ category: System
+ stability: experimental
+--
+1.7.10.4
+
diff --git a/standalone/android/install-haskell-packages b/standalone/android/install-haskell-packages
index 3e4c061a82..749f45f62d 100755
--- a/standalone/android/install-haskell-packages
+++ b/standalone/android/install-haskell-packages
@@ -27,8 +27,12 @@ cabalinstall () {
patched () {
pkg=$1
- shift 1
- cabal unpack $pkg
+ ver=$2
+ if [ -z "$ver" ]; then
+ cabal unpack $pkg
+ else
+ cabal unpack $pkg-$ver
+ fi
cd $pkg*
git init
git config user.name dummy
@@ -45,7 +49,7 @@ patched () {
fi
fi
done
- cabalinstall "$@"
+ cabalinstall
rm -rf $pkg*
cd ..
}
@@ -81,7 +85,9 @@ install_pkgs () {
patched profunctors
patched skein
patched lens
+ patched certificate
patched persistent-template
+ patched system-filepath
patched wai-app-static
patched shakespeare
patched shakespeare-css
@@ -95,12 +101,13 @@ install_pkgs () {
patched yesod
patched shakespeare-text
patched process-conduit
- patched gnuidn
patched DAV
patched yesod-static
patched uuid
patched dns
patched gnutls
+ patched libxml-sax
+ patched network-protocol-xmpp
cd ..
diff --git a/standalone/no-th/haskell-patches/DAV_build-without-TH.patch b/standalone/no-th/haskell-patches/DAV_build-without-TH.patch
index ac6ba2a190..d57d79a11c 100644
--- a/standalone/no-th/haskell-patches/DAV_build-without-TH.patch
+++ b/standalone/no-th/haskell-patches/DAV_build-without-TH.patch
@@ -1,27 +1,22 @@
-From 67e5fc4eb21fe801f7ab4c01b98c02912c5cb43f Mon Sep 17 00:00:00 2001
-From: Joey Hess
-Date: Wed, 18 Dec 2013 05:44:10 +0000
+From a908cec3ae1644d72d04ccc7657433d8335665bc Mon Sep 17 00:00:00 2001
+From: dummy
+Date: Sat, 8 Feb 2014 17:11:05 +0000
Subject: [PATCH] expand TH
-plus manual fixups
---
- DAV.cabal | 22 +---
- Network/Protocol/HTTP/DAV.hs | 96 +++++++++++++----
- Network/Protocol/HTTP/DAV/TH.hs | 232 +++++++++++++++++++++++++++++++++++++++-
- 3 files changed, 307 insertions(+), 43 deletions(-)
+ DAV.cabal | 24 +---
+ Network/Protocol/HTTP/DAV.hs | 96 ++++++++++++----
+ Network/Protocol/HTTP/DAV/TH.hs | 232 ++++++++++++++++++++++++++++++++++++++-
+ 3 files changed, 307 insertions(+), 45 deletions(-)
diff --git a/DAV.cabal b/DAV.cabal
-index 1f1eb1f..ea117ff 100644
+index 3a755bb..748b0e1 100644
--- a/DAV.cabal
+++ b/DAV.cabal
-@@ -36,27 +36,7 @@ library
- , lifted-base >= 0.1
- , monad-control
- , mtl >= 2.1
-- , transformers >= 0.3
-- , transformers-base
-- , xml-conduit >= 1.0 && <= 1.2
-- , xml-hamlet >= 0.4 && <= 0.5
+@@ -42,29 +42,7 @@ library
+ , transformers-base
+ , xml-conduit >= 1.0 && <= 1.2
+ , xml-hamlet >= 0.4 && <= 0.5
-executable hdav
- main-is: hdav.hs
- ghc-options: -Wall
@@ -30,24 +25,30 @@ index 1f1eb1f..ea117ff 100644
- , bytestring
- , case-insensitive >= 0.4
- , containers
+- , either >= 4.1
+- , errors
- , http-client >= 0.2
- , http-client-tls >= 0.2
- , http-types >= 0.7
- , lens >= 3.0
- , lifted-base >= 0.1
-- , monad-control
+- , monad-control >= 0.3.2
- , mtl >= 2.1
- , network >= 2.3
-- , optparse-applicative
+- , optparse-applicative >= 0.5.0
+- , transformers >= 0.3
+- , transformers-base
+- , xml-conduit >= 1.0 && <= 1.2
+- , xml-hamlet >= 0.4 && <= 0.5
+ , text
- , transformers >= 0.3
- , transformers-base
- , xml-conduit >= 1.0 && <= 1.2
+
+ source-repository head
+ type: git
diff --git a/Network/Protocol/HTTP/DAV.hs b/Network/Protocol/HTTP/DAV.hs
-index 9d8c070..5993fca 100644
+index 94d21bc..c48618f 100644
--- a/Network/Protocol/HTTP/DAV.hs
+++ b/Network/Protocol/HTTP/DAV.hs
-@@ -77,7 +77,7 @@ import Network.HTTP.Types (hContentType, Method, Status, RequestHeaders, unautho
+@@ -78,7 +78,7 @@ import Network.HTTP.Types (hContentType, Method, Status, RequestHeaders, unautho
import qualified Text.XML as XML
import Text.XML.Cursor (($/), (&/), element, node, fromDocument, checkName)
@@ -56,7 +57,7 @@ index 9d8c070..5993fca 100644
import Data.CaseInsensitive (mk)
-@@ -335,28 +335,84 @@ makeCollection url username password = choke $ evalDAVT url $ do
+@@ -336,28 +336,84 @@ makeCollection url username password = choke $ evalDAVT url $ do
propname :: XML.Document
propname = XML.Document (XML.Prologue [] Nothing []) root []
where
@@ -410,5 +411,5 @@ index b072116..5a01bf9 100644
+ Data.Functor.<$> (_f_a2R5 __userAgent'_a2Re))
+{-# INLINE userAgent #-}
--
-1.8.5.1
+1.7.10.4
diff --git a/standalone/no-th/haskell-patches/lens_no-TH.patch b/standalone/no-th/haskell-patches/lens_no-TH.patch
index ffcf0027ec..81e370146e 100644
--- a/standalone/no-th/haskell-patches/lens_no-TH.patch
+++ b/standalone/no-th/haskell-patches/lens_no-TH.patch
@@ -1,52 +1,58 @@
-From 2b5fa1851a84f58b43e7c4224bd5695a32a80de9 Mon Sep 17 00:00:00 2001
+From b9b3cd52735f9ede1a83960968dc1f0e91e061d6 Mon Sep 17 00:00:00 2001
From: dummy
-Date: Wed, 18 Dec 2013 03:27:54 +0000
+Date: Fri, 7 Feb 2014 21:49:11 +0000
Subject: [PATCH] avoid TH
---
- lens.cabal | 13 +------------
- src/Control/Lens.hs | 4 ++--
- src/Control/Lens/Internal/Exception.hs | 30 ------------------------------
- src/Control/Lens/Prism.hs | 2 --
- 4 files changed, 3 insertions(+), 46 deletions(-)
+ lens.cabal | 14 +-------------
+ src/Control/Lens.hs | 6 ++----
+ src/Control/Lens/Cons.hs | 2 --
+ src/Control/Lens/Internal/Fold.hs | 2 --
+ src/Control/Lens/Internal/Reflection.hs | 2 --
+ src/Control/Lens/Prism.hs | 2 --
+ src/Control/Monad/Primitive/Lens.hs | 1 -
+ 7 files changed, 3 insertions(+), 26 deletions(-)
diff --git a/lens.cabal b/lens.cabal
-index 8477892..a6ac7a5 100644
+index cee2da7..1e467c4 100644
--- a/lens.cabal
+++ b/lens.cabal
@@ -10,7 +10,7 @@ stability: provisional
homepage: http://github.com/ekmett/lens/
bug-reports: http://github.com/ekmett/lens/issues
- copyright: Copyright (C) 2012-2013 Edward A. Kmett
+ copyright: Copyright (C) 2012-2014 Edward A. Kmett
-build-type: Custom
+build-type: Simple
+ -- build-tools: cpphs
tested-with: GHC == 7.6.3
synopsis: Lenses, Folds and Traversals
- description:
-@@ -173,7 +173,6 @@ library
- containers >= 0.4.0 && < 0.6,
- distributive >= 0.3 && < 1,
- filepath >= 1.2.0.0 && < 1.4,
-- generic-deriving >= 1.4 && < 1.7,
- ghc-prim,
- hashable >= 1.1.2.3 && < 1.3,
- MonadCatchIO-transformers >= 0.3 && < 0.4,
-@@ -235,14 +234,12 @@ library
+@@ -216,7 +216,6 @@ library
+ Control.Exception.Lens
+ Control.Lens
+ Control.Lens.Action
+- Control.Lens.At
+ Control.Lens.Combinators
+ Control.Lens.Cons
+ Control.Lens.Each
+@@ -256,17 +255,14 @@ library
+ Control.Lens.Reified
Control.Lens.Review
Control.Lens.Setter
- Control.Lens.Simple
- Control.Lens.TH
Control.Lens.Traversal
Control.Lens.Tuple
Control.Lens.Type
Control.Lens.Wrapped
- Control.Lens.Zipper
Control.Lens.Zoom
- Control.Monad.Error.Lens
+ Control.Monad.Primitive.Lens
Control.Parallel.Strategies.Lens
Control.Seq.Lens
+- Data.Aeson.Lens
Data.Array.Lens
-@@ -266,12 +263,8 @@ library
+ Data.Bits.Lens
+ Data.ByteString.Lens
+@@ -289,12 +285,8 @@ library
Data.Typeable.Lens
Data.Vector.Lens
Data.Vector.Generic.Lens
@@ -58,8 +64,8 @@ index 8477892..a6ac7a5 100644
- Language.Haskell.TH.Lens
Numeric.Lens
- if flag(safe)
-@@ -370,7 +363,6 @@ test-suite doctests
+ other-modules:
+@@ -394,7 +386,6 @@ test-suite doctests
deepseq,
doctest >= 0.9.1,
filepath,
@@ -67,7 +73,7 @@ index 8477892..a6ac7a5 100644
mtl,
nats,
parallel,
-@@ -396,7 +388,6 @@ benchmark plated
+@@ -432,7 +423,6 @@ benchmark plated
comonad,
criterion,
deepseq,
@@ -75,7 +81,7 @@ index 8477892..a6ac7a5 100644
lens,
transformers
-@@ -431,7 +422,6 @@ benchmark unsafe
+@@ -467,7 +457,6 @@ benchmark unsafe
comonads-fd,
criterion,
deepseq,
@@ -83,7 +89,7 @@ index 8477892..a6ac7a5 100644
lens,
transformers
-@@ -448,6 +438,5 @@ benchmark zipper
+@@ -484,6 +473,5 @@ benchmark zipper
comonads-fd,
criterion,
deepseq,
@@ -91,77 +97,87 @@ index 8477892..a6ac7a5 100644
lens,
transformers
diff --git a/src/Control/Lens.hs b/src/Control/Lens.hs
-index f7c6548..125153e 100644
+index 7e15267..bb4d87b 100644
--- a/src/Control/Lens.hs
+++ b/src/Control/Lens.hs
-@@ -59,7 +59,7 @@ module Control.Lens
+@@ -41,7 +41,6 @@
+ ----------------------------------------------------------------------------
+ module Control.Lens
+ ( module Control.Lens.Action
+- , module Control.Lens.At
+ , module Control.Lens.Cons
+ , module Control.Lens.Each
+ , module Control.Lens.Empty
+@@ -58,7 +57,7 @@ module Control.Lens
+ , module Control.Lens.Reified
, module Control.Lens.Review
, module Control.Lens.Setter
- , module Control.Lens.Simple
-#ifndef DISABLE_TEMPLATE_HASKELL
+#if 0
, module Control.Lens.TH
#endif
, module Control.Lens.Traversal
-@@ -89,7 +89,7 @@ import Control.Lens.Reified
+@@ -69,7 +68,6 @@ module Control.Lens
+ ) where
+
+ import Control.Lens.Action
+-import Control.Lens.At
+ import Control.Lens.Cons
+ import Control.Lens.Each
+ import Control.Lens.Empty
+@@ -86,7 +84,7 @@ import Control.Lens.Prism
+ import Control.Lens.Reified
import Control.Lens.Review
import Control.Lens.Setter
- import Control.Lens.Simple
-#ifndef DISABLE_TEMPLATE_HASKELL
+#if 0
import Control.Lens.TH
#endif
import Control.Lens.Traversal
-diff --git a/src/Control/Lens/Internal/Exception.hs b/src/Control/Lens/Internal/Exception.hs
-index 387203e..bb1ca10 100644
---- a/src/Control/Lens/Internal/Exception.hs
-+++ b/src/Control/Lens/Internal/Exception.hs
-@@ -128,18 +128,6 @@ class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where
- handler_ l = handler l . const
- {-# INLINE handler_ #-}
+diff --git a/src/Control/Lens/Cons.hs b/src/Control/Lens/Cons.hs
+index a80e9c8..7d27b80 100644
+--- a/src/Control/Lens/Cons.hs
++++ b/src/Control/Lens/Cons.hs
+@@ -55,8 +55,6 @@ import Data.Vector.Unboxed (Unbox)
+ import qualified Data.Vector.Unboxed as Unbox
+ import Data.Word
--instance Handleable SomeException IO Exception.Handler where
-- handler = handlerIO
+-{-# ANN module "HLint: ignore Eta reduce" #-}
-
--instance Handleable SomeException m (CatchIO.Handler m) where
-- handler = handlerCatchIO
--
--handlerIO :: forall a r. Getting (First a) SomeException a -> (a -> IO r) -> Exception.Handler r
--handlerIO l f = reify (preview l) $ \ (_ :: Proxy s) -> Exception.Handler (\(Handling a :: Handling a s IO) -> f a)
--
--handlerCatchIO :: forall m a r. Getting (First a) SomeException a -> (a -> m r) -> CatchIO.Handler m r
--handlerCatchIO l f = reify (preview l) $ \ (_ :: Proxy s) -> CatchIO.Handler (\(Handling a :: Handling a s m) -> f a)
+ -- $setup
+ -- >>> :set -XNoOverloadedStrings
+ -- >>> import Control.Lens
+diff --git a/src/Control/Lens/Internal/Fold.hs b/src/Control/Lens/Internal/Fold.hs
+index 00e4b66..03c9cd2 100644
+--- a/src/Control/Lens/Internal/Fold.hs
++++ b/src/Control/Lens/Internal/Fold.hs
+@@ -37,8 +37,6 @@ import Data.Maybe
+ import Data.Semigroup hiding (Min, getMin, Max, getMax)
+ import Data.Reflection
+
+-{-# ANN module "HLint: ignore Avoid lambda" #-}
-
------------------------------------------------------------------------------
- -- Helpers
+ -- Folding
------------------------------------------------------------------------------
-@@ -159,21 +147,3 @@ supply = unsafePerformIO $ newIORef 0
- -- | This permits the construction of an \"impossible\" 'Control.Exception.Handler' that matches only if some function does.
- newtype Handling a s (m :: * -> *) = Handling a
+diff --git a/src/Control/Lens/Internal/Reflection.hs b/src/Control/Lens/Internal/Reflection.hs
+index bf09f2c..c9e112f 100644
+--- a/src/Control/Lens/Internal/Reflection.hs
++++ b/src/Control/Lens/Internal/Reflection.hs
+@@ -64,8 +64,6 @@ import Data.Word
+ import Data.Typeable
+ import Data.Reflection
---- the m parameter exists simply to break the Typeable1 pattern, so we can provide this without overlap.
---- here we simply generate a fresh TypeRep so we'll fail to compare as equal to any other TypeRep.
--instance Typeable (Handling a s m) where
-- typeOf _ = unsafePerformIO $ do
-- i <- atomicModifyIORef supply $ \a -> let a' = a + 1 in a' `seq` (a', a)
-- return $ mkTyConApp (mkTyCon3 "lens" "Control.Lens.Internal.Exception" ("Handling" ++ show i)) []
-- {-# INLINE typeOf #-}
+-{-# ANN module "HLint: ignore Avoid lambda" #-}
-
---- The @Handling@ wrapper is uninteresting, and should never be thrown, so you won't get much benefit here.
--instance Show (Handling a s m) where
-- showsPrec d _ = showParen (d > 10) $ showString "Handling ..."
-- {-# INLINE showsPrec #-}
--
--instance Reifies s (SomeException -> Maybe a) => Exception (Handling a s m) where
-- toException _ = SomeException HandlingException
-- {-# INLINE toException #-}
-- fromException = fmap Handling . reflect (Proxy :: Proxy s)
-- {-# INLINE fromException #-}
+ class Typeable s => B s where
+ reflectByte :: proxy s -> IntPtr
+
diff --git a/src/Control/Lens/Prism.hs b/src/Control/Lens/Prism.hs
-index 45b5cfe..88c7ff9 100644
+index 9e0bec7..0cf6737 100644
--- a/src/Control/Lens/Prism.hs
+++ b/src/Control/Lens/Prism.hs
-@@ -53,8 +53,6 @@ import Unsafe.Coerce
+@@ -59,8 +59,6 @@ import Unsafe.Coerce
import Data.Profunctor.Unsafe
#endif
@@ -170,6 +186,18 @@ index 45b5cfe..88c7ff9 100644
-- $setup
-- >>> :set -XNoOverloadedStrings
-- >>> import Control.Lens
+diff --git a/src/Control/Monad/Primitive/Lens.hs b/src/Control/Monad/Primitive/Lens.hs
+index ee942c6..2f37134 100644
+--- a/src/Control/Monad/Primitive/Lens.hs
++++ b/src/Control/Monad/Primitive/Lens.hs
+@@ -20,7 +20,6 @@ import Control.Lens
+ import Control.Monad.Primitive (PrimMonad(..))
+ import GHC.Prim (State#)
+
+-{-# ANN module "HLint: ignore Unused LANGUAGE pragma" #-}
+
+ prim :: (PrimMonad m) => Iso' (m a) (State# (PrimState m) -> (# State# (PrimState m), a #))
+ prim = iso internal primitive
--
-1.8.5.1
+1.7.10.4
diff --git a/standalone/no-th/haskell-patches/yesod-core_expand_TH.patch b/standalone/no-th/haskell-patches/yesod-core_expand_TH.patch
index d5596395a1..adf0679ead 100644
--- a/standalone/no-th/haskell-patches/yesod-core_expand_TH.patch
+++ b/standalone/no-th/haskell-patches/yesod-core_expand_TH.patch
@@ -1,17 +1,17 @@
-From 08cc43788c16fb91f63bc0bd520eeccdcdab477a Mon Sep 17 00:00:00 2001
+From 5f30a68faaa379ac3fe9f0b016dd1a20969d548f Mon Sep 17 00:00:00 2001
From: dummy
-Date: Tue, 17 Dec 2013 17:15:33 +0000
+Date: Fri, 7 Feb 2014 23:04:06 +0000
Subject: [PATCH] remove and expand TH
---
- Yesod/Core.hs | 30 +++---
- Yesod/Core/Class/Yesod.hs | 249 +++++++++++++++++++++++++++++++--------------
- Yesod/Core/Dispatch.hs | 27 ++---
- Yesod/Core/Handler.hs | 25 ++---
- Yesod/Core/Internal/Run.hs | 4 +-
- Yesod/Core/Internal/TH.hs | 111 --------------------
- Yesod/Core/Widget.hs | 32 +-----
- 7 files changed, 209 insertions(+), 269 deletions(-)
+ Yesod/Core.hs | 30 +++---
+ Yesod/Core/Class/Yesod.hs | 248 ++++++++++++++++++++++++++++++--------------
+ Yesod/Core/Dispatch.hs | 37 ++-----
+ Yesod/Core/Handler.hs | 25 ++---
+ Yesod/Core/Internal/Run.hs | 4 +-
+ Yesod/Core/Internal/TH.hs | 111 --------------------
+ Yesod/Core/Widget.hs | 32 +-----
+ 7 files changed, 209 insertions(+), 278 deletions(-)
diff --git a/Yesod/Core.hs b/Yesod/Core.hs
index 12e59d5..2817a69 100644
@@ -67,7 +67,7 @@ index 12e59d5..2817a69 100644
, renderCssUrl
) where
diff --git a/Yesod/Core/Class/Yesod.hs b/Yesod/Core/Class/Yesod.hs
-index a64d6eb..5dffbfa 100644
+index 140600b..6c718e2 100644
--- a/Yesod/Core/Class/Yesod.hs
+++ b/Yesod/Core/Class/Yesod.hs
@@ -5,11 +5,15 @@
@@ -127,7 +127,7 @@ index a64d6eb..5dffbfa 100644
-- | Override the rendering function for a particular URL. One use case for
-- this is to offload static hosting to a different domain name to avoid
-@@ -370,45 +383,103 @@ widgetToPageContent w = do
+@@ -374,45 +387,103 @@ widgetToPageContent w = do
-- modernizr should be at the end of the http://www.modernizr.com/docs/#installing
-- the asynchronous loader means your page doesn't have to wait for all the js to load
let (mcomplete, asyncScripts) = asyncHelper render scripts jscript jsLoc
@@ -270,7 +270,7 @@ index a64d6eb..5dffbfa 100644
return $ PageContent title headAll $
case jsLoader master of
-@@ -438,10 +509,13 @@ defaultErrorHandler NotFound = selectRep $ do
+@@ -442,10 +513,13 @@ defaultErrorHandler NotFound = selectRep $ do
r <- waiRequest
let path' = TE.decodeUtf8With TEE.lenientDecode $ W.rawPathInfo r
setTitle "Not Found"
@@ -288,7 +288,7 @@ index a64d6eb..5dffbfa 100644
provideRep $ return $ object ["message" .= ("Not Found" :: Text)]
-- For API requests.
-@@ -451,10 +525,11 @@ defaultErrorHandler NotFound = selectRep $ do
+@@ -455,10 +529,11 @@ defaultErrorHandler NotFound = selectRep $ do
defaultErrorHandler NotAuthenticated = selectRep $ do
provideRep $ defaultLayout $ do
setTitle "Not logged in"
@@ -304,7 +304,7 @@ index a64d6eb..5dffbfa 100644
provideRep $ do
-- 401 *MUST* include a WWW-Authenticate header
-@@ -476,10 +551,13 @@ defaultErrorHandler NotAuthenticated = selectRep $ do
+@@ -480,10 +555,13 @@ defaultErrorHandler NotAuthenticated = selectRep $ do
defaultErrorHandler (PermissionDenied msg) = selectRep $ do
provideRep $ defaultLayout $ do
setTitle "Permission Denied"
@@ -322,7 +322,7 @@ index a64d6eb..5dffbfa 100644
provideRep $
return $ object $ [
"message" .= ("Permission Denied. " <> msg)
-@@ -488,30 +566,43 @@ defaultErrorHandler (PermissionDenied msg) = selectRep $ do
+@@ -492,30 +570,42 @@ defaultErrorHandler (PermissionDenied msg) = selectRep $ do
defaultErrorHandler (InvalidArgs ia) = selectRep $ do
provideRep $ defaultLayout $ do
setTitle "Invalid Arguments"
@@ -377,15 +377,19 @@ index a64d6eb..5dffbfa 100644
+ id
+ ((Text.Blaze.Internal.preEscapedText . T.pack)
+ " not supported
") }
-+
- provideRep $ return $ object ["message" .= ("Bad method" :: Text), "method" .= m]
+ provideRep $ return $ object ["message" .= ("Bad method" :: Text), "method" .= TE.decodeUtf8With TEE.lenientDecode m]
asyncHelper :: (url -> [x] -> Text)
diff --git a/Yesod/Core/Dispatch.hs b/Yesod/Core/Dispatch.hs
-index df822e2..5583495 100644
+index e6f489d..3ff37c1 100644
--- a/Yesod/Core/Dispatch.hs
+++ b/Yesod/Core/Dispatch.hs
-@@ -6,18 +6,18 @@
+@@ -1,4 +1,3 @@
+-{-# LANGUAGE TemplateHaskell #-}
+ {-# LANGUAGE OverloadedStrings #-}
+ {-# LANGUAGE TypeFamilies #-}
+ {-# LANGUAGE FlexibleInstances #-}
+@@ -6,18 +5,18 @@
{-# LANGUAGE CPP #-}
module Yesod.Core.Dispatch
( -- * Quasi-quoted routing
@@ -414,7 +418,7 @@ index df822e2..5583495 100644
, PathMultiPiece (..)
, Texts
-- * Convert to WAI
-@@ -124,13 +124,6 @@ toWaiApp site = do
+@@ -128,13 +127,6 @@ toWaiAppLogger logger site = do
, yreSite = site
, yreSessionBackend = sb
}
@@ -428,8 +432,31 @@ index df822e2..5583495 100644
middleware <- mkDefaultMiddlewares logger
return $ middleware $ toWaiAppYre yre
+@@ -163,13 +155,7 @@ warp port site = do
+ ]
+ -}
+ , Network.Wai.Handler.Warp.settingsOnException = const $ \e ->
+- messageLoggerSource
+- site
+- logger
+- $(qLocation >>= liftLoc)
+- "yesod-core"
+- LevelError
+- (toLogStr $ "Exception from Warp: " ++ show e)
++ error (show e)
+ }
+
+ -- | A default set of middlewares.
+@@ -194,7 +180,6 @@ mkDefaultMiddlewares logger = do
+ -- | Deprecated synonym for 'warp'.
+ warpDebug :: YesodDispatch site => Int -> site -> IO ()
+ warpDebug = warp
+-{-# DEPRECATED warpDebug "Please use warp instead" #-}
+
+ -- | Runs your application using default middlewares (i.e., via 'toWaiApp'). It
+ -- reads port information from the PORT environment variable, as used by tools
diff --git a/Yesod/Core/Handler.hs b/Yesod/Core/Handler.hs
-index 3581dbc..908256e 100644
+index 7c561c5..847d475 100644
--- a/Yesod/Core/Handler.hs
+++ b/Yesod/Core/Handler.hs
@@ -164,7 +164,7 @@ import Data.Text.Encoding (decodeUtf8With, encodeUtf8)
@@ -449,7 +476,7 @@ index 3581dbc..908256e 100644
get :: MonadHandler m => m GHState
get = liftHandlerT $ HandlerT $ I.readIORef . handlerState
-@@ -743,19 +744,15 @@ redirectToPost :: (MonadHandler m, RedirectUrl (HandlerSite m) url)
+@@ -748,19 +749,15 @@ redirectToPost :: (MonadHandler m, RedirectUrl (HandlerSite m) url)
-> m a
redirectToPost url = do
urlText <- toTextUrl url
@@ -479,10 +506,10 @@ index 3581dbc..908256e 100644
-- | Wraps the 'Content' generated by 'hamletToContent' in a 'RepHtml'.
hamletToRepHtml :: MonadHandler m => HtmlUrl (Route (HandlerSite m)) -> m Html
diff --git a/Yesod/Core/Internal/Run.hs b/Yesod/Core/Internal/Run.hs
-index 25f51f1..d04d2cd 100644
+index 10871a2..6ed631e 100644
--- a/Yesod/Core/Internal/Run.hs
+++ b/Yesod/Core/Internal/Run.hs
-@@ -15,7 +15,7 @@ import Control.Exception.Lifted (catch)
+@@ -16,7 +16,7 @@ import Control.Exception.Lifted (catch)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Logger (LogLevel (LevelError), LogSource,
@@ -491,7 +518,7 @@ index 25f51f1..d04d2cd 100644
import Control.Monad.Trans.Resource (runResourceT, withInternalState, runInternalState, createInternalState, closeInternalState)
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as S8
-@@ -128,8 +128,6 @@ safeEh :: (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
+@@ -131,8 +131,6 @@ safeEh :: (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
-> ErrorResponse
-> YesodApp
safeEh log' er req = do
@@ -680,5 +707,5 @@ index a972efa..156cd45 100644
ihamletToRepHtml :: (MonadHandler m, RenderMessage (HandlerSite m) message)
=> HtmlUrlI18n message (Route (HandlerSite m))
--
-1.8.5.1
+1.7.10.4
diff --git a/standalone/no-th/haskell-patches/yesod-form_spliced-TH.patch b/standalone/no-th/haskell-patches/yesod-form_spliced-TH.patch
index 0a82434ea3..18cae3a34f 100644
--- a/standalone/no-th/haskell-patches/yesod-form_spliced-TH.patch
+++ b/standalone/no-th/haskell-patches/yesod-form_spliced-TH.patch
@@ -1,19 +1,19 @@
-From fbd8f048c239e34625e438a24213534f6f68c3e8 Mon Sep 17 00:00:00 2001
+From 9f62992414f900fcafa00a838925e24c4365c50f Mon Sep 17 00:00:00 2001
From: dummy
-Date: Tue, 17 Dec 2013 18:34:25 +0000
-Subject: [PATCH] spliced TH
+Date: Fri, 7 Feb 2014 23:11:31 +0000
+Subject: [PATCH] splice TH
---
- Yesod/Form/Fields.hs | 771 ++++++++++++++++++++++++++++++++++++------------
- Yesod/Form/Functions.hs | 239 ++++++++++++---
- Yesod/Form/Jquery.hs | 129 ++++++--
- Yesod/Form/MassInput.hs | 233 ++++++++++++---
- Yesod/Form/Nic.hs | 65 +++-
- yesod-form.cabal | 1 +
+ Yesod/Form/Fields.hs | 771 +++++++++++++++++++++++++++++++++++------------
+ Yesod/Form/Functions.hs | 239 ++++++++++++---
+ Yesod/Form/Jquery.hs | 129 ++++++--
+ Yesod/Form/MassInput.hs | 233 +++++++++++---
+ Yesod/Form/Nic.hs | 65 +++-
+ yesod-form.cabal | 1 +
6 files changed, 1127 insertions(+), 311 deletions(-)
diff --git a/Yesod/Form/Fields.hs b/Yesod/Form/Fields.hs
-index b2a47c6..016c98b 100644
+index 97d0034..016c98b 100644
--- a/Yesod/Form/Fields.hs
+++ b/Yesod/Form/Fields.hs
@@ -1,4 +1,3 @@
@@ -74,7 +74,7 @@ index b2a47c6..016c98b 100644
- , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
-$newline never
--
+-
-|]
+ , fieldView = \theId name attrs val isReq -> toWidget $ \ _render_arOn
+ -> do { id
@@ -103,7 +103,7 @@ index b2a47c6..016c98b 100644
- , fieldView = \theId name attrs val isReq -> toWidget [hamlet|
-$newline never
--
+-
-|]
+ , fieldView = \theId name attrs val isReq -> toWidget $ \ _render_arOz
+ -> do { id
@@ -1789,7 +1789,7 @@ index 2862678..04ddaba 100644
}
where
diff --git a/yesod-form.cabal b/yesod-form.cabal
-index 9e0c710..a39f71f 100644
+index 1f6e0e1..4667861 100644
--- a/yesod-form.cabal
+++ b/yesod-form.cabal
@@ -19,6 +19,7 @@ library
@@ -1798,8 +1798,8 @@ index 9e0c710..a39f71f 100644
, shakespeare-css >= 1.0 && < 1.1
+ , shakespeare
, shakespeare-js >= 1.0.2 && < 1.3
- , persistent >= 1.2 && < 1.3
+ , persistent >= 1.2 && < 1.4
, template-haskell
--
-1.8.5.1
+1.7.10.4
diff --git a/standalone/no-th/haskell-patches/yesod_hack-TH.patch b/standalone/no-th/haskell-patches/yesod_hack-TH.patch
index eedc7df158..4ee8aa5bb2 100644
--- a/standalone/no-th/haskell-patches/yesod_hack-TH.patch
+++ b/standalone/no-th/haskell-patches/yesod_hack-TH.patch
@@ -1,12 +1,13 @@
-From e3d1ead4f02c2c45e64a1ccad5b461cc6fdabbd2 Mon Sep 17 00:00:00 2001
+From 69398345ff1e63bcc6a23fce18e42390328b78d2 Mon Sep 17 00:00:00 2001
From: dummy
Date: Tue, 17 Dec 2013 18:48:56 +0000
Subject: [PATCH] hack for TH
---
- Yesod.hs | 19 ++++++++++++--
- Yesod/Default/Util.hs | 69 ++-------------------------------------------------
- 2 files changed, 19 insertions(+), 69 deletions(-)
+ Yesod.hs | 19 ++++++++++++--
+ Yesod/Default/Main.hs | 23 -----------------
+ Yesod/Default/Util.hs | 69 ++-----------------------------------------------
+ 3 files changed, 19 insertions(+), 92 deletions(-)
diff --git a/Yesod.hs b/Yesod.hs
index b367144..fbe309c 100644
@@ -39,6 +40,49 @@ index b367144..fbe309c 100644
+delete = undefined
+insert = undefined
+
+diff --git a/Yesod/Default/Main.hs b/Yesod/Default/Main.hs
+index 0780539..2c73800 100644
+--- a/Yesod/Default/Main.hs
++++ b/Yesod/Default/Main.hs
+@@ -1,10 +1,8 @@
+ {-# LANGUAGE CPP #-}
+ {-# LANGUAGE DeriveDataTypeable #-}
+ {-# LANGUAGE OverloadedStrings #-}
+-{-# LANGUAGE TemplateHaskell #-}
+ module Yesod.Default.Main
+ ( defaultMain
+- , defaultMainLog
+ , defaultRunner
+ , defaultDevelApp
+ , LogFunc
+@@ -54,27 +52,6 @@ defaultMain load getApp = do
+
+ type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO ()
+
+--- | Same as @defaultMain@, but gets a logging function back as well as an
+--- @Application@ to install Warp exception handlers.
+---
+--- Since 1.2.5
+-defaultMainLog :: (Show env, Read env)
+- => IO (AppConfig env extra)
+- -> (AppConfig env extra -> IO (Application, LogFunc))
+- -> IO ()
+-defaultMainLog load getApp = do
+- config <- load
+- (app, logFunc) <- getApp config
+- runSettings defaultSettings
+- { settingsPort = appPort config
+- , settingsHost = appHost config
+- , settingsOnException = const $ \e -> logFunc
+- $(qLocation >>= liftLoc)
+- "yesod"
+- LevelError
+- (toLogStr $ "Exception from Warp: " ++ show e)
+- } app
+-
+ -- | Run your application continously, listening for SIGINT and exiting
+ -- when received
+ --
diff --git a/Yesod/Default/Util.hs b/Yesod/Default/Util.hs
index a10358e..0547424 100644
--- a/Yesod/Default/Util.hs
@@ -136,5 +180,5 @@ index a10358e..0547424 100644
- else return $ Just ex
- else return Nothing
--
-1.8.5.1
+1.7.10.4
diff --git a/templates/configurators/main.hamlet b/templates/configurators/main.hamlet
index dc2a6ce585..984fe05b01 100644
--- a/templates/configurators/main.hamlet
+++ b/templates/configurators/main.hamlet
@@ -14,25 +14,29 @@
Tune the behavior of git-annex, including how many copies #
to retain of each file, and how much disk space it can use.