Merge branch 'master' into s3-aws
Conflicts: Utility/Url.hs debian/changelog git-annex.cabal
This commit is contained in:
commit
f7847ae98d
282 changed files with 6524 additions and 1207 deletions
6
Annex.hs
6
Annex.hs
|
@ -15,6 +15,7 @@ module Annex (
|
|||
eval,
|
||||
getState,
|
||||
changeState,
|
||||
withState,
|
||||
setFlag,
|
||||
setField,
|
||||
setOutput,
|
||||
|
@ -214,6 +215,11 @@ changeState modifier = do
|
|||
mvar <- ask
|
||||
liftIO $ modifyMVar_ mvar $ return . modifier
|
||||
|
||||
withState :: (AnnexState -> (AnnexState, b)) -> Annex b
|
||||
withState modifier = do
|
||||
mvar <- ask
|
||||
liftIO $ modifyMVar mvar $ return . modifier
|
||||
|
||||
{- Sets a flag to True -}
|
||||
setFlag :: String -> Annex ()
|
||||
setFlag flag = changeState $ \s ->
|
||||
|
|
|
@ -12,6 +12,7 @@ module Annex.CatFile (
|
|||
catTree,
|
||||
catObjectDetails,
|
||||
catFileHandle,
|
||||
catFileStop,
|
||||
catKey,
|
||||
catKeyFile,
|
||||
catKeyFileHEAD,
|
||||
|
@ -71,6 +72,14 @@ catFileHandle = do
|
|||
Annex.changeState $ \s -> s { Annex.catfilehandles = m' }
|
||||
return h
|
||||
|
||||
{- Stops all running cat-files. Should only be run when it's known that
|
||||
- nothing is using the handles, eg at shutdown. -}
|
||||
catFileStop :: Annex ()
|
||||
catFileStop = do
|
||||
m <- Annex.withState $ \s ->
|
||||
(s { Annex.catfilehandles = M.empty }, Annex.catfilehandles s)
|
||||
liftIO $ mapM_ Git.CatFile.catFileStop (M.elems m)
|
||||
|
||||
{- From the Sha or Ref of a symlink back to the key.
|
||||
-
|
||||
- Requires a mode witness, to guarantee that the file is a symlink.
|
||||
|
|
|
@ -56,10 +56,7 @@ import Annex.Perms
|
|||
import Annex.Link
|
||||
import Annex.Content.Direct
|
||||
import Annex.ReplaceFile
|
||||
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.WinLock
|
||||
#endif
|
||||
import Utility.LockFile
|
||||
|
||||
{- Checks if a given key's content is currently present. -}
|
||||
inAnnex :: Key -> Annex Bool
|
||||
|
@ -104,25 +101,21 @@ inAnnexSafe key = inAnnex' (fromMaybe False) (Just False) go key
|
|||
=<< contentLockFile key
|
||||
|
||||
#ifndef mingw32_HOST_OS
|
||||
checkindirect f = liftIO $ openforlock f >>= check is_missing
|
||||
checkindirect contentfile = liftIO $ checkOr is_missing contentfile
|
||||
{- 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. -}
|
||||
- the lock file generally won't exist unless a removal is in
|
||||
- process. -}
|
||||
checkdirect contentfile lockfile = liftIO $
|
||||
ifM (doesFileExist contentfile)
|
||||
( openforlock lockfile >>= check is_unlocked
|
||||
( checkOr is_unlocked lockfile
|
||||
, return is_missing
|
||||
)
|
||||
openforlock f = catchMaybeIO $
|
||||
openFd f ReadOnly Nothing defaultFileFlags
|
||||
check _ (Just h) = do
|
||||
v <- getLock h (ReadLock, AbsoluteSeek, 0, 0)
|
||||
closeFd h
|
||||
checkOr def lockfile = do
|
||||
v <- checkLocked lockfile
|
||||
return $ case v of
|
||||
Just _ -> is_locked
|
||||
Nothing -> is_unlocked
|
||||
check def Nothing = return def
|
||||
Nothing -> def
|
||||
Just True -> is_locked
|
||||
Just False -> is_unlocked
|
||||
#else
|
||||
checkindirect f = liftIO $ ifM (doesFileExist f)
|
||||
( do
|
||||
|
@ -159,14 +152,20 @@ contentLockFile key = ifM isDirect
|
|||
, return Nothing
|
||||
)
|
||||
|
||||
newtype ContentLock = ContentLock Key
|
||||
|
||||
{- 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
|
||||
- it. (If the content is not present, no locking is done.)
|
||||
-}
|
||||
lockContent :: Key -> (ContentLock -> Annex a) -> Annex a
|
||||
lockContent key a = do
|
||||
contentfile <- calcRepo $ gitAnnexLocation key
|
||||
lockfile <- contentLockFile key
|
||||
maybe noop setuplockfile lockfile
|
||||
bracket (liftIO $ lock contentfile lockfile) (unlock lockfile) (const a)
|
||||
bracket
|
||||
(lock contentfile lockfile)
|
||||
(unlock lockfile)
|
||||
(const $ a $ ContentLock key)
|
||||
where
|
||||
alreadylocked = error "content is locked"
|
||||
setuplockfile lockfile = modifyContent lockfile $
|
||||
|
@ -176,17 +175,17 @@ lockContent key a = do
|
|||
void $ liftIO $ tryIO $
|
||||
nukeFile lockfile
|
||||
#ifndef mingw32_HOST_OS
|
||||
lock contentfile Nothing = opencontentforlock contentfile >>= dolock
|
||||
lock _ (Just lockfile) = openforlock lockfile >>= dolock . Just
|
||||
lock contentfile Nothing = liftIO $
|
||||
opencontentforlock contentfile >>= dolock
|
||||
lock _ (Just lockfile) = do
|
||||
mode <- annexFileMode
|
||||
liftIO $ createLockFile mode lockfile >>= dolock . Just
|
||||
{- Since content files are stored with the write bit disabled, have
|
||||
- to fiddle with permissions to open for an exclusive lock. -}
|
||||
opencontentforlock f = catchMaybeIO $ ifM (doesFileExist f)
|
||||
( withModifiedFileMode f
|
||||
opencontentforlock f = catchDefaultIO Nothing $
|
||||
withModifiedFileMode f
|
||||
(`unionFileModes` ownerWriteMode)
|
||||
(openforlock f)
|
||||
, openforlock f
|
||||
)
|
||||
openforlock f = openFd f ReadWrite Nothing defaultFileFlags
|
||||
(openExistingLockFile f)
|
||||
dolock Nothing = return Nothing
|
||||
dolock (Just fd) = do
|
||||
v <- tryIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||
|
@ -197,7 +196,8 @@ lockContent key a = do
|
|||
maybe noop cleanuplockfile mlockfile
|
||||
liftIO $ maybe noop closeFd mfd
|
||||
#else
|
||||
lock _ (Just lockfile) = maybe alreadylocked (return . Just) =<< lockExclusive lockfile
|
||||
lock _ (Just lockfile) = liftIO $
|
||||
maybe alreadylocked (return . Just) =<< lockExclusive lockfile
|
||||
lock _ Nothing = return Nothing
|
||||
unlock mlockfile mlockhandle = do
|
||||
liftIO $ maybe noop dropLock mlockhandle
|
||||
|
@ -377,7 +377,7 @@ sendAnnex key rollback sendobject = go =<< prepSendAnnex key
|
|||
)
|
||||
|
||||
{- Returns a file that contains an object's content,
|
||||
- and an check to run after the transfer is complete.
|
||||
- and a check to run after the transfer is complete.
|
||||
-
|
||||
- In direct mode, it's possible for the file to change as it's being sent,
|
||||
- and the check detects this case and returns False.
|
||||
|
@ -432,9 +432,10 @@ cleanObjectLoc key cleaner = do
|
|||
{- Removes a key's file from .git/annex/objects/
|
||||
-
|
||||
- In direct mode, deletes the associated files or files, and replaces
|
||||
- them with symlinks. -}
|
||||
removeAnnex :: Key -> Annex ()
|
||||
removeAnnex key = withObjectLoc key remove removedirect
|
||||
- them with symlinks.
|
||||
-}
|
||||
removeAnnex :: ContentLock -> Annex ()
|
||||
removeAnnex (ContentLock key) = withObjectLoc key remove removedirect
|
||||
where
|
||||
remove file = cleanObjectLoc key $ do
|
||||
secureErase file
|
||||
|
@ -579,7 +580,7 @@ preseedTmp key file = go =<< inAnnex key
|
|||
( return True
|
||||
, do
|
||||
s <- calcRepo $ gitAnnexLocation key
|
||||
liftIO $ copyFileExternal s file
|
||||
liftIO $ copyFileExternal CopyTimeStamps s file
|
||||
)
|
||||
|
||||
{- Blocks writing to an annexed file, and modifies file permissions to
|
||||
|
|
|
@ -210,7 +210,7 @@ addContentWhenNotPresent key contentfile associatedfile = do
|
|||
v <- isAnnexLink associatedfile
|
||||
when (Just key == v) $
|
||||
replaceFile associatedfile $
|
||||
liftIO . void . copyFileExternal contentfile
|
||||
liftIO . void . copyFileExternal CopyAllMetaData contentfile
|
||||
updateInodeCache key associatedfile
|
||||
|
||||
{- Some filesystems get new inodes each time they are mounted.
|
||||
|
|
|
@ -357,7 +357,7 @@ toDirectGen k f = do
|
|||
`catchIO` (\_ -> freezeContent loc)
|
||||
fromdirect loc = do
|
||||
replaceFile f $
|
||||
liftIO . void . copyFileExternal loc
|
||||
liftIO . void . copyFileExternal CopyAllMetaData loc
|
||||
updateInodeCache k f
|
||||
|
||||
{- Removes a direct mode file, while retaining its content in the annex
|
||||
|
|
|
@ -23,8 +23,11 @@ import qualified Git.LsFiles
|
|||
import qualified Git.Config
|
||||
import qualified Git.Construct
|
||||
import qualified Git.Types as Git
|
||||
import qualified Git.Objects
|
||||
import qualified Annex.Branch
|
||||
import Logs.UUID
|
||||
import Logs.Trust.Basic
|
||||
import Types.TrustLevel
|
||||
import Annex.Version
|
||||
import Annex.UUID
|
||||
import Config
|
||||
|
@ -70,6 +73,7 @@ initialize mdescription = do
|
|||
Annex.Branch.create
|
||||
describeUUID u =<< genDescription mdescription
|
||||
|
||||
-- Everything except for uuid setup.
|
||||
initialize' :: Annex ()
|
||||
initialize' = do
|
||||
checkFifoSupport
|
||||
|
@ -87,6 +91,7 @@ initialize' = do
|
|||
switchHEADBack
|
||||
)
|
||||
createInodeSentinalFile
|
||||
checkSharedClone
|
||||
|
||||
uninitialize :: Annex ()
|
||||
uninitialize = do
|
||||
|
@ -242,3 +247,10 @@ checkBadBare = allM (not <$>)
|
|||
where
|
||||
hasPreCommitHook = inRepo $ doesFileExist . hookFile preCommitHook
|
||||
hasDotGitHEAD = inRepo $ \r -> doesFileExist $ Git.localGitDir r </> "HEAD"
|
||||
|
||||
checkSharedClone :: Annex ()
|
||||
checkSharedClone = whenM (inRepo Git.Objects.isSharedClone) $ do
|
||||
showSideAction "Repository was cloned with --shared; setting annex.hardlink=true and making repository untrusted."
|
||||
u <- getUUID
|
||||
trustSet u UnTrusted
|
||||
setConfig (annexConfig "hardlink") (Git.Config.boolConfig True)
|
||||
|
|
|
@ -19,13 +19,10 @@ import Annex
|
|||
import Types.LockPool
|
||||
import qualified Git
|
||||
import Annex.Perms
|
||||
import Utility.LockFile
|
||||
|
||||
import qualified Data.Map as M
|
||||
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.WinLock
|
||||
#endif
|
||||
|
||||
{- Create a specified lock file, and takes a shared lock, which is retained
|
||||
- in the pool. -}
|
||||
lockFileShared :: FilePath -> Annex ()
|
||||
|
@ -35,9 +32,7 @@ lockFileShared file = go =<< fromLockPool file
|
|||
go Nothing = do
|
||||
#ifndef mingw32_HOST_OS
|
||||
mode <- annexFileMode
|
||||
lockhandle <- liftIO $ noUmask mode $
|
||||
openFd file ReadOnly (Just mode) defaultFileFlags
|
||||
liftIO $ waitToSetLock lockhandle (ReadLock, AbsoluteSeek, 0, 0)
|
||||
lockhandle <- liftIO $ noUmask mode $ lockShared (Just mode) file
|
||||
#else
|
||||
lockhandle <- liftIO $ waitToLock $ lockShared file
|
||||
#endif
|
||||
|
@ -47,11 +42,7 @@ unlockFile :: FilePath -> Annex ()
|
|||
unlockFile file = maybe noop go =<< fromLockPool file
|
||||
where
|
||||
go lockhandle = do
|
||||
#ifndef mingw32_HOST_OS
|
||||
liftIO $ closeFd lockhandle
|
||||
#else
|
||||
liftIO $ dropLock lockhandle
|
||||
#endif
|
||||
changeLockPool $ M.delete file
|
||||
|
||||
getLockPool :: Annex LockPool
|
||||
|
@ -72,15 +63,10 @@ withExclusiveLock getlockfile a = do
|
|||
lockfile <- fromRepo getlockfile
|
||||
createAnnexDirectory $ takeDirectory lockfile
|
||||
mode <- annexFileMode
|
||||
bracketIO (lock lockfile mode) unlock (const a)
|
||||
bracketIO (lock mode lockfile) dropLock (const a)
|
||||
where
|
||||
#ifndef mingw32_HOST_OS
|
||||
lock lockfile mode = do
|
||||
l <- noUmask mode $ createFile lockfile mode
|
||||
waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
|
||||
return l
|
||||
unlock = closeFd
|
||||
lock mode = noUmask mode . lockExclusive (Just mode)
|
||||
#else
|
||||
lock lockfile _mode = waitToLock $ lockExclusive lockfile
|
||||
unlock = dropLock
|
||||
lock _mode = waitToLock . lockExclusive
|
||||
#endif
|
||||
|
|
13
Annex/Ssh.hs
13
Annex/Ssh.hs
|
@ -35,6 +35,7 @@ import Config.Files
|
|||
import Utility.Env
|
||||
import Types.CleanupActions
|
||||
import Annex.Index (addGitEnv)
|
||||
import Utility.LockFile
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Annex.Perms
|
||||
#endif
|
||||
|
@ -151,14 +152,12 @@ sshCleanup = mapM_ cleanup =<< enumSocketFiles
|
|||
let lockfile = socket2lock socketfile
|
||||
unlockFile lockfile
|
||||
mode <- annexFileMode
|
||||
fd <- liftIO $ noUmask mode $
|
||||
openFd lockfile ReadWrite (Just mode) defaultFileFlags
|
||||
v <- liftIO $ tryIO $
|
||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||
v <- liftIO $ noUmask mode $ tryLockExclusive (Just mode) lockfile
|
||||
case v of
|
||||
Left _ -> noop
|
||||
Right _ -> forceStopSsh socketfile
|
||||
liftIO $ closeFd fd
|
||||
Nothing -> noop
|
||||
Just lck -> do
|
||||
forceStopSsh socketfile
|
||||
liftIO $ dropLock lck
|
||||
#else
|
||||
forceStopSsh socketfile
|
||||
#endif
|
||||
|
|
|
@ -23,7 +23,7 @@ import Annex.Notification as X
|
|||
import Annex.Perms
|
||||
import Utility.Metered
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.WinLock
|
||||
import Utility.LockFile
|
||||
#endif
|
||||
|
||||
import Control.Concurrent
|
||||
|
@ -81,10 +81,13 @@ runTransfer' ignorelock t file shouldretry a = do
|
|||
case mfd of
|
||||
Nothing -> return (Nothing, False)
|
||||
Just fd -> do
|
||||
setFdOption fd CloseOnExec True
|
||||
locked <- catchMaybeIO $
|
||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||
if isNothing locked
|
||||
then return (Nothing, True)
|
||||
then do
|
||||
closeFd fd
|
||||
return (Nothing, True)
|
||||
else do
|
||||
void $ tryIO $ writeTransferInfoFile info tfile
|
||||
return (mfd, False)
|
||||
|
|
|
@ -26,7 +26,7 @@ getUserAgent = Annex.getState $
|
|||
Just . fromMaybe defaultUserAgent . Annex.useragent
|
||||
|
||||
getUrlOptions :: Annex U.UrlOptions
|
||||
getUrlOptions = U.UrlOptions
|
||||
getUrlOptions = mkUrlOptions
|
||||
<$> getUserAgent
|
||||
<*> headers
|
||||
<*> options
|
||||
|
|
|
@ -53,6 +53,10 @@ postRestart url = do
|
|||
liftIO . sendNotification . globalRedirNotifier =<< getDaemonStatus
|
||||
void $ liftIO $ forkIO $ do
|
||||
threadDelaySeconds (Seconds 120)
|
||||
terminateSelf
|
||||
|
||||
terminateSelf :: IO ()
|
||||
terminateSelf =
|
||||
#ifndef mingw32_HOST_OS
|
||||
signalProcess sigTERM =<< getPID
|
||||
#else
|
||||
|
|
|
@ -21,7 +21,9 @@ import Assistant.Drop
|
|||
import Assistant.Ssh
|
||||
import Assistant.TransferQueue
|
||||
import Assistant.Types.UrlRenderer
|
||||
import Assistant.Restart
|
||||
import qualified Annex.Branch
|
||||
import qualified Git
|
||||
import qualified Git.LsFiles
|
||||
import qualified Git.Command.Batch
|
||||
import qualified Git.Config
|
||||
|
@ -146,6 +148,8 @@ waitForNextCheck = do
|
|||
- will block the watcher. -}
|
||||
dailyCheck :: UrlRenderer -> Assistant Bool
|
||||
dailyCheck urlrenderer = do
|
||||
checkRepoExists
|
||||
|
||||
g <- liftAnnex gitRepo
|
||||
batchmaker <- liftIO getBatchCommandMaker
|
||||
|
||||
|
@ -203,6 +207,7 @@ dailyCheck urlrenderer = do
|
|||
|
||||
hourlyCheck :: Assistant ()
|
||||
hourlyCheck = do
|
||||
checkRepoExists
|
||||
#ifndef mingw32_HOST_OS
|
||||
checkLogSize 0
|
||||
#else
|
||||
|
@ -316,3 +321,9 @@ cleanOld check f = go =<< catchMaybeIO getmtime
|
|||
getmtime = realToFrac . modificationTime <$> getSymbolicLinkStatus f
|
||||
go (Just mtime) | check mtime = nukeFile f
|
||||
go _ = noop
|
||||
|
||||
checkRepoExists :: Assistant ()
|
||||
checkRepoExists = do
|
||||
g <- liftAnnex gitRepo
|
||||
liftIO $ unlessM (doesDirectoryExist $ Git.repoPath g) $
|
||||
terminateSelf
|
||||
|
|
|
@ -77,7 +77,7 @@ expireUnused duration = do
|
|||
forM_ oldkeys $ \k -> do
|
||||
debug ["removing old unused key", key2file k]
|
||||
liftAnnex $ do
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
logStatus k InfoMissing
|
||||
where
|
||||
boundry = durationToPOSIXTime <$> duration
|
||||
|
|
|
@ -96,7 +96,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
|
|||
, transferKey = k
|
||||
}
|
||||
cleanup = liftAnnex $ do
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
setUrlMissing k u
|
||||
logStatus k InfoMissing
|
||||
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
||||
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
||||
|
||||
module Assistant.WebApp.Control where
|
||||
|
||||
|
@ -16,16 +16,10 @@ import Assistant.TransferSlots
|
|||
import Assistant.Restart
|
||||
import Utility.LogFile
|
||||
import Utility.NotificationBroadcaster
|
||||
import Utility.PID
|
||||
|
||||
import Control.Concurrent
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Text as T
|
||||
#ifndef mingw32_HOST_OS
|
||||
import System.Posix (signalProcess, sigTERM)
|
||||
#else
|
||||
import Utility.WinProcess
|
||||
#endif
|
||||
|
||||
getShutdownR :: Handler Html
|
||||
getShutdownR = page "Shutdown" Nothing $
|
||||
|
@ -53,15 +47,11 @@ getShutdownConfirmedR = do
|
|||
- page time to load in the browser. -}
|
||||
void $ liftIO $ forkIO $ do
|
||||
threadDelay 2000000
|
||||
#ifndef mingw32_HOST_OS
|
||||
signalProcess sigTERM =<< getPID
|
||||
#else
|
||||
terminatePID =<< getPID
|
||||
#endif
|
||||
terminateSelf
|
||||
redirect NotRunningR
|
||||
|
||||
{- Use a custom page to avoid putting long polling elements on it that will
|
||||
- fail and cause the web browser to show an error once the webapp is
|
||||
- fail and cause thet web browser to show an error once the webapp is
|
||||
- truely stopped. -}
|
||||
getNotRunningR :: Handler Html
|
||||
getNotRunningR = customPage' False Nothing $
|
||||
|
|
|
@ -12,6 +12,7 @@ import Types.Backend
|
|||
import Types.Key
|
||||
import Types.KeySource
|
||||
import Backend.Utilities
|
||||
import Git.FilePath
|
||||
|
||||
backends :: [Backend]
|
||||
backends = [backend]
|
||||
|
@ -27,16 +28,13 @@ backend = Backend
|
|||
}
|
||||
|
||||
{- The key includes the file size, modification time, and the
|
||||
- basename of the filename.
|
||||
-
|
||||
- That allows multiple files with the same names to have different keys,
|
||||
- while also allowing a file to be moved around while retaining the
|
||||
- same key.
|
||||
- original filename relative to the top of the git repository.
|
||||
-}
|
||||
keyValue :: KeySource -> Annex (Maybe Key)
|
||||
keyValue source = do
|
||||
stat <- liftIO $ getFileStatus $ contentLocation source
|
||||
n <- genKeyName $ takeFileName $ keyFilename source
|
||||
relf <- getTopFilePath <$> inRepo (toTopFilePath $ keyFilename source)
|
||||
n <- genKeyName relf
|
||||
return $ Just $ stubKey
|
||||
{ keyName = n
|
||||
, keyBackendName = name backend
|
||||
|
|
|
@ -23,6 +23,7 @@ tests =
|
|||
, TestCase "git version" getGitVersion
|
||||
, testCp "cp_a" "-a"
|
||||
, testCp "cp_p" "-p"
|
||||
, testCp "cp_preserve_timestamps" "--preserve=timestamps"
|
||||
, testCp "cp_reflink_auto" "--reflink=auto"
|
||||
, TestCase "xargs -0" $ requireCmd "xargs_0" "xargs -0 </dev/null"
|
||||
, TestCase "rsync" $ requireCmd "rsync" "rsync --version >/dev/null"
|
||||
|
|
|
@ -82,7 +82,7 @@ symToHardLink f = whenM (isSymbolicLink <$> getSymbolicLinkStatus f) $ do
|
|||
installFile :: FilePath -> FilePath -> IO ()
|
||||
installFile top f = do
|
||||
createDirectoryIfMissing True destdir
|
||||
void $ copyFileExternal f destdir
|
||||
void $ copyFileExternal CopyTimeStamps f destdir
|
||||
where
|
||||
destdir = inTop top $ parentDir f
|
||||
|
||||
|
|
30
CmdLine.hs
30
CmdLine.hs
|
@ -6,6 +6,7 @@
|
|||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE BangPatterns #-}
|
||||
|
||||
module CmdLine (
|
||||
dispatch,
|
||||
|
@ -25,6 +26,7 @@ import Common.Annex
|
|||
import qualified Annex
|
||||
import qualified Git
|
||||
import qualified Git.AutoCorrect
|
||||
import qualified Git.Config
|
||||
import Annex.Content
|
||||
import Annex.Environment
|
||||
import Command
|
||||
|
@ -34,14 +36,17 @@ import Types.Messages
|
|||
dispatch :: Bool -> CmdParams -> [Command] -> [Option] -> [(String, String)] -> String -> IO Git.Repo -> IO ()
|
||||
dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
|
||||
setupConsole
|
||||
r <- E.try getgitrepo :: IO (Either E.SomeException Git.Repo)
|
||||
case r of
|
||||
Left e -> maybe (throw e) (\a -> a params) (cmdnorepo cmd)
|
||||
Right g -> do
|
||||
case getOptCmd args cmd commonoptions of
|
||||
Right (flags, params) -> go flags params
|
||||
=<< (E.try getgitrepo :: IO (Either E.SomeException Git.Repo))
|
||||
Left parseerr -> error parseerr
|
||||
where
|
||||
go flags params (Right g) = do
|
||||
state <- Annex.new g
|
||||
Annex.eval state $ do
|
||||
checkEnvironment
|
||||
checkfuzzy
|
||||
when fuzzy $
|
||||
inRepo $ autocorrect . Just
|
||||
forM_ fields $ uncurry Annex.setField
|
||||
when (cmdnomessages cmd) $
|
||||
Annex.setOutput QuietOutput
|
||||
|
@ -51,13 +56,14 @@ dispatch fuzzyok allargs allcmds commonoptions fields header getgitrepo = do
|
|||
startup
|
||||
performCommandAction cmd params
|
||||
shutdown $ cmdnocommit cmd
|
||||
where
|
||||
go _flags params (Left e) = do
|
||||
when fuzzy $
|
||||
autocorrect =<< Git.Config.global
|
||||
maybe (throw e) (\a -> a params) (cmdnorepo cmd)
|
||||
err msg = msg ++ "\n\n" ++ usage header allcmds
|
||||
cmd = Prelude.head cmds
|
||||
(fuzzy, cmds, name, args) = findCmd fuzzyok allargs allcmds err
|
||||
(flags, params) = getOptCmd args cmd commonoptions
|
||||
checkfuzzy = when fuzzy $
|
||||
inRepo $ Git.AutoCorrect.prepare name cmdname cmds
|
||||
autocorrect = Git.AutoCorrect.prepare name cmdname cmds
|
||||
|
||||
{- Parses command line params far enough to find the Command to run, and
|
||||
- returns the remaining params.
|
||||
|
@ -81,12 +87,12 @@ findCmd fuzzyok argv cmds err
|
|||
|
||||
{- Parses command line options, and returns actions to run to configure flags
|
||||
- and the remaining parameters for the command. -}
|
||||
getOptCmd :: CmdParams -> Command -> [Option] -> ([Annex ()], CmdParams)
|
||||
getOptCmd :: CmdParams -> Command -> [Option] -> Either String ([Annex ()], CmdParams)
|
||||
getOptCmd argv cmd commonoptions = check $
|
||||
getOpt Permute (commonoptions ++ cmdoptions cmd) argv
|
||||
where
|
||||
check (flags, rest, []) = (flags, rest)
|
||||
check (_, _, errs) = error $ unlines
|
||||
check (flags, rest, []) = Right (flags, rest)
|
||||
check (_, _, errs) = Left $ unlines
|
||||
[ concat errs
|
||||
, commandUsage cmd
|
||||
]
|
||||
|
|
|
@ -96,8 +96,8 @@ import qualified Command.XMPPGit
|
|||
#endif
|
||||
import qualified Command.RemoteDaemon
|
||||
#endif
|
||||
#ifdef WITH_TESTSUITE
|
||||
import qualified Command.Test
|
||||
#ifdef WITH_TESTSUITE
|
||||
import qualified Command.FuzzTest
|
||||
import qualified Command.TestRemote
|
||||
#endif
|
||||
|
@ -188,8 +188,8 @@ cmds = concat
|
|||
#endif
|
||||
, Command.RemoteDaemon.def
|
||||
#endif
|
||||
#ifdef WITH_TESTSUITE
|
||||
, Command.Test.def
|
||||
#ifdef WITH_TESTSUITE
|
||||
, Command.FuzzTest.def
|
||||
, Command.TestRemote.def
|
||||
#endif
|
||||
|
|
|
@ -189,10 +189,9 @@ seekHelper :: ([FilePath] -> Git.Repo -> IO ([FilePath], IO Bool)) -> [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
|
||||
error $ p ++ " not found"
|
||||
return $ concat ll
|
||||
|
||||
notSymlink :: FilePath -> IO Bool
|
||||
|
|
|
@ -75,14 +75,19 @@ start file = ifAnnexed file addpresent add
|
|||
showStart "add" file
|
||||
next $ perform file
|
||||
addpresent key = ifM isDirect
|
||||
( ifM (goodContent key file) ( stop , add )
|
||||
( do
|
||||
ms <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
|
||||
case ms of
|
||||
Just s | isSymbolicLink s -> fixup key
|
||||
_ -> ifM (goodContent key file) ( stop , add )
|
||||
, fixup key
|
||||
)
|
||||
fixup key = do
|
||||
-- fixup from an interrupted add; the symlink
|
||||
-- is present but not yet added to git
|
||||
-- the annexed symlink is present but not yet added to git
|
||||
showStart "add" file
|
||||
liftIO $ removeFile file
|
||||
whenM isDirect $
|
||||
void $ addAssociatedFile key file
|
||||
next $ next $ cleanup file key Nothing =<< inAnnex key
|
||||
|
||||
{- The file that's being added is locked down before a key is generated,
|
||||
|
|
|
@ -55,8 +55,12 @@ startRemote afile numcopies key remote = do
|
|||
showStart' ("drop " ++ Remote.name remote) key afile
|
||||
next $ performRemote key afile numcopies remote
|
||||
|
||||
-- Note that lockContent is called before checking if the key is present
|
||||
-- on enough remotes to allow removal. This avoids a scenario where two
|
||||
-- or more remotes are trying to remove a key at the same time, and each
|
||||
-- see the key is present on the other.
|
||||
performLocal :: Key -> AssociatedFile -> NumCopies -> Maybe Remote -> CommandPerform
|
||||
performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
||||
performLocal key afile numcopies knownpresentremote = lockContent key $ \contentlock -> do
|
||||
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
|
||||
let trusteduuids' = case knownpresentremote of
|
||||
Nothing -> trusteduuids
|
||||
|
@ -66,7 +70,7 @@ performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
|||
u <- getUUID
|
||||
ifM (canDrop u key afile numcopies trusteduuids' tocheck [])
|
||||
( do
|
||||
removeAnnex key
|
||||
removeAnnex contentlock
|
||||
notifyDrop afile True
|
||||
next $ cleanupLocal key
|
||||
, do
|
||||
|
@ -75,7 +79,7 @@ performLocal key afile numcopies knownpresentremote = lockContent key $ do
|
|||
)
|
||||
|
||||
performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
|
||||
performRemote key afile numcopies remote = lockContent key $ do
|
||||
performRemote key afile numcopies remote = do
|
||||
-- Filter the remote it's being dropped from out of the lists of
|
||||
-- places assumed to have the key, and places to check.
|
||||
-- When the local repo has the key, that's one additional copy,
|
||||
|
|
|
@ -28,8 +28,8 @@ start key = stopUnless (inAnnex key) $ do
|
|||
next $ perform key
|
||||
|
||||
perform :: Key -> CommandPerform
|
||||
perform key = lockContent key $ do
|
||||
removeAnnex key
|
||||
perform key = lockContent key $ \contentlock -> do
|
||||
removeAnnex contentlock
|
||||
next $ cleanup key
|
||||
|
||||
cleanup :: Key -> CommandCleanup
|
||||
|
|
|
@ -90,7 +90,7 @@ start mode (srcfile, destfile) =
|
|||
handleexisting =<< liftIO (catchMaybeIO $ getSymbolicLinkStatus destfile)
|
||||
liftIO $ createDirectoryIfMissing True (parentDir destfile)
|
||||
liftIO $ if mode == Duplicate || mode == SkipDuplicates
|
||||
then void $ copyFileExternal srcfile destfile
|
||||
then void $ copyFileExternal CopyAllMetaData srcfile destfile
|
||||
else moveFile srcfile destfile
|
||||
Command.Add.perform destfile
|
||||
handleexisting Nothing = noop
|
||||
|
|
|
@ -91,7 +91,7 @@ expectedPresent dest key = do
|
|||
return $ dest `elem` remotes
|
||||
|
||||
toPerform :: Remote -> Bool -> Key -> AssociatedFile -> Bool -> Either String Bool -> CommandPerform
|
||||
toPerform dest move key afile fastcheck isthere = moveLock move key $
|
||||
toPerform dest move key afile fastcheck isthere = do
|
||||
case isthere of
|
||||
Left err -> do
|
||||
showNote err
|
||||
|
@ -115,8 +115,8 @@ toPerform dest move key afile fastcheck isthere = moveLock move key $
|
|||
finish
|
||||
where
|
||||
finish
|
||||
| move = do
|
||||
removeAnnex key
|
||||
| move = lockContent key $ \contentlock -> do
|
||||
removeAnnex contentlock
|
||||
next $ Command.Drop.cleanupLocal key
|
||||
| otherwise = next $ return True
|
||||
|
||||
|
@ -150,8 +150,7 @@ fromOk src key = go =<< Annex.getState Annex.force
|
|||
return $ u /= Remote.uuid src && elem src remotes
|
||||
|
||||
fromPerform :: Remote -> Bool -> Key -> AssociatedFile -> CommandPerform
|
||||
fromPerform src move key afile = moveLock move key $
|
||||
ifM (inAnnex key)
|
||||
fromPerform src move key afile = ifM (inAnnex key)
|
||||
( dispatch move True
|
||||
, dispatch move =<< go
|
||||
)
|
||||
|
@ -165,9 +164,3 @@ fromPerform src move key afile = moveLock move key $
|
|||
dispatch True True = do -- finish moving
|
||||
ok <- Remote.removeKey src key
|
||||
next $ Command.Drop.cleanupRemote key src ok
|
||||
|
||||
{- Locks a key in order for it to be moved.
|
||||
- No lock is needed when a key is being copied. -}
|
||||
moveLock :: Bool -> Key -> Annex a -> Annex a
|
||||
moveLock True key a = lockContent key a
|
||||
moveLock False _ a = a
|
||||
|
|
|
@ -18,16 +18,12 @@ import Annex.Direct
|
|||
import Annex.Hook
|
||||
import Annex.View
|
||||
import Annex.View.ViewedFile
|
||||
import Annex.Perms
|
||||
import Annex.LockFile
|
||||
import Logs.View
|
||||
import Logs.MetaData
|
||||
import Types.View
|
||||
import Types.MetaData
|
||||
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.WinLock
|
||||
#endif
|
||||
|
||||
import qualified Data.Set as S
|
||||
|
||||
def :: [Command]
|
||||
|
@ -92,19 +88,4 @@ showMetaDataChange = showLongNote . unlines . concatMap showmeta . fromMetaData
|
|||
|
||||
{- Takes exclusive lock; blocks until available. -}
|
||||
lockPreCommitHook :: Annex a -> Annex a
|
||||
lockPreCommitHook a = do
|
||||
lockfile <- fromRepo gitAnnexPreCommitLock
|
||||
createAnnexDirectory $ takeDirectory lockfile
|
||||
mode <- annexFileMode
|
||||
bracketIO (lock lockfile mode) unlock (const a)
|
||||
where
|
||||
#ifndef mingw32_HOST_OS
|
||||
lock lockfile mode = do
|
||||
l <- liftIO $ noUmask mode $ createFile lockfile mode
|
||||
liftIO $ waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
|
||||
return l
|
||||
unlock = closeFd
|
||||
#else
|
||||
lock lockfile _mode = liftIO $ waitToLock $ lockExclusive lockfile
|
||||
unlock = dropLock
|
||||
#endif
|
||||
lockPreCommitHook = withExclusiveLock gitAnnexPreCommitLock
|
||||
|
|
|
@ -44,7 +44,7 @@ fieldTransfer :: Direction -> Key -> (MeterUpdate -> Annex Bool) -> CommandStart
|
|||
fieldTransfer direction key a = do
|
||||
afile <- Fields.getField Fields.associatedFile
|
||||
ok <- maybe (a $ const noop)
|
||||
(\u -> runTransfer (Transfer direction (toUUID u) key) afile noRetry a)
|
||||
(\u -> runner (Transfer direction (toUUID u) key) afile noRetry a)
|
||||
=<< Fields.getField Fields.remoteUUID
|
||||
liftIO $ exitBool ok
|
||||
where
|
||||
|
|
|
@ -122,15 +122,15 @@ syncRemotes rs = ifM (Annex.getState Annex.fast) ( nub <$> pickfast , wanted )
|
|||
fastest = fromMaybe [] . headMaybe . Remote.byCost
|
||||
|
||||
commit :: CommandStart
|
||||
commit = next $ next $ ifM isDirect
|
||||
( do
|
||||
commit = next $ next $ do
|
||||
showStart "commit" ""
|
||||
Annex.Branch.commit "update"
|
||||
ifM isDirect
|
||||
( do
|
||||
void stageDirect
|
||||
void preCommitDirect
|
||||
commitStaged Git.Branch.ManualCommit commitmessage
|
||||
, do
|
||||
showStart "commit" ""
|
||||
Annex.Branch.commit "update"
|
||||
inRepo $ Git.Branch.commitQuiet Git.Branch.ManualCommit
|
||||
[ Param "-a"
|
||||
, Param "-m"
|
||||
|
|
|
@ -114,7 +114,7 @@ test st r k =
|
|||
, check "storeKey when already present" store
|
||||
, present True
|
||||
, check "retrieveKeyFile" $ do
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
get
|
||||
, check "fsck downloaded object" fsck
|
||||
, check "retrieveKeyFile resume from 33%" $ do
|
||||
|
@ -124,20 +124,20 @@ test st r k =
|
|||
sz <- hFileSize h
|
||||
L.hGet h $ fromInteger $ sz `div` 3
|
||||
liftIO $ L.writeFile tmp partial
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
get
|
||||
, check "fsck downloaded object" fsck
|
||||
, check "retrieveKeyFile resume from 0" $ do
|
||||
tmp <- prepTmp k
|
||||
liftIO $ writeFile tmp ""
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
get
|
||||
, check "fsck downloaded object" fsck
|
||||
, check "retrieveKeyFile resume from end" $ do
|
||||
loc <- Annex.calcRepo (gitAnnexLocation k)
|
||||
tmp <- prepTmp k
|
||||
void $ liftIO $ copyFileExternal loc tmp
|
||||
removeAnnex k
|
||||
void $ liftIO $ copyFileExternal CopyAllMetaData loc tmp
|
||||
lockContent k removeAnnex
|
||||
get
|
||||
, check "fsck downloaded object" fsck
|
||||
, check "removeKey when present" remove
|
||||
|
@ -183,7 +183,7 @@ testUnavailable st r k =
|
|||
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
||||
cleanup rs ks ok = do
|
||||
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
||||
forM_ ks removeAnnex
|
||||
forM_ ks $ \k -> lockContent k removeAnnex
|
||||
return ok
|
||||
|
||||
chunkSizes :: Int -> Bool -> [Int]
|
||||
|
|
|
@ -89,7 +89,7 @@ cleanupIndirect file key = do
|
|||
)
|
||||
where
|
||||
copyfrom src =
|
||||
thawContent file `after` liftIO (copyFileExternal src file)
|
||||
thawContent file `after` liftIO (copyFileExternal CopyAllMetaData src file)
|
||||
hardlinkfrom src =
|
||||
#ifndef mingw32_HOST_OS
|
||||
-- creating a hard link could fall; fall back to copying
|
||||
|
|
|
@ -103,7 +103,7 @@ removeUnannexed = go []
|
|||
go c [] = return c
|
||||
go c (k:ks) = ifM (inAnnexCheck k $ liftIO . enoughlinks)
|
||||
( do
|
||||
removeAnnex k
|
||||
lockContent k removeAnnex
|
||||
go c ks
|
||||
, go (k:c) ks
|
||||
)
|
||||
|
|
|
@ -46,7 +46,7 @@ perform dest key = do
|
|||
tmpdest <- fromRepo $ gitAnnexTmpObjectLocation key
|
||||
liftIO $ createDirectoryIfMissing True (parentDir tmpdest)
|
||||
showAction "copying"
|
||||
ifM (liftIO $ copyFileExternal src tmpdest)
|
||||
ifM (liftIO $ copyFileExternal CopyAllMetaData src tmpdest)
|
||||
( do
|
||||
liftIO $ do
|
||||
removeFile dest
|
||||
|
|
|
@ -189,7 +189,12 @@ bloomBitsHashes :: Annex (Int, Int)
|
|||
bloomBitsHashes = do
|
||||
capacity <- bloomCapacity
|
||||
accuracy <- bloomAccuracy
|
||||
return $ suggestSizing capacity (1/ fromIntegral accuracy)
|
||||
case safeSuggestSizing capacity (1 / fromIntegral accuracy) of
|
||||
Left e -> do
|
||||
warning $ "bloomfilter " ++ e ++ "; falling back to sane value"
|
||||
-- precaulculated value for 500000 (1/1000)
|
||||
return (8388608,10)
|
||||
Right v -> return v
|
||||
|
||||
{- Creates a bloom filter, and runs an action, such as withKeysReferenced,
|
||||
- to populate it.
|
||||
|
|
|
@ -41,9 +41,9 @@ fuzzymatches input showchoice choices = fst $ unzip $
|
|||
|
||||
{- Takes action based on git's autocorrect configuration, in preparation for
|
||||
- an autocorrected command being run. -}
|
||||
prepare :: String -> (c -> String) -> [c] -> Repo -> IO ()
|
||||
prepare :: String -> (c -> String) -> [c] -> Maybe Repo -> IO ()
|
||||
prepare input showmatch matches r =
|
||||
case readish $ Git.Config.get "help.autocorrect" "0" r of
|
||||
case readish . Git.Config.get "help.autocorrect" "0" =<< r of
|
||||
Just n
|
||||
| n == 0 -> list
|
||||
| n < 0 -> warn
|
||||
|
|
|
@ -33,3 +33,17 @@ looseObjectFile :: Repo -> Sha -> FilePath
|
|||
looseObjectFile r sha = objectsDir r </> prefix </> rest
|
||||
where
|
||||
(prefix, rest) = splitAt 2 (fromRef sha)
|
||||
|
||||
listAlternates :: Repo -> IO [FilePath]
|
||||
listAlternates r = catchDefaultIO [] (lines <$> readFile alternatesfile)
|
||||
where
|
||||
alternatesfile = objectsDir r </> "info" </> "alternates"
|
||||
|
||||
{- A repository recently cloned with --shared will have one or more
|
||||
- alternates listed, and contain no loose objects or packs. -}
|
||||
isSharedClone :: Repo -> IO Bool
|
||||
isSharedClone r = allM id
|
||||
[ not . null <$> listAlternates r
|
||||
, null <$> listLooseObjectShas r
|
||||
, null <$> listPackFiles r
|
||||
]
|
||||
|
|
|
@ -102,7 +102,13 @@ parseRemoteLocation s repo = ret $ calcloc s
|
|||
&& not ("::" `isInfixOf` v)
|
||||
scptourl v = "ssh://" ++ host ++ slash dir
|
||||
where
|
||||
(host, dir) = separate (== ':') v
|
||||
(host, dir)
|
||||
-- handle ipv6 address inside []
|
||||
| "[" `isPrefixOf` v = case break (== ']') v of
|
||||
(h, ']':':':d) -> (h ++ "]", d)
|
||||
(h, ']':d) -> (h ++ "]", d)
|
||||
(h, d) -> (h, d)
|
||||
| otherwise = separate (== ':') v
|
||||
slash d | d == "" = "/~/" ++ d
|
||||
| "/" `isPrefixOf` d = d
|
||||
| "~" `isPrefixOf` d = '/':d
|
||||
|
|
|
@ -17,9 +17,7 @@ import Utility.Metered
|
|||
import Utility.Percentage
|
||||
import Utility.QuickCheck
|
||||
import Utility.PID
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Utility.WinLock
|
||||
#endif
|
||||
import Utility.LockFile
|
||||
|
||||
import Data.Time.Clock
|
||||
import Data.Time.Clock.POSIX
|
||||
|
@ -131,19 +129,12 @@ checkTransfer :: Transfer -> Annex (Maybe TransferInfo)
|
|||
checkTransfer t = do
|
||||
tfile <- fromRepo $ transferFile t
|
||||
#ifndef mingw32_HOST_OS
|
||||
mode <- annexFileMode
|
||||
mfd <- liftIO $ catchMaybeIO $
|
||||
openFd (transferLockFile tfile) ReadOnly (Just mode) defaultFileFlags
|
||||
case mfd of
|
||||
Nothing -> return Nothing -- failed to open file; not running
|
||||
Just fd -> do
|
||||
locked <- liftIO $
|
||||
getLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||
liftIO $ closeFd fd
|
||||
case locked of
|
||||
Nothing -> return Nothing
|
||||
Just (pid, _) -> liftIO $ catchDefaultIO Nothing $
|
||||
liftIO $ do
|
||||
v <- getLockStatus (transferLockFile tfile)
|
||||
case v of
|
||||
Just (pid, _) -> catchDefaultIO Nothing $
|
||||
readTransferInfoFile (Just pid) tfile
|
||||
Nothing -> return Nothing
|
||||
#else
|
||||
v <- liftIO $ lockShared $ transferLockFile tfile
|
||||
liftIO $ case v of
|
||||
|
|
|
@ -11,7 +11,6 @@ module Logs.Trust (
|
|||
TrustLevel(..),
|
||||
trustGet,
|
||||
trustMap,
|
||||
trustSet,
|
||||
trustPartition,
|
||||
trustExclude,
|
||||
lookupTrust,
|
||||
|
@ -20,17 +19,15 @@ module Logs.Trust (
|
|||
) where
|
||||
|
||||
import qualified Data.Map as M
|
||||
import Data.Time.Clock.POSIX
|
||||
|
||||
import Common.Annex
|
||||
import Types.TrustLevel
|
||||
import qualified Annex.Branch
|
||||
import qualified Annex
|
||||
import Logs
|
||||
import Logs.UUIDBased
|
||||
import Remote.List
|
||||
import qualified Types.Remote
|
||||
import Logs.Trust.Pure as X
|
||||
import Logs.Trust.Basic as X
|
||||
|
||||
{- Returns a list of UUIDs that the trustLog indicates have the
|
||||
- specified trust level.
|
||||
|
@ -39,17 +36,6 @@ import Logs.Trust.Pure as X
|
|||
trustGet :: TrustLevel -> Annex [UUID]
|
||||
trustGet level = M.keys . M.filter (== level) <$> trustMap
|
||||
|
||||
{- Changes the trust level for a uuid in the trustLog. -}
|
||||
trustSet :: UUID -> TrustLevel -> Annex ()
|
||||
trustSet uuid@(UUID _) level = do
|
||||
ts <- liftIO getPOSIXTime
|
||||
Annex.Branch.change trustLog $
|
||||
showLog showTrustLog .
|
||||
changeLog ts uuid level .
|
||||
parseLog (Just . parseTrustLog)
|
||||
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
|
||||
trustSet NoUUID _ = error "unknown UUID; cannot modify"
|
||||
|
||||
{- Returns the TrustLevel of a given repo UUID. -}
|
||||
lookupTrust :: UUID -> Annex TrustLevel
|
||||
lookupTrust u = (fromMaybe SemiTrusted . M.lookup u) <$> trustMap
|
||||
|
|
32
Logs/Trust/Basic.hs
Normal file
32
Logs/Trust/Basic.hs
Normal file
|
@ -0,0 +1,32 @@
|
|||
{- git-annex trust log, basics
|
||||
-
|
||||
- Copyright 2010-2012 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Logs.Trust.Basic (
|
||||
module X,
|
||||
trustSet,
|
||||
) where
|
||||
|
||||
import Data.Time.Clock.POSIX
|
||||
|
||||
import Common.Annex
|
||||
import Types.TrustLevel
|
||||
import qualified Annex.Branch
|
||||
import qualified Annex
|
||||
import Logs
|
||||
import Logs.UUIDBased
|
||||
import Logs.Trust.Pure as X
|
||||
|
||||
{- Changes the trust level for a uuid in the trustLog. -}
|
||||
trustSet :: UUID -> TrustLevel -> Annex ()
|
||||
trustSet uuid@(UUID _) level = do
|
||||
ts <- liftIO getPOSIXTime
|
||||
Annex.Branch.change trustLog $
|
||||
showLog showTrustLog .
|
||||
changeLog ts uuid level .
|
||||
parseLog (Just . parseTrustLog)
|
||||
Annex.changeState $ \s -> s { Annex.trustmap = Nothing }
|
||||
trustSet NoUUID _ = error "unknown UUID; cannot modify"
|
2
Makefile
2
Makefile
|
@ -218,7 +218,7 @@ android: Build/EvilSplicer
|
|||
sed -i 's/^ Build-Depends: / Build-Depends: yesod-routes, yesod-core, shakespeare-css, shakespeare-js, shakespeare, blaze-markup, file-embed, wai-app-static, /' tmp/androidtree/git-annex.cabal
|
||||
# Avoid warnings due to sometimes unused imports added for the splices.
|
||||
sed -i 's/GHC-Options: \(.*\)-Wall/GHC-Options: \1-Wall -fno-warn-unused-imports /i' tmp/androidtree/git-annex.cabal
|
||||
sed -i 's/Extensions: /Extensions: MagicHash /i' tmp/no-th-tree/git-annex.cabal
|
||||
sed -i 's/Extensions: /Extensions: MagicHash /i' tmp/androidtree/git-annex.cabal
|
||||
# Cabal cannot cross compile with custom build type, so workaround.
|
||||
sed -i 's/Build-type: Custom/Build-type: Simple/' tmp/androidtree/git-annex.cabal
|
||||
# Build just once, but link twice, for 2 different versions of Android.
|
||||
|
|
14
Messages.hs
14
Messages.hs
|
@ -25,7 +25,6 @@ module Messages (
|
|||
showErr,
|
||||
warning,
|
||||
warningIO,
|
||||
fileNotFound,
|
||||
indent,
|
||||
maybeShowJSON,
|
||||
showFullJSON,
|
||||
|
@ -45,7 +44,6 @@ import System.Log.Logger
|
|||
import System.Log.Formatter
|
||||
import System.Log.Handler (setFormatter, LogHandler)
|
||||
import System.Log.Handler.Simple
|
||||
import qualified Data.Set as S
|
||||
|
||||
import Common hiding (handle)
|
||||
import Types
|
||||
|
@ -172,18 +170,6 @@ warningIO w = do
|
|||
hFlush stdout
|
||||
hPutStrLn stderr w
|
||||
|
||||
{- Displays a warning one time about a file the user specified not existing. -}
|
||||
fileNotFound :: FilePath -> Annex ()
|
||||
fileNotFound file = do
|
||||
st <- Annex.getState Annex.output
|
||||
let shown = fileNotFoundShown st
|
||||
when (S.notMember file shown) $ do
|
||||
let shown' = S.insert file shown
|
||||
let st' = st { fileNotFoundShown = shown' }
|
||||
Annex.changeState $ \s -> s { Annex.output = st' }
|
||||
liftIO $ hPutStrLn stderr $ unwords
|
||||
[ "git-annex:", file, "not found" ]
|
||||
|
||||
indent :: String -> String
|
||||
indent = intercalate "\n" . map (\l -> " " ++ l) . lines
|
||||
|
||||
|
|
|
@ -51,6 +51,7 @@ import qualified Remote.Helper.Ssh as Ssh
|
|||
import qualified Remote.GCrypt
|
||||
import Config.Files
|
||||
import Creds
|
||||
import Annex.CatFile
|
||||
|
||||
import Control.Concurrent
|
||||
import Control.Concurrent.MSampleVar
|
||||
|
@ -338,8 +339,8 @@ dropKey r key
|
|||
commitOnCleanup r $ onLocal r $ do
|
||||
ensureInitialized
|
||||
whenM (Annex.Content.inAnnex key) $ do
|
||||
Annex.Content.lockContent key $
|
||||
Annex.Content.removeAnnex key
|
||||
Annex.Content.lockContent key
|
||||
Annex.Content.removeAnnex
|
||||
logStatus key InfoMissing
|
||||
Annex.Content.saveState True
|
||||
return True
|
||||
|
@ -354,15 +355,27 @@ copyFromRemote' r key file dest
|
|||
| not $ Git.repoIsUrl (repo r) = guardUsable (repo r) (return False) $ do
|
||||
params <- Ssh.rsyncParams r Download
|
||||
u <- getUUID
|
||||
hardlink <- annexHardLink <$> Annex.getGitConfig
|
||||
-- run copy from perspective of remote
|
||||
onLocal r $ do
|
||||
ensureInitialized
|
||||
v <- Annex.Content.prepSendAnnex key
|
||||
case v of
|
||||
Nothing -> return False
|
||||
Just (object, checksuccess) ->
|
||||
runTransfer (Transfer Download u key) file noRetry
|
||||
(rsyncOrCopyFile params object dest)
|
||||
Just (object, checksuccess) -> do
|
||||
let copier = rsyncOrCopyFile params object dest
|
||||
#ifndef mingw32_HOST_OS
|
||||
let linker = createLink object dest >> return True
|
||||
go <- ifM (pure hardlink <&&> not <$> isDirect)
|
||||
( return $ \m -> liftIO (catchBoolIO linker)
|
||||
<||> copier m
|
||||
, return copier
|
||||
)
|
||||
#else
|
||||
let go = copier
|
||||
#endif
|
||||
runTransfer (Transfer Download u key)
|
||||
file noRetry go
|
||||
<&&> checksuccess
|
||||
| Git.repoIsSsh (repo r) = feedprogressback $ \feeder -> do
|
||||
direct <- isDirect
|
||||
|
@ -500,6 +513,8 @@ repairRemote r a = return $ do
|
|||
{- Runs an action from the perspective of a local remote.
|
||||
-
|
||||
- The AnnexState is cached for speed and to avoid resource leaks.
|
||||
- However, catFileStop is called to avoid git-cat-file processes hanging
|
||||
- around on removable media.
|
||||
-
|
||||
- The repository's git-annex branch is not updated, as an optimisation.
|
||||
- No caller of onLocal can query data from the branch and be ensured
|
||||
|
@ -520,7 +535,8 @@ onLocal r a = do
|
|||
cache st = Annex.changeState $ \s -> s
|
||||
{ Annex.remoteannexstate = M.insert (uuid r) st (Annex.remoteannexstate s) }
|
||||
go st a' = do
|
||||
(ret, st') <- liftIO $ Annex.run st a'
|
||||
(ret, st') <- liftIO $ Annex.run st $
|
||||
catFileStop `after` a'
|
||||
cache st'
|
||||
return ret
|
||||
|
||||
|
@ -539,7 +555,7 @@ rsyncOrCopyFile rsyncparams src dest p =
|
|||
docopy = liftIO $ bracket
|
||||
(forkIO $ watchfilesize zeroBytesProcessed)
|
||||
(void . tryIO . killThread)
|
||||
(const $ copyFileExternal src dest)
|
||||
(const $ copyFileExternal CopyTimeStamps src dest)
|
||||
watchfilesize oldsz = do
|
||||
threadDelay 500000 -- 0.5 seconds
|
||||
v <- catchMaybeIO $
|
||||
|
|
|
@ -16,10 +16,9 @@ import Types.Remote
|
|||
import Types.CleanupActions
|
||||
import qualified Annex
|
||||
import Annex.LockFile
|
||||
import Utility.LockFile
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Annex.Perms
|
||||
#else
|
||||
import Utility.WinLock
|
||||
#endif
|
||||
|
||||
{- Modifies a remote's access functions to first run the
|
||||
|
@ -84,19 +83,12 @@ runHooks r starthook stophook a = do
|
|||
unlockFile lck
|
||||
#ifndef mingw32_HOST_OS
|
||||
mode <- annexFileMode
|
||||
fd <- liftIO $ noUmask mode $
|
||||
openFd lck ReadWrite (Just mode) defaultFileFlags
|
||||
v <- liftIO $ tryIO $
|
||||
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
|
||||
case v of
|
||||
Left _ -> noop
|
||||
Right _ -> run stophook
|
||||
liftIO $ closeFd fd
|
||||
v <- liftIO $ noUmask mode $ tryLockExclusive (Just mode) lck
|
||||
#else
|
||||
v <- liftIO $ lockExclusive lck
|
||||
#endif
|
||||
case v of
|
||||
Nothing -> noop
|
||||
Just lockhandle -> do
|
||||
run stophook
|
||||
liftIO $ dropLock lockhandle
|
||||
#endif
|
||||
|
|
|
@ -92,7 +92,7 @@ gen r u c gc = do
|
|||
genRsyncOpts :: RemoteConfig -> RemoteGitConfig -> [CommandParam] -> RsyncUrl -> RsyncOpts
|
||||
genRsyncOpts c gc transport url = RsyncOpts
|
||||
{ rsyncUrl = url
|
||||
, rsyncOptions = opts []
|
||||
, rsyncOptions = transport ++ opts []
|
||||
, rsyncUploadOptions = transport ++ opts (remoteAnnexRsyncUploadOptions gc)
|
||||
, rsyncDownloadOptions = transport ++ opts (remoteAnnexRsyncDownloadOptions gc)
|
||||
, rsyncShellEscape = M.lookup "shellescape" c /= Just "no"
|
||||
|
|
|
@ -183,7 +183,7 @@ testDav url (Just (u, p)) = do
|
|||
test $ liftIO $ evalDAVT url $ do
|
||||
prepDAV user pass
|
||||
makeParentDirs
|
||||
inLocation tmpDir $ void mkCol
|
||||
void $ mkColRecursive tmpDir
|
||||
inLocation (tmpLocation "git-annex-test") $ do
|
||||
putContentM (Nothing, L.empty)
|
||||
delContentM
|
||||
|
|
19
Test.hs
19
Test.hs
|
@ -17,9 +17,6 @@ import Test.Tasty.Ingredients.Rerun
|
|||
import Data.Monoid
|
||||
|
||||
import Options.Applicative hiding (command)
|
||||
#if MIN_VERSION_optparse_applicative(0,8,0)
|
||||
import qualified Options.Applicative.Types as Opt
|
||||
#endif
|
||||
import qualified Data.Map as M
|
||||
import qualified Text.JSON
|
||||
|
||||
|
@ -115,17 +112,17 @@ main ps = do
|
|||
exitFailure
|
||||
)
|
||||
where
|
||||
progdesc = "git-annex test"
|
||||
parseOpts pprefs pinfo args =
|
||||
#if MIN_VERSION_optparse_applicative(0,8,0)
|
||||
pure $ case execParserPure pprefs pinfo args of
|
||||
Opt.Success v -> v
|
||||
Opt.Failure f -> error $ fst $ Opt.execFailure f progdesc
|
||||
Opt.CompletionInvoked _ -> error "completion not supported"
|
||||
#if MIN_VERSION_optparse_applicative(0,10,0)
|
||||
case execParserPure pprefs pinfo args of
|
||||
(Options.Applicative.Failure failure) -> do
|
||||
let (msg, _exit) = renderFailure failure progdesc
|
||||
error msg
|
||||
v -> handleParseResult v
|
||||
#else
|
||||
either (error <=< flip errMessage progdesc) return $
|
||||
execParserPure pprefs pinfo args
|
||||
handleParseResult $ execParserPure pprefs pinfo args
|
||||
#endif
|
||||
progdesc = "git-annex test"
|
||||
|
||||
ingredients :: [Ingredient]
|
||||
ingredients =
|
||||
|
|
|
@ -52,6 +52,7 @@ data GitConfig = GitConfig
|
|||
, annexGenMetaData :: Bool
|
||||
, annexListen :: Maybe String
|
||||
, annexStartupScan :: Bool
|
||||
, annexHardLink :: Bool
|
||||
, coreSymlinks :: Bool
|
||||
, gcryptId :: Maybe String
|
||||
}
|
||||
|
@ -87,6 +88,7 @@ extractGitConfig r = GitConfig
|
|||
, annexGenMetaData = getbool (annex "genmetadata") False
|
||||
, annexListen = getmaybe (annex "listen")
|
||||
, annexStartupScan = getbool (annex "startupscan") True
|
||||
, annexHardLink = getbool (annex "hardlink") False
|
||||
, coreSymlinks = getbool "core.symlinks" True
|
||||
, gcryptId = getmaybe "core.gcrypt-id"
|
||||
}
|
||||
|
|
|
@ -5,20 +5,12 @@
|
|||
- 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
|
||||
import Utility.LockFile
|
||||
|
||||
type LockPool = M.Map FilePath LockHandle
|
||||
|
|
|
@ -7,8 +7,6 @@
|
|||
|
||||
module Types.Messages where
|
||||
|
||||
import qualified Data.Set as S
|
||||
|
||||
data OutputType = NormalOutput | QuietOutput | JSONOutput
|
||||
|
||||
data SideActionBlock = NoBlock | StartBlock | InBlock
|
||||
|
@ -17,8 +15,7 @@ data SideActionBlock = NoBlock | StartBlock | InBlock
|
|||
data MessageState = MessageState
|
||||
{ outputType :: OutputType
|
||||
, sideActionBlock :: SideActionBlock
|
||||
, fileNotFoundShown :: S.Set FilePath
|
||||
}
|
||||
|
||||
defaultMessageState :: MessageState
|
||||
defaultMessageState = MessageState NormalOutput NoBlock S.empty
|
||||
defaultMessageState = MessageState NormalOutput NoBlock
|
||||
|
|
|
@ -9,7 +9,7 @@
|
|||
|
||||
module Utility.Bloom (
|
||||
Bloom,
|
||||
suggestSizing,
|
||||
safeSuggestSizing,
|
||||
Hashable,
|
||||
cheapHashes,
|
||||
notElemB,
|
||||
|
@ -25,7 +25,7 @@ import qualified Data.BloomFilter as Bloom
|
|||
#else
|
||||
import qualified Data.BloomFilter as Bloom
|
||||
#endif
|
||||
import Data.BloomFilter.Easy (suggestSizing, Bloom)
|
||||
import Data.BloomFilter.Easy (safeSuggestSizing, Bloom)
|
||||
import Data.BloomFilter.Hash (Hashable, cheapHashes)
|
||||
import Control.Monad.ST.Safe (ST)
|
||||
|
||||
|
|
|
@ -1,6 +1,6 @@
|
|||
{- file copying
|
||||
-
|
||||
- Copyright 2010-2013 Joey Hess <joey@kitenet.net>
|
||||
- Copyright 2010-2014 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
@ -9,16 +9,20 @@
|
|||
|
||||
module Utility.CopyFile (
|
||||
copyFileExternal,
|
||||
createLinkOrCopy
|
||||
createLinkOrCopy,
|
||||
CopyMetaData(..)
|
||||
) where
|
||||
|
||||
import Common
|
||||
import qualified Build.SysConfig as SysConfig
|
||||
|
||||
data CopyMetaData = CopyTimeStamps | CopyAllMetaData
|
||||
deriving (Eq)
|
||||
|
||||
{- The cp command is used, because I hate reinventing the wheel,
|
||||
- and because this allows easy access to features like cp --reflink. -}
|
||||
copyFileExternal :: FilePath -> FilePath -> IO Bool
|
||||
copyFileExternal src dest = do
|
||||
copyFileExternal :: CopyMetaData -> FilePath -> FilePath -> IO Bool
|
||||
copyFileExternal meta src dest = do
|
||||
whenM (doesFileExist dest) $
|
||||
removeFile dest
|
||||
boolSystem "cp" $ params ++ [File src, File dest]
|
||||
|
@ -26,12 +30,16 @@ copyFileExternal src dest = do
|
|||
#ifndef __ANDROID__
|
||||
params = map snd $ filter fst
|
||||
[ (SysConfig.cp_reflink_auto, Param "--reflink=auto")
|
||||
, (SysConfig.cp_a, Param "-a")
|
||||
, (SysConfig.cp_p && not SysConfig.cp_a, Param "-p")
|
||||
, (allmeta && SysConfig.cp_a, Param "-a")
|
||||
, (allmeta && SysConfig.cp_p && not SysConfig.cp_a
|
||||
, Param "-p")
|
||||
, (not allmeta && SysConfig.cp_preserve_timestamps
|
||||
, Param "--preserve=timestamps")
|
||||
]
|
||||
#else
|
||||
params = []
|
||||
#endif
|
||||
allmeta = meta == CopyAllMetaData
|
||||
|
||||
{- Create a hard link if the filesystem allows it, and fall back to copying
|
||||
- the file. -}
|
||||
|
@ -42,7 +50,7 @@ createLinkOrCopy src dest = go `catchIO` const fallback
|
|||
go = do
|
||||
createLink src dest
|
||||
return True
|
||||
fallback = copyFileExternal src dest
|
||||
fallback = copyFileExternal CopyAllMetaData src dest
|
||||
#else
|
||||
createLinkOrCopy = copyFileExternal
|
||||
createLinkOrCopy = copyFileExternal CopyAllMetaData
|
||||
#endif
|
||||
|
|
|
@ -15,7 +15,7 @@ import Utility.PID
|
|||
import Utility.LogFile
|
||||
#else
|
||||
import Utility.WinProcess
|
||||
import Utility.WinLock
|
||||
import Utility.LockFile
|
||||
#endif
|
||||
|
||||
#ifndef mingw32_HOST_OS
|
||||
|
|
|
@ -163,8 +163,9 @@ type UserId = String
|
|||
{- All of the user's secret keys, with their UserIds.
|
||||
- Note that the UserId may be empty. -}
|
||||
secretKeys :: IO (M.Map KeyId UserId)
|
||||
secretKeys = M.fromList . parse . lines <$> readStrict params
|
||||
secretKeys = catchDefaultIO M.empty makemap
|
||||
where
|
||||
makemap = M.fromList . parse . lines <$> readStrict params
|
||||
params = [Params "--with-colons --list-secret-keys --fixed-list-mode"]
|
||||
parse = extract [] Nothing . map (split ":")
|
||||
extract c (Just keyid) (("uid":_:_:_:_:_:_:_:_:userid:_):rest) =
|
||||
|
|
20
Utility/LockFile.hs
Normal file
20
Utility/LockFile.hs
Normal file
|
@ -0,0 +1,20 @@
|
|||
{- Lock files
|
||||
-
|
||||
- Posix and Windows lock files are extremely different.
|
||||
- This module does *not* attempt to be a portability shim, it just exposes
|
||||
- the native locking of the OS.
|
||||
-
|
||||
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Utility.LockFile (module X) where
|
||||
|
||||
#ifndef mingw32_HOST_OS
|
||||
import Utility.LockFile.Posix as X
|
||||
#else
|
||||
import Utility.LockFile.Windows as X
|
||||
#endif
|
99
Utility/LockFile/Posix.hs
Normal file
99
Utility/LockFile/Posix.hs
Normal file
|
@ -0,0 +1,99 @@
|
|||
{- Posix lock files
|
||||
-
|
||||
- Copyright 2014 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
module Utility.LockFile.Posix (
|
||||
LockHandle,
|
||||
lockShared,
|
||||
lockExclusive,
|
||||
tryLockExclusive,
|
||||
createLockFile,
|
||||
openExistingLockFile,
|
||||
isLocked,
|
||||
checkLocked,
|
||||
getLockStatus,
|
||||
dropLock,
|
||||
) where
|
||||
|
||||
import Utility.Exception
|
||||
import Utility.Applicative
|
||||
|
||||
import System.IO
|
||||
import System.Posix
|
||||
import Data.Maybe
|
||||
|
||||
type LockFile = FilePath
|
||||
|
||||
newtype LockHandle = LockHandle Fd
|
||||
|
||||
-- Takes a shared lock, blocking until the lock is available.
|
||||
lockShared :: Maybe FileMode -> LockFile -> IO LockHandle
|
||||
lockShared = lock ReadLock
|
||||
|
||||
-- Takes an exclusive lock, blocking until the lock is available.
|
||||
lockExclusive :: Maybe FileMode -> LockFile -> IO LockHandle
|
||||
lockExclusive = lock WriteLock
|
||||
|
||||
-- Tries to take an exclusive lock, but does not block.
|
||||
tryLockExclusive :: Maybe FileMode -> LockFile -> IO (Maybe LockHandle)
|
||||
tryLockExclusive mode lockfile = do
|
||||
l <- openLockFile mode lockfile
|
||||
v <- tryIO $ setLock l (WriteLock, AbsoluteSeek, 0, 0)
|
||||
case v of
|
||||
Left _ -> do
|
||||
closeFd l
|
||||
return Nothing
|
||||
Right _ -> return $ Just $ LockHandle l
|
||||
|
||||
-- Setting the FileMode allows creation of a new lock file.
|
||||
-- If it's Nothing then this only succeeds when the lock file already exists.
|
||||
lock :: LockRequest -> Maybe FileMode -> LockFile -> IO LockHandle
|
||||
lock lockreq mode lockfile = do
|
||||
l <- openLockFile mode lockfile
|
||||
waitToSetLock l (lockreq, AbsoluteSeek, 0, 0)
|
||||
return (LockHandle l)
|
||||
|
||||
-- Create and opens lock file; does not lock it.
|
||||
createLockFile :: FileMode -> LockFile -> IO Fd
|
||||
createLockFile filemode = openLockFile (Just filemode)
|
||||
|
||||
-- Opens an existing lock file; does not lock it, and if it does not exist,
|
||||
-- returns Nothing.
|
||||
openExistingLockFile :: LockFile -> IO (Maybe Fd)
|
||||
openExistingLockFile = catchMaybeIO . openLockFile Nothing
|
||||
|
||||
-- Close on exec flag is set so child processes do not inherit the lock.
|
||||
openLockFile :: Maybe FileMode -> LockFile -> IO Fd
|
||||
openLockFile filemode lockfile = do
|
||||
l <- openFd lockfile ReadWrite filemode defaultFileFlags
|
||||
setFdOption l CloseOnExec True
|
||||
return l
|
||||
|
||||
-- Check if a file is locked, either exclusively, or with shared lock.
|
||||
-- When the file doesn't exist, it's considered not locked.
|
||||
isLocked :: LockFile -> IO Bool
|
||||
isLocked = fromMaybe False <$$> checkLocked
|
||||
|
||||
-- Returns Nothing when the file doesn't exist, for cases where
|
||||
-- that is different from it not being locked.
|
||||
checkLocked :: LockFile -> IO (Maybe Bool)
|
||||
checkLocked = maybe Nothing (Just . isJust) <$$> getLockStatus'
|
||||
|
||||
getLockStatus :: LockFile -> IO (Maybe (ProcessID, FileLock))
|
||||
getLockStatus = fromMaybe Nothing <$$> getLockStatus'
|
||||
|
||||
getLockStatus' :: LockFile -> IO (Maybe (Maybe (ProcessID, FileLock)))
|
||||
getLockStatus' lockfile = go =<< catchMaybeIO open
|
||||
where
|
||||
open = openFd lockfile ReadOnly Nothing defaultFileFlags
|
||||
go Nothing = return Nothing
|
||||
go (Just h) = do
|
||||
ret <- getLock h (ReadLock, AbsoluteSeek, 0, 0)
|
||||
closeFd h
|
||||
return (Just ret)
|
||||
|
||||
dropLock :: LockHandle -> IO ()
|
||||
dropLock (LockHandle fd) = closeFd fd
|
|
@ -5,7 +5,7 @@
|
|||
- License: BSD-2-clause
|
||||
-}
|
||||
|
||||
module Utility.WinLock (
|
||||
module Utility.LockFile.Windows (
|
||||
lockShared,
|
||||
lockExclusive,
|
||||
dropLock,
|
||||
|
@ -17,9 +17,6 @@ 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
|
||||
|
@ -30,7 +27,11 @@ 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. -}
|
||||
- a shared or exclusive lock.
|
||||
-
|
||||
- Note that exclusive locking also prevents the file from being opened for
|
||||
- read or write by any other progess. So for advisory locking of a file's
|
||||
- content, a different LockFile should be used. -}
|
||||
lockExclusive :: LockFile -> IO (Maybe LockHandle)
|
||||
lockExclusive = openLock fILE_SHARE_NONE
|
||||
|
||||
|
@ -44,15 +45,20 @@ lockExclusive = openLock fILE_SHARE_NONE
|
|||
- 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.
|
||||
-
|
||||
- Also, passing Nothing for SECURITY_ATTRIBUTES ensures that the lock file
|
||||
- is not inheerited by any child process.
|
||||
-}
|
||||
openLock :: ShareMode -> LockFile -> IO (Maybe LockHandle)
|
||||
openLock sharemode f = do
|
||||
h <- withTString f $ \c_f ->
|
||||
c_CreateFile c_f gENERIC_READ sharemode (maybePtr Nothing)
|
||||
c_CreateFile c_f gENERIC_READ sharemode security_attributes
|
||||
oPEN_ALWAYS fILE_ATTRIBUTE_NORMAL (maybePtr Nothing)
|
||||
return $ if h == iNVALID_HANDLE_VALUE
|
||||
then Nothing
|
||||
else Just h
|
||||
where
|
||||
security_attributes = maybePtr Nothing
|
||||
|
||||
dropLock :: LockHandle -> IO ()
|
||||
dropLock = closeHandle
|
|
@ -6,11 +6,14 @@
|
|||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RankNTypes #-}
|
||||
|
||||
module Utility.Url (
|
||||
URLString,
|
||||
UserAgent,
|
||||
UrlOptions(..),
|
||||
UrlOptions,
|
||||
mkUrlOptions,
|
||||
check,
|
||||
checkBoth,
|
||||
exists,
|
||||
|
@ -25,6 +28,7 @@ import Network.HTTP.Conduit
|
|||
import Network.HTTP.Types
|
||||
import Data.Default
|
||||
import qualified Data.CaseInsensitive as CI
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.UTF8 as B8
|
||||
|
||||
import qualified Build.SysConfig
|
||||
|
@ -39,11 +43,39 @@ data UrlOptions = UrlOptions
|
|||
{ userAgent :: Maybe UserAgent
|
||||
, reqHeaders :: Headers
|
||||
, reqParams :: [CommandParam]
|
||||
#if MIN_VERSION_http_conduit(2,0,0)
|
||||
, applyRequest :: Request -> Request
|
||||
#else
|
||||
, applyRequest :: forall m. Request m -> Request m
|
||||
#endif
|
||||
}
|
||||
|
||||
instance Default UrlOptions
|
||||
where
|
||||
def = UrlOptions Nothing [] []
|
||||
def = UrlOptions Nothing [] [] id
|
||||
|
||||
mkUrlOptions :: Maybe UserAgent -> Headers -> [CommandParam] -> UrlOptions
|
||||
mkUrlOptions useragent reqheaders reqparams =
|
||||
UrlOptions useragent reqheaders reqparams applyrequest
|
||||
where
|
||||
applyrequest = \r -> r { requestHeaders = requestHeaders r ++ addedheaders }
|
||||
addedheaders = uaheader ++ otherheaders
|
||||
uaheader = case useragent of
|
||||
Nothing -> []
|
||||
Just ua -> [(hUserAgent, B8.fromString ua)]
|
||||
otherheaders = map toheader reqheaders
|
||||
toheader s =
|
||||
let (h, v) = separate (== ':') s
|
||||
h' = CI.mk (B8.fromString h)
|
||||
in case v of
|
||||
(' ':v') -> (h', B8.fromString v')
|
||||
_ -> (h', B8.fromString v)
|
||||
|
||||
addUserAgent :: UrlOptions -> [CommandParam] -> [CommandParam]
|
||||
addUserAgent uo ps = case userAgent uo of
|
||||
Nothing -> ps
|
||||
-- --user-agent works for both wget and curl commands
|
||||
Just ua -> ps ++ [Param "--user-agent", Param ua]
|
||||
|
||||
{- Checks that an url exists and could be successfully downloaded,
|
||||
- also checking that its size, if available, matches a specified size. -}
|
||||
|
@ -105,7 +137,7 @@ exists url uo = case parseURIRelaxed url of
|
|||
(responseHeaders resp)
|
||||
|
||||
existsconduit req = withManager $ \mgr -> do
|
||||
let req' = (addUrlOptions uo req) { method = methodHead }
|
||||
let req' = headRequest (applyRequest uo req)
|
||||
resp <- http req' mgr
|
||||
-- forces processing the response before the
|
||||
-- manager is closed
|
||||
|
@ -115,11 +147,19 @@ exists url uo = case parseURIRelaxed url of
|
|||
liftIO $ closeManager mgr
|
||||
return ret
|
||||
|
||||
-- works for both wget and curl commands
|
||||
addUserAgent :: UrlOptions -> [CommandParam] -> [CommandParam]
|
||||
addUserAgent uo ps = case userAgent uo of
|
||||
Nothing -> ps
|
||||
Just ua -> ps ++ [Param "--user-agent", Param ua]
|
||||
#if MIN_VERSION_http_conduit(2,0,0)
|
||||
headRequest :: Request -> Request
|
||||
#else
|
||||
headRequest :: Request m -> Request m
|
||||
#endif
|
||||
headRequest r = r
|
||||
{ method = methodHead
|
||||
-- remove defaut Accept-Encoding header, to get actual,
|
||||
-- not gzip compressed size.
|
||||
, requestHeaders = (hAcceptEncoding, B.empty) :
|
||||
filter (\(h, _) -> h /= hAcceptEncoding)
|
||||
(requestHeaders r)
|
||||
}
|
||||
|
||||
addUrlOptions :: UrlOptions -> Request -> Request
|
||||
addUrlOptions uo r = r { requestHeaders = requestHeaders r ++ uaheader ++ otherheaders}
|
||||
|
@ -187,3 +227,14 @@ download' quiet url file uo =
|
|||
{- Allows for spaces and other stuff in urls, properly escaping them. -}
|
||||
parseURIRelaxed :: URLString -> Maybe URI
|
||||
parseURIRelaxed = parseURI . escapeURIString isAllowedInURI
|
||||
|
||||
hAcceptEncoding :: CI.CI B.ByteString
|
||||
hAcceptEncoding = "Accept-Encoding"
|
||||
|
||||
#if ! MIN_VERSION_http_types(0,7,0)
|
||||
hContentLength :: CI.CI B.ByteString
|
||||
hContentLength = "Content-Length"
|
||||
|
||||
hUserAgent :: CI.CI B.ByteString
|
||||
hUserAgent = "User-Agent"
|
||||
#endif
|
||||
|
|
71
debian/changelog
vendored
71
debian/changelog
vendored
|
@ -1,4 +1,63 @@
|
|||
git-annex (5.20140718) UNRELEASED; urgency=medium
|
||||
git-annex (5.20140916) UNRELEASED; urgency=medium
|
||||
|
||||
* assistant: Detect when repository has been deleted or moved, and
|
||||
automatically shut down the assistant. Closes: #761261
|
||||
* Windows: Avoid crashing trying to list gpg secret keys, for gcrypt
|
||||
which is not yet supported on Windows.
|
||||
* WebDav: Fix enableremote crash when the remote already exists.
|
||||
(Bug introduced in version 5.20140817.)
|
||||
* add: In direct mode, adding an annex symlink will check it into git,
|
||||
as was already done in indirect mode.
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Mon, 15 Sep 2014 14:39:17 -0400
|
||||
|
||||
git-annex (5.20140915) unstable; urgency=medium
|
||||
|
||||
* New annex.hardlink setting. Closes: #758593
|
||||
* init: Automatically detect when a repository was cloned with --shared,
|
||||
and set annex.hardlink=true, as well as marking the repository as
|
||||
untrusted.
|
||||
* Fix parsing of ipv6 address in git remote address when it was not
|
||||
formatted as an url.
|
||||
* The annex-rsync-transport configuration is now also used when checking
|
||||
if a key is present on a rsync remote, and when dropping a key from
|
||||
the remote.
|
||||
* Promote file not found warning message to an error.
|
||||
* Fix transfer lock file FD leak that could occur when two separate
|
||||
git-annex processes were both working to perform the same set of
|
||||
transfers.
|
||||
* sync: Ensure that pending changes to git-annex branch are committed
|
||||
before push when in direct mode. (Fixing a very minor reversion.)
|
||||
* WORM backend: Switched to include the relative path to the file inside
|
||||
the repository, rather than just the file's base name. Note that if you're
|
||||
relying on such things to keep files separate with WORM, you should really
|
||||
be using a better backend.
|
||||
* Rather than crashing when there's a problem with the requested bloomfilter
|
||||
capacity/accuracy, fall back to a reasonable default bloom filter size.
|
||||
* Fix build with optparse-applicative 0.10. Closes: #761484
|
||||
* webapp: Fixed visual glitch in xmpp pairing that was reported live by a
|
||||
user who tracked me down in front of a coffee cart in Portland.
|
||||
(New bug reporting method of choice?)
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Mon, 15 Sep 2014 10:45:00 -0400
|
||||
|
||||
git-annex (5.20140831) unstable; urgency=medium
|
||||
|
||||
* Make --help work when not in a git repository. Closes: #758592
|
||||
* Ensure that all lock fds are close-on-exec, fixing various problems with
|
||||
them being inherited by child processes such as git commands.
|
||||
* When accessing a local remote, shut down git-cat-file processes
|
||||
afterwards, to ensure that remotes on removable media can be unmounted.
|
||||
Closes: #758630
|
||||
* Fix handing of autocorrection when running outside a git repository.
|
||||
* Fix stub git-annex test support when built without tasty.
|
||||
* Do not preserve permissions and acls when copying files from
|
||||
one local git repository to another. Timestamps are still preserved
|
||||
as long as cp --preserve=timestamps is supported. Closes: #729757
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Sun, 31 Aug 2014 12:30:08 -0700
|
||||
|
||||
git-annex (5.20140817) unstable; urgency=medium
|
||||
|
||||
* New chunk= option to chunk files stored in special remotes.
|
||||
Supported by: directory, S3, webdav, gcrypt, rsync, and all external
|
||||
|
@ -16,15 +75,11 @@ git-annex (5.20140718) UNRELEASED; urgency=medium
|
|||
were incompletely repaired before.
|
||||
* Fix cost calculation for non-encrypted remotes.
|
||||
* Display exception message when a transfer fails due to an exception.
|
||||
* WebDAV, S3: Sped up by avoiding making multiple http connections
|
||||
* WebDAV: Sped up by avoiding making multiple http connections
|
||||
when storing a file.
|
||||
* WebDAV, S3: Avoid buffering whole file in memory when uploading and
|
||||
* WebDAV: Avoid buffering whole file in memory when uploading and
|
||||
downloading.
|
||||
* WebDAV: Dropped support for DAV before 1.0.
|
||||
* S3: Switched to using the haskell aws library.
|
||||
* S3: Now supports https. To enable this, configure a S3 special remote to
|
||||
use port=443. However, with encrypted special remotes, this does not
|
||||
add any security.
|
||||
* testremote: New command to test uploads/downloads to a remote.
|
||||
* Dropping an object from a bup special remote now deletes the git branch
|
||||
for the object, although of course the object's content cannot be deleted
|
||||
|
@ -45,7 +100,7 @@ git-annex (5.20140718) UNRELEASED; urgency=medium
|
|||
remote. The remote may have moved between networks, or reconnected.
|
||||
* Switched from the old haskell HTTP library to http-conduit.
|
||||
|
||||
-- Joey Hess <joeyh@debian.org> Mon, 21 Jul 2014 14:41:26 -0400
|
||||
-- Joey Hess <joeyh@debian.org> Sun, 17 Aug 2014 10:30:58 -0400
|
||||
|
||||
git-annex (5.20140717) unstable; urgency=high
|
||||
|
||||
|
|
32
debian/control
vendored
32
debian/control
vendored
|
@ -19,7 +19,7 @@ Build-Depends:
|
|||
libghc-dav-dev (>= 1.0) [amd64 i386 kfreebsd-amd64 kfreebsd-i386 powerpc],
|
||||
libghc-quickcheck2-dev,
|
||||
libghc-monad-control-dev (>= 0.3),
|
||||
libghc-exceptions-dev,
|
||||
libghc-exceptions-dev (>= 0.6),
|
||||
libghc-transformers-dev,
|
||||
libghc-unix-compat-dev,
|
||||
libghc-dlist-dev,
|
||||
|
@ -33,16 +33,16 @@ Build-Depends:
|
|||
libghc-stm-dev (>= 2.3),
|
||||
libghc-dbus-dev (>= 0.10.3) [linux-any],
|
||||
libghc-fdo-notify-dev (>= 0.3) [linux-any],
|
||||
libghc-yesod-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-yesod-static-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-yesod-default-dev [i386 amd64 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-hamlet-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-shakespeare-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-clientsession-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-warp-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-warp-tls-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-wai-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-wai-extra-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc sparc],
|
||||
libghc-yesod-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-yesod-static-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-yesod-default-dev [i386 amd64 kfreebsd-amd64 powerpc],
|
||||
libghc-hamlet-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-shakespeare-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-clientsession-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-warp-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-warp-tls-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-wai-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-wai-extra-dev [i386 amd64 kfreebsd-i386 kfreebsd-amd64 powerpc],
|
||||
libghc-securemem-dev,
|
||||
libghc-byteable-dev,
|
||||
libghc-dns-dev,
|
||||
|
@ -61,12 +61,12 @@ Build-Depends:
|
|||
libghc-feed-dev (>= 0.3.9.2),
|
||||
libghc-regex-tdfa-dev [!mipsel !s390],
|
||||
libghc-regex-compat-dev [mipsel s390],
|
||||
libghc-tasty-dev (>= 0.7) [!mipsel !sparc],
|
||||
libghc-tasty-hunit-dev [!mipsel !sparc],
|
||||
libghc-tasty-quickcheck-dev [!mipsel !sparc],
|
||||
libghc-tasty-rerun-dev [!mipsel !sparc],
|
||||
libghc-tasty-dev (>= 0.7) [!sparc],
|
||||
libghc-tasty-hunit-dev [!sparc],
|
||||
libghc-tasty-quickcheck-dev [!sparc],
|
||||
libghc-tasty-rerun-dev [!sparc],
|
||||
libghc-optparse-applicative-dev [!sparc],
|
||||
lsof [!kfreebsd-i386 !kfreebsd-amd64],
|
||||
lsof [!kfreebsd-i386 !kfreebsd-amd64 !hurd-any],
|
||||
ikiwiki,
|
||||
perlmagick,
|
||||
git (>= 1:1.8.4),
|
||||
|
|
|
@ -13,7 +13,7 @@ can use different ones for different files.
|
|||
* `SHA256` -- Does not include the file extension in the key, which can
|
||||
lead to better deduplication but can confuse some programs.
|
||||
* `WORM` ("Write Once, Read Many") This assumes that any file with
|
||||
the same basename, size, and modification time has the same content.
|
||||
the same filename, size, and modification time has the same content.
|
||||
This is the least expensive backend, recommended for really large
|
||||
files or slow systems.
|
||||
* `SHA512`, `SHA512E` -- Best SHA-2 hash, for the very paranoid.
|
||||
|
|
|
@ -0,0 +1,295 @@
|
|||
### Please describe the problem.
|
||||
|
||||
Installing git-annex on a new Nexus 5 with Android 4.4.4 using [Android 4.4 and 4.3 git-annex.apk](http://downloads.kitenet.net/git-annex/android/current/4.3/git-annex.apk) does not give me a working git-annex environment. It seems permission is denied to install many of the app files.
|
||||
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
|
||||
1. Install git-annex
|
||||
2. From within `adb shell`, run: `/data/data/ga.androidterm/runshell`
|
||||
3. Try one of the included programs, e.g., `git`
|
||||
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
|
||||
The current (as of 2014-08-30) git-annex for Android 4.3 and up on Android 4.4.4.
|
||||
|
||||
|
||||
### Please provide any additional information below.
|
||||
|
||||
Running `/data/data/ga.androidterm/runshell` from `adb shell` gives me:
|
||||
|
||||
[[!format txt """
|
||||
shell@hammerhead:/ $ /data/data/ga.androidterm/runshell
|
||||
Falling back to hardcoded app location; cannot find expected files in /data/app-lib
|
||||
shell@hammerhead:/sdcard/git-annex.home $ ls
|
||||
git-annex-install.log
|
||||
shell@hammerhead:/sdcard/git-annex.home $ cat git-annex-install.log
|
||||
Installation starting to /data/data/ga.androidterm
|
||||
71c22504d777380dd59d2128b97715fde9ef6bec
|
||||
mv: can't rename '/data/data/ga.androidterm/bin': Permission denied
|
||||
installing busybox
|
||||
ln: /data/data/ga.androidterm/bin/busybox: Permission denied
|
||||
installing git-annex
|
||||
ln: /data/data/ga.androidterm/bin/git-annex: Permission denied
|
||||
installing git-shell
|
||||
ln: /data/data/ga.androidterm/bin/git-shell: Permission denied
|
||||
installing git-upload-pack
|
||||
ln: /data/data/ga.androidterm/bin/git-upload-pack: Permission denied
|
||||
installing git
|
||||
ln: /data/data/ga.androidterm/bin/git: Permission denied
|
||||
installing gpg
|
||||
ln: /data/data/ga.androidterm/bin/gpg: Permission denied
|
||||
installing rsync
|
||||
ln: /data/data/ga.androidterm/bin/rsync: Permission denied
|
||||
installing ssh
|
||||
ln: /data/data/ga.androidterm/bin/ssh: Permission denied
|
||||
installing ssh-keygen
|
||||
ln: /data/data/ga.androidterm/bin/ssh-keygen: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/[: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/[[: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ar: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/arp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ash: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/base64: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/basename: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/beep: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/blkid: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/blockdev: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/bunzip2: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/bzcat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/bzip2: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cal: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/catv: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chattr: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chgrp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chmod: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chown: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chpst: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chroot: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chrt: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/chvt: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cksum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/clear: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cmp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/comm: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cpio: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cttyhack: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/cut: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dc: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/deallocvt: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/devmem: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/diff: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dirname: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dmesg: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dnsd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dos2unix: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dpkg: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dpkg-deb: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/du: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/dumpkmap: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/echo: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/envdir: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/envuidgid: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/expand: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fakeidentd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/false: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fbset: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fbsplash: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fdflush: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fdformat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fdisk: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fgconsole: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/find: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/findfs: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/flash_lock: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/flash_unlock: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/flashcp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/flock: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fold: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/freeramdisk: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ftpd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ftpget: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ftpput: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/fuser: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/getopt: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/grep: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/gunzip: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/gzip: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/hd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/hdparm: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/head: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/hexdump: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/httpd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ifconfig: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ifdown: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ifup: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/inotifyd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/install: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/iostat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ip: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ipaddr: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ipcalc: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/iplink: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/iproute: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/iprule: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/iptunnel: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/klogd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ln: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/loadkmap: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/losetup: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lpd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lpq: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lpr: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ls: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lsattr: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lsof: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lspci: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lsusb: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lzcat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lzma: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lzop: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/lzopcat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/makedevs: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/makemime: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/man: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/md5sum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mkdir: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mkfifo: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mknod: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mkswap: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mktemp: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/more: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mpstat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/mv: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/nbd-client: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/nc: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/netstat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/nice: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/nmeter: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/nohup: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/od: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/openvt: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/patch: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pidof: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pipe_progress: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pmap: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/popmaildir: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/printenv: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/printf: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pscan: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pstree: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pwd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/pwdx: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/raidautorun: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rdev: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/readlink: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/readprofile: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/realpath: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/reformime: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/renice: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/reset: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/resize: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rev: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rm: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rmdir: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/route: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rpm: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rpm2cpio: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rtcwake: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/run-parts: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/runsv: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/runsvdir: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/rx: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/script: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/scriptreplay: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sed: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sendmail: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/seq: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setconsole: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setkeycodes: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setlogcons: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setserial: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setsid: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/setuidgid: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sh: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sha1sum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sha256sum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sha512sum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/showkey: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sleep: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/smemcap: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/softlimit: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sort: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/split: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/start-stop-daemon: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/strings: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/stty: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sum: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sv: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/svlogd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sync: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/sysctl: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tac: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tail: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tar: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tcpsvd: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tee: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/test: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/time: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/timeout: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/top: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/touch: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tr: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/true: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/ttysize: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tunctl: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/tune2fs: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/udhcpc: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/uname: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/uncompress: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unexpand: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/uniq: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unix2dos: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unlzma: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unlzop: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unxz: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/unzip: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/uudecode: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/uuencode: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/vi: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/volname: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/watch: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/wc: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/wget: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/which: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/whoami: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/whois: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/xargs: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/xz: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/xzcat: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/yes: Permission denied
|
||||
busybox: /data/data/ga.androidterm/bin/zcat: Permission denied
|
||||
tar: can't remove old file ./links/git-shell: Permission denied
|
||||
cat: can't open '/data/data/ga.androidterm/links/git': Permission denied
|
||||
rm: can't stat '/data/data/ga.androidterm/links/git': Permission denied
|
||||
cat: can't open '/data/data/ga.androidterm/links/git-shell': Permission denied
|
||||
rm: can't stat '/data/data/ga.androidterm/links/git-shell': Permission denied
|
||||
cat: can't open '/data/data/ga.androidterm/links/git-upload-pack': Permission denied
|
||||
rm: can't stat '/data/data/ga.androidterm/links/git-upload-pack': Permission denied
|
||||
lib/lib.runshell.so: line 133: can't create /data/data/ga.androidterm/runshell: Permission denied
|
||||
lib/lib.runshell.so: line 133: can't create /data/data/ga.androidterm/runshell: Permission denied
|
||||
chmod: runshell: Operation not permitted
|
||||
lib/lib.runshell.so: line 133: can't create /data/data/ga.androidterm/bin/trustedkeys.gpg: Permission denied
|
||||
lib/lib.runshell.so: line 133: can't create /data/data/ga.androidterm/installed-version: Permission denied
|
||||
Installation complete
|
||||
tar: write: Broken pipe
|
||||
shell@hammerhead:/sdcard/git-annex.home $ ^D
|
||||
shell@hammerhead:/ $
|
||||
"""]]
|
||||
|
||||
Android is new to me, so it's possible I'm doing something utterly wrong.
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawk9nck8WX8-ADF3Fdh5vFo4Qrw1I_bJcR8"
|
||||
nickname="Jon Ander"
|
||||
subject="comment 14"
|
||||
date="2014-09-08T07:27:46Z"
|
||||
content="""
|
||||
Still experiencing this bug in Debian testing (5.20140717) and Debian sid (5.20140831)
|
||||
"""]]
|
1305
doc/bugs/Assistant_removed_all_references_to_files.mdwn
Normal file
1305
doc/bugs/Assistant_removed_all_references_to_files.mdwn
Normal file
File diff suppressed because it is too large
Load diff
|
@ -0,0 +1,14 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="comment 1"
|
||||
date="2014-09-11T17:45:31Z"
|
||||
content="""
|
||||
Unfortunately, the old version of git-annex you have been using is exactly the wrong version, so you ran into this horrible bug, which is fixed in newer versions.
|
||||
|
||||
<http://git-annex.branchable.com/bugs/bad_merge_commit_deleting_all_files/>
|
||||
|
||||
That page has details, including instructions on how to recover your data.
|
||||
|
||||
I hope that you were not using that old version because it's included in some distribution somewhere still?
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://andrew.aylett.co.uk/"
|
||||
nickname="andrew"
|
||||
subject="comment 2"
|
||||
date="2014-09-11T19:03:07Z"
|
||||
content="""
|
||||
Unfortunately, that bug involves merges while I'm seeing regular commits so I don't think it's identical.
|
||||
|
||||
As to why I'm on that version, it appears that the updater and something in my environment conspired against me, leaving an old version in my path. I'll fix that now and let you know if I see the issue again.
|
||||
"""]]
|
44
doc/bugs/Bloom_filter_capacity_too_large_to_represent.mdwn
Normal file
44
doc/bugs/Bloom_filter_capacity_too_large_to_represent.mdwn
Normal file
|
@ -0,0 +1,44 @@
|
|||
### Please describe the problem.
|
||||
When running git-annex info I get an error when it tries to show the bloom filter size
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
git-annex info in my Photos repo
|
||||
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
[[!format sh """
|
||||
$ git-annex version
|
||||
git-annex version: 5.20140814-g9b89b5c
|
||||
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV Inotify DBus DesktopNotify 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 ddar hook external
|
||||
local repository version: 5
|
||||
supported repository version: 5
|
||||
upgrade supported from repository versions: 0 1 2 4
|
||||
"""]]
|
||||
|
||||
### Please provide any additional information below.
|
||||
|
||||
[[!format sh """
|
||||
$ git-annex info
|
||||
repository mode: direct
|
||||
trusted repositories: 2
|
||||
c0e4106e-2631-11e2-9749-1bfa37a61069 -- [rose]
|
||||
ca735977-973c-44bc-9257-915b2c875e39 -- synology [here]
|
||||
semitrusted repositories: 3
|
||||
00000000-0000-0000-0000-000000000001 -- web
|
||||
7e5c0010-2634-4a5e-bc7b-6fea84b8b947 -- [glacier]
|
||||
d7e01abc-d74b-40e2-8607-3d41ce8bc4bd -- seagate3
|
||||
untrusted repositories: 1
|
||||
c1fe5922-43f1-11e2-b146-33530f7fa6cc -- x200s
|
||||
transfers in progress: none
|
||||
available local disk space: 928.4 gigabytes (+1 megabyte reserved)
|
||||
local annex keys: 34758
|
||||
local annex size: 186.78 gigabytes
|
||||
annexed files in working tree: 35300
|
||||
size of annexed files in working tree: 193.76 gigabytes
|
||||
bloom filter size: git-annex: Data.BloomFilter.Util.suggestSizing: capacity too large to represent
|
||||
"""]]
|
||||
|
||||
> I've worked around this problem in the arm autobuilder (only build
|
||||
> affected), so [[done]] --[[Joey]]
|
|
@ -0,0 +1,14 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="comment 1"
|
||||
date="2014-09-12T16:03:09Z"
|
||||
content="""
|
||||
It seems you must have tweaked the annex.bloomcapacity and/or annex.bloomaccuracy settings, probably to some quite large values.
|
||||
|
||||
For example capacity of 50000000 and accuracy of 10000000000 will fail this way.
|
||||
|
||||
This happens when it runs out of Double floating point precision to calculate the requested bloom filter size. I think that a bloom filter can be built that has this capacity/accuracy, it's just that Data.BloomFilter.Easy.safeSuggestSizing falls over trying to find the bloom filter size. Also, such a bloom filter may use rather a lot of memory..
|
||||
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="comment 2"
|
||||
date="2014-09-12T16:34:56Z"
|
||||
content="""
|
||||
However, in Greg's case he had no such configuration. Instead, I think something is broken with the use of floating point or bit math that bloomfilter uses, on the NAS where he's using git-annex.
|
||||
|
||||
I have made git-annex not crash when this happens, just show a warning and fall back to a reasonable default bloom filter size. If the problem is with the bit math, then the bloom filter may not work either, which would probably show up as false negatives, so `git annex unused` not finding things that are unused.
|
||||
|
||||
I need to update the armel build with this so Greg can test it..
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="comment 3"
|
||||
date="2014-09-12T16:38:47Z"
|
||||
content="""
|
||||
I have reproduced the bug, using the standalone build on an arm box (turtle).
|
||||
|
||||
On the same box, the debian git-annex build works ok.
|
||||
|
||||
Suggests to me the problem is related to the cross-compiling method used for the standalone arm build.
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="turns out to be an upstream bug already filed"
|
||||
date="2014-09-12T17:46:23Z"
|
||||
content="""
|
||||
It seems that this is a bug on bloomfilter 2.0.0.0 on armel generally. It's also preventing this newer version from building on armel currently:
|
||||
|
||||
<http://bugs.debian.org/756801>
|
||||
|
||||
The git-annex standalone arm autobuilder installed it with cabal, so ended up with the newer, broken version.
|
||||
"""]]
|
|
@ -21,3 +21,4 @@ Instead of just using the basename, WORM keys could be kept stable by
|
|||
using the relative path and anchoring it to the root of the
|
||||
repository.
|
||||
|
||||
> [[fixed|done]] --[[Joey]]
|
||||
|
|
|
@ -0,0 +1,21 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 2"
|
||||
date="2014-08-16T11:42:22Z"
|
||||
content="""
|
||||
Hm, I don’t quite follow the remark on having everything in a single
|
||||
directory. Rather than saying that the relative path adds additional
|
||||
entropy, what I was aiming at is the file-system cannot have two
|
||||
alternate versions of one file name at the same path with the same
|
||||
mtime, and that’s why it occurred to me that encoding both path and
|
||||
mtime within the key doesn’t just increase the odds, but effectively
|
||||
_guarantees_ that there won’t be any collisions. Does this seem to
|
||||
hold up, or am I missing something? (Of course one can fudge the
|
||||
mtimes, but that’s something under the user’s control.)
|
||||
|
||||
While a large repo with many files very likely has lots of distinct
|
||||
files with identical basename, mtime (in s.) and size, all these files
|
||||
with the same mtime must necessarily be located at different paths.
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,15 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 3"
|
||||
date="2014-08-16T13:58:28Z"
|
||||
content="""
|
||||
One scenario where the above guarantee would be violated is when one
|
||||
moves a new file of identical size, basename, and mtime, into a path
|
||||
where a key-colliding file has been kept before. Still, I’d consider
|
||||
this a scenario one could reasonably control for (especially in the
|
||||
archive usecase); plus, even without manual control such a
|
||||
move-induced collision would be much more unlikely than a collision of
|
||||
basenames only.
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 4"
|
||||
date="2014-08-18T18:39:33Z"
|
||||
content="""
|
||||
> Rather than saying that the relative path adds additional entropy, what I was aiming at is the file-system cannot have two alternate versions of one file name at the same path with the same mtime
|
||||
|
||||
True of a single filesystem, but not of a set of connected git repositories. :)
|
||||
|
||||
So there are multiple scenarios when encoding the file path in the key doesn't help. The probabilities of these seem low, but perhaps not as low as the probability that there will be two differing files with the same name+size+mtime in the first place. It's not clear to me that it adds more than a false sense of security to change from basename to git filename.
|
||||
"""]]
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 5"
|
||||
date="2014-08-18T20:54:10Z"
|
||||
content="""
|
||||
> True of a single filesystem, but not of a set of connected git repositories.
|
||||
|
||||
That’s a good point. Might depend on the use case, though.
|
||||
|
||||
> The probabilities of these seem low, but perhaps not as low as the probability that there will be two differing files with the same name+size+mtime in the first place.
|
||||
|
||||
This one I’m not completely sure about. E.g., I have an annex with web pages mirrored from the web. Due to the crawler implementation, there are lots of «index.html» or «favicon.ico» with the same mtime (in particular when mtime is read with a 1 sec. precision). Files like favicon are often bitmaps of the same resolution and often have the same size due to this. Because there are file-formats where both size and basename are semantically pre-determined, there is zero entropy from these sources alone (also cf. «readme.txt»). The entropy of mtime alone is not really large, I suppose, and in some use-cases will also approach zero (think «initializing a repo by cp -r on a fast disk without preserving mtime). The relative path could make a huge difference there. I believe this argument is actually what worried me the most. Does it seem valid?
|
||||
|
||||
Apart from entropy, there’s the non-probabilistic advantage we discussed (granted, with some limiting constraints which one has to assure for oneself). Granted, one might argue a hash would be the better way, but this is not always practical in every setup.
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.132"
|
||||
subject="comment 6"
|
||||
date="2014-09-11T18:41:45Z"
|
||||
content="""
|
||||
Ok, those are good examples. I personally think it would be insane to use WORM in a repository in either of those cases, or really in almost any case where you do not have a strong degree of confidence that unique file contents have unique file names. If people are going to abuse WORM like that, it might be best to simply remove it. (Except I have quite a lot of WORMy disks.)
|
||||
|
||||
I suppose I'll add the extra data, although I remain unconvinced that it is going to help anyone who should actually be using WORM.
|
||||
"""]]
|
|
@ -0,0 +1,387 @@
|
|||
### Please describe the problem.
|
||||
Using the assistant on two computers to setup a shared encrypted repository (while sharing the same pgp key) on a third computer leads to files not propagating between one and two.
|
||||
|
||||
The first and second computer does not get changes done on the other. If new files are added on the first computer it appears as if everything works (no error messages) but the files never reach the second computer (and vice versa).
|
||||
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
|
||||
Three computers needed.
|
||||
|
||||
* Computer A: Use the assistant to create a repository
|
||||
* Computer A: Use the assitant to setup a remote repository on Computer C (Add another repository - Remote server - Encrypt with GnuPG key/Encript repository with a new encryption key - Save changes)
|
||||
|
||||
[At this point files propagate from A to C]
|
||||
|
||||
* Computer A: Export the private and public gpg keys to files
|
||||
* Computer B: Import these private and public gpg files, fix trust to ultimate
|
||||
* Computer B: Use the assistant to create a repository
|
||||
* Computer B: Use the assitant to connect with the remote repository on Computer C (Add another repository - Remote server - Combine the repositories)
|
||||
|
||||
[Files created on A before adding B now appear on B]
|
||||
|
||||
[New files created on A do not appear on B, new files created on B do not appear on A. Files from A and B seem to propagate to C (the number of files/directories in the object sub directory on C goes up after adding files on A or B)]
|
||||
|
||||
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
Computer A:
|
||||
[[!format sh """
|
||||
dirk@A:~$ lsb_release -a
|
||||
No LSB modules are available.
|
||||
Distributor ID: Ubuntu
|
||||
Description: Ubuntu 14.04.1 LTS
|
||||
Release: 14.04
|
||||
Codename: trusty
|
||||
dirk@A:~$ git-annex version
|
||||
git-annex version: 5.20140818-g10bf03a
|
||||
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV Inotify DBus DesktopNotify 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 ddar hook external
|
||||
local repository version: 5
|
||||
supported repository version: 5
|
||||
upgrade supported from repository versions: 0 1 2 4
|
||||
dirk@A:~$
|
||||
|
||||
dirk@A:~$ gpg --list-keys --list-options show-uid-validity
|
||||
/home/dirk/.gnupg/pubring.gpg
|
||||
-----------------------------
|
||||
pub 4096R/0A7AA2A4 2014-08-23
|
||||
uid [ultimate] dirk's git-annex encryption key
|
||||
|
||||
dirk@A:~$ gpg --list-secret-keys --list-options show-uid-validity
|
||||
/home/dirk/.gnupg/secring.gpg
|
||||
-----------------------------
|
||||
sec 4096R/0A7AA2A4 2014-08-23
|
||||
uid dirk's git-annex encryption key
|
||||
|
||||
dirk@A:~$
|
||||
"""]]
|
||||
|
||||
Computer B:
|
||||
[[!format sh """
|
||||
dirk@B:~$ lsb_release -a
|
||||
No LSB modules are available.
|
||||
Distributor ID: Ubuntu
|
||||
Description: Ubuntu 14.04.1 LTS
|
||||
Release: 14.04
|
||||
Codename: trusty
|
||||
dirk@B:~$ git-annex version
|
||||
git-annex version: 5.20140818-g10bf03a
|
||||
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV Inotify DBus DesktopNotify 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 ddar hook external
|
||||
dirk@B:~$
|
||||
|
||||
dirk@B:~$ gpg --list-keys --list-options show-uid-validity
|
||||
/home/dirk/.gnupg/pubring.gpg
|
||||
-----------------------------
|
||||
pub 4096R/0A7AA2A4 2014-08-23
|
||||
uid [ultimate] dirk's git-annex encryption key
|
||||
|
||||
dirk@B:~$ gpg --list-secret-keys --list-options show-uid-validity
|
||||
/home/dirk/.gnupg/secring.gpg
|
||||
-----------------------------
|
||||
sec 4096R/0A7AA2A4 2014-08-23
|
||||
uid dirk's git-annex encryption key
|
||||
|
||||
dirk@B:~$
|
||||
"""]]
|
||||
|
||||
Computer C:
|
||||
[[!format sh """
|
||||
dirk@C:~$ lsb_release -a
|
||||
No LSB modules are available.
|
||||
Distributor ID: Debian
|
||||
Description: Debian GNU/Linux 7.6 (wheezy)
|
||||
Release: 7.6
|
||||
Codename: wheezy
|
||||
dirk@C:~$ git-annex version
|
||||
git-annex version: 5.20140717~bpo70+1
|
||||
build flags: Assistant Webapp Pairing S3 Inotify DBus XMPP 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 tahoe glacier ddar hook external
|
||||
dirk@C:~$
|
||||
"""]]
|
||||
|
||||
### Please provide any additional information below.
|
||||
|
||||
.git/annex/daemon.log - Computer A
|
||||
[[!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-08-23 15:15:01 CEST] main: starting assistant version 5.20140818-g10bf03a
|
||||
[2014-08-23 15:15:01 CEST] Cronner: You should enable consistency checking to protect your data.
|
||||
(scanning...) [2014-08-23 15:15:01 CEST] Watcher: Performing startup scan
|
||||
(started...)
|
||||
gpg: new configuration file `/home/dirk/.gnupg/gpg.conf' created
|
||||
gpg: WARNING: options in `/home/dirk/.gnupg/gpg.conf' are not yet active during this run
|
||||
|
||||
Not enough random bytes available. Please do some other work to give
|
||||
the OS a chance to collect more entropy! (Need 235 more bytes)
|
||||
....+++++
|
||||
|
||||
Not enough random bytes available. Please do some other work to give
|
||||
the OS a chance to collect more entropy! (Need 196 more bytes)
|
||||
.......+++++
|
||||
gpg: /home/dirk/.gnupg/trustdb.gpg: trustdb created
|
||||
gpg: key 0A7AA2A4 marked as ultimately trusted
|
||||
Generating public/private rsa key pair.
|
||||
Your identification has been saved in /tmp/git-annex-keygen.0/key.
|
||||
Your public key has been saved in /tmp/git-annex-keygen.0/key.pub.
|
||||
The key fingerprint is:
|
||||
7d:02:34:56:d4:86:b6:e5:82:b0:d9:4f:3b:51:b3:c7 dirk@A
|
||||
The key's randomart image is:
|
||||
+--[ RSA 2048]----+
|
||||
| +ooo |
|
||||
| .o .o * |
|
||||
| =.o * + |
|
||||
| o oo= o E |
|
||||
| Soo+.. |
|
||||
| +o |
|
||||
| . |
|
||||
| |
|
||||
| |
|
||||
+-----------------+
|
||||
(encryption setup) (hybrid cipher with gpg key 7815EA570A7AA2A4) gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gpg: checking the trustdb
|
||||
gpg: 3 marginal(s) needed, 1 complete(s) needed, PGP trust model
|
||||
gpg: depth: 0 valid: 1 signed: 0 trust: 0-, 0q, 0n, 0m, 0f, 1u
|
||||
gcrypt: Repository not found: ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Repository not found: ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
gcrypt: Setting up new repository
|
||||
gcrypt: Remote ID is :id:00RaA3cNQu+nZDMERYMM
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
* [new branch] git-annex -> git-annex
|
||||
ok
|
||||
[2014-08-23 15:25:46 CEST] main: Syncing with C_annex
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:45 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:45 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
* [new branch] git-annex -> synced/git-annex
|
||||
* [new branch] annex/direct/master -> synced/master
|
||||
[2014-08-23 15:26:46 CEST] Pusher: Syncing with C_annex
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
Everything up-to-date
|
||||
[2014-08-23 15:34:01 CEST] Committer: Adding hhhhn.txt
|
||||
add hhhhn.txt ok
|
||||
add hhhhn.txt ok
|
||||
[2014-08-23 15:34:01 CEST] Committer: Committing changes to git
|
||||
(Recording state in git...)
|
||||
[2014-08-23 15:34:01 CEST] Pusher: Syncing with C_annex
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
(gpg)
|
||||
GPGHMACSHA1--7a46226ea53e4043cb45e8df6a2382ac2696164e
|
||||
|
||||
74 100% 0.00kB/s 0:00:00
|
||||
74 100% 0.00kB/s 0:00:00 (xfr#1, to-chk=0/1)
|
||||
[2014-08-23 15:34:01 CEST] Transferrer: Uploaded hhhhn.txt
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:33:27 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: WARNING:
|
||||
gcrypt: WARNING: Remote ID has changed!
|
||||
gcrypt: WARNING: from :id:00RaA3cNQu+nZDMERYMM
|
||||
gcrypt: WARNING: to :id:h/BFJbR+mE8CEkASZ/tx
|
||||
gcrypt: WARNING:
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
85b70d6..e1d6871 annex/direct/master -> synced/master
|
||||
+ 99dc810...a7a89ff git-annex -> synced/git-annex (forced update)
|
||||
[2014-08-23 15:34:07 CEST] Pusher: Syncing with C_annex
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:34:04 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
a7a89ff..e68b5a9 git-annex -> synced/git-annex
|
||||
[2014-08-23 15:48:30 CEST] main: warning git-annex has been shut down
|
||||
# End of transcript or log.
|
||||
"""]]
|
||||
|
||||
.git/annex/daemon.log - Computer B
|
||||
[[!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-08-23 15:30:11 CEST] main: starting assistant version 5.20140818-g10bf03a
|
||||
[2014-08-23 15:30:11 CEST] Cronner: You should enable consistency checking to protect your data.
|
||||
|
||||
dbus failed; falling back to mtab polling (ClientError {clientErrorMessage = "runClient: unable to determine DBUS address", clientErrorFatal = True})
|
||||
|
||||
No known network monitor available through dbus; falling back to polling
|
||||
(scanning...) [2014-08-23 15:30:11 CEST] Watcher: Performing startup scan
|
||||
(started...)
|
||||
Generating public/private rsa key pair.
|
||||
Your identification has been saved in /tmp/git-annex-keygen.0/key.
|
||||
Your public key has been saved in /tmp/git-annex-keygen.0/key.pub.
|
||||
The key fingerprint is:
|
||||
b5:c3:6b:af:fc:fe:82:f2:a6:f3:42:e9:50:4b:63:9e dirk@A
|
||||
The key's randomart image is:
|
||||
+--[ RSA 2048]----+
|
||||
| |
|
||||
| |
|
||||
| . |
|
||||
| =o . |
|
||||
| =S=+ |
|
||||
| . E o |
|
||||
| + o. |
|
||||
| =oo.. |
|
||||
| .O=++o. |
|
||||
+-----------------+
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: checking the trustdb
|
||||
gpg: 3 marginal(s) needed, 1 complete(s) needed, PGP trust model
|
||||
gpg: depth: 0 valid: 1 signed: 0 trust: 0-, 0q, 0n, 0m, 0f, 1u
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Remote ID is :id:00RaA3cNQu+nZDMERYMM
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Remote ID is :id:00RaA3cNQu+nZDMERYMM
|
||||
Receiving objects: 14% (1/7)
|
||||
Receiving objects: 28% (2/7)
|
||||
Receiving objects: 42% (3/7)
|
||||
Receiving objects: 57% (4/7)
|
||||
Receiving objects: 71% (5/7)
|
||||
Receiving objects: 85% (6/7)
|
||||
Receiving objects: 100% (7/7)
|
||||
Receiving objects: 100% (7/7), done.
|
||||
Receiving objects: 12% (1/8)
|
||||
Receiving objects: 25% (2/8)
|
||||
Receiving objects: 37% (3/8)
|
||||
Receiving objects: 50% (4/8)
|
||||
Receiving objects: 62% (5/8)
|
||||
Receiving objects: 75% (6/8)
|
||||
Receiving objects: 87% (7/8)
|
||||
Receiving objects: 100% (8/8)
|
||||
Receiving objects: 100% (8/8), done.
|
||||
From gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex
|
||||
* [new branch] git-annex -> tmpgcryptremote/git-annex
|
||||
* [new branch] synced/git-annex -> tmpgcryptremote/synced/git-annex
|
||||
* [new branch] synced/master -> tmpgcryptremote/synced/master
|
||||
* [new branch] master -> tmpgcryptremote/master
|
||||
(merging tmpgcryptremote/git-annex tmpgcryptremote/synced/git-annex into git-annex...)
|
||||
(Recording state in git...)
|
||||
(encryption update) (hybrid cipher with gpg key 7815EA570A7AA2A4) gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Remote ID is :id:00RaA3cNQu+nZDMERYMM
|
||||
From gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex
|
||||
* [new branch] git-annex -> C_annex/git-annex
|
||||
* [new branch] synced/git-annex -> C_annex/synced/git-annex
|
||||
* [new branch] synced/master -> C_annex/synced/master
|
||||
* [new branch] master -> C_annex/master
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
remote: error: denying non-fast-forward refs/heads/master (you should pull first)
|
||||
To ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
! [remote rejected] refs/gcrypt/gitception+ -> master (non-fast-forward)
|
||||
error: failed to push some refs to 'ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/'
|
||||
error: failed to push some refs to 'gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/'
|
||||
ok
|
||||
[2014-08-23 15:31:36 CEST] main: Syncing with C_annex
|
||||
|
||||
Automatic merge went well; stopped before committing as requested
|
||||
Already up-to-date!
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
[2014-08-23 15:31:37 CEST] Pusher: Syncing with C_annex
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gcrypt: Repository not found: ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
gcrypt: Setting up new repository
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
fatal: ambiguous argument 'refs/heads/synced/master..refs/remotes/C_annex/synced/master': unknown revision or path not in the working tree.
|
||||
Use '--' to separate paths from revisions, like this:
|
||||
'git <command> [<revision>...] -- [<file>...]'
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Remote ID is :id:h/BFJbR+mE8CEkASZ/tx
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:25:49 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
* [new branch] git-annex -> synced/git-annex
|
||||
* [new branch] annex/direct/master -> synced/master
|
||||
fatal: Not a valid object name refs/gcrypt/gitception+
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
5d2eb63..e4763b8 git-annex -> synced/git-annex
|
||||
da18915..3068bad annex/direct/master -> synced/master
|
||||
[2014-08-23 15:32:37 CEST] Pusher: Syncing with C_annex
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:31:43 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: WARNING:
|
||||
gcrypt: WARNING: Remote ID has changed!
|
||||
gcrypt: WARNING: from :id:00RaA3cNQu+nZDMERYMM
|
||||
gcrypt: WARNING: to :id:h/BFJbR+mE8CEkASZ/tx
|
||||
gcrypt: WARNING:
|
||||
Everything up-to-date
|
||||
[2014-08-23 15:33:17 CEST] Committer: Adding fmksmxxs.txt
|
||||
add fmksmxxs.txt ok
|
||||
add fmksmxxs.txt ok
|
||||
[2014-08-23 15:33:18 CEST] Committer: Committing changes to git
|
||||
(Recording state in git...)
|
||||
[2014-08-23 15:33:18 CEST] Pusher: Syncing with C_annex
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
(gpg) gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:31:43 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
|
||||
GPGHMACSHA1--f605f108429ffba3058a2fcf0bc006a1fbe600be
|
||||
|
||||
70 100% 0.00kB/s 0:00:00
|
||||
70 100% 0.00kB/s 0:00:00 (xfr#1, to-chk=0/1)
|
||||
[2014-08-23 15:33:20 CEST] Transferrer: Uploaded fmksmxxs.txt
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
e4763b8..85dbfc5 git-annex -> synced/git-annex
|
||||
3068bad..85b70d6 annex/direct/master -> synced/master
|
||||
[2014-08-23 15:33:25 CEST] Pusher: Syncing with C_annex
|
||||
(Recording state in git...)
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:33:22 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from "dirk's git-annex encryption key"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
85dbfc5..99dc810 git-annex -> synced/git-annex
|
||||
[2014-08-23 15:48:39 CEST] main: warning git-annex has been shut down
|
||||
# End of transcript or log.
|
||||
"""]]
|
|
@ -0,0 +1,35 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawk7iPiqWr3BVPLWEDvJhSSvcOqheLEbLNo"
|
||||
nickname="Dirk"
|
||||
subject="comment 1"
|
||||
date="2014-08-23T18:13:06Z"
|
||||
content="""
|
||||
Restarting the two git-annex instances actually now leads to an error message on computer B.
|
||||
|
||||
[[!format sh \"\"\"
|
||||
[2014-08-23 20:02:00 CEST] main: starting assistant version 5.20140818-g10bf03a
|
||||
[2014-08-23 20:02:00 CEST] Cronner: You should enable consistency checking to protect your data.
|
||||
|
||||
dbus failed; falling back to mtab polling (ClientError {clientErrorMessage = \"runClient: unable to determine DBUS address\", clientErrorFatal = True})
|
||||
[2014-08-23 20:02:00 CEST] TransferScanner: Syncing with C_annex
|
||||
|
||||
No known network monitor available through dbus; falling back to polling
|
||||
(scanning...) [2014-08-23 20:02:00 CEST] Watcher: Performing startup scan
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
(started...)
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:34:08 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from \"dirk's git-annex encryption key\"
|
||||
gcrypt: Packfile 59a8d97d3d252effb044625e020f9dc8621804649186a5c33c4e47f9e961cc1a does not match digest!
|
||||
fatal: early EOF
|
||||
gcrypt: Development version -- Repository format MAY CHANGE
|
||||
gcrypt: Decrypting manifest
|
||||
gpg: Signature made Sat 23 Aug 2014 03:34:08 PM CEST using RSA key ID 0A7AA2A4
|
||||
gpg: Good signature from \"dirk's git-annex encryption key\"
|
||||
gcrypt: Encrypting to: -r 7815EA570A7AA2A4
|
||||
gcrypt: Requesting manifest signature
|
||||
To gcrypt::ssh://dirk@git-annex-C-dirk_1022_annex/~/annex/
|
||||
e1d6871..85b70d6 annex/direct/master -> synced/master
|
||||
+ e68b5a9...99dc810 git-annex -> synced/git-annex (forced update)
|
||||
\"\"\"]]
|
||||
"""]]
|
57
doc/bugs/Upload_to_S3_fails_.mdwn
Normal file
57
doc/bugs/Upload_to_S3_fails_.mdwn
Normal file
|
@ -0,0 +1,57 @@
|
|||
### Please describe the problem.
|
||||
|
||||
Uploading a 21GB file to an S3 special remote fails. It will generally fail somewhere at about 3-15%. I am using the new chunking feature, with chunks set to 25MiB.
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
|
||||
$ git annex copy my-big-file.tar.bz --to s3
|
||||
copy my-big-file.tar.bz (gpg) (checking s3...) (to s3...)
|
||||
13% 863.8KB/s 6h0m
|
||||
ErrorClosed
|
||||
failed
|
||||
git-annex: copy: 1 failed
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
|
||||
Running on Arch Linux.
|
||||
|
||||
git-annex version: 5.20140818-g10bf03a
|
||||
build flags: Assistant Webapp Webapp-secure Pairing Testsuite S3 WebDAV Inotify DBus DesktopNotify 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 ddar hook external
|
||||
local repository version: 5
|
||||
supported repository version: 5
|
||||
upgrade supported from repository versions: 0 1 2 4
|
||||
|
||||
### Please provide any additional information below.
|
||||
|
||||
If I fire up the web app and open the log, the end looks like this:
|
||||
|
||||
|
||||
[[!format sh """
|
||||
...
|
||||
|
||||
3% 857.3KB/s 6h46m
|
||||
3% 857.3KB/s 6h46m
|
||||
3% 857.3KB/s 6h46m
|
||||
3% 857.4KB/s 6h46m
|
||||
3% 857.4KB/s 6h46m
|
||||
3% 857.5KB/s 6h46m
|
||||
3% 857.5KB/s 6h46m
|
||||
3% 857.6KB/s 6h46m
|
||||
3% 857.6KB/s 6h46m
|
||||
3% 857.6KB/s 6h46m
|
||||
3% 857.7KB/s 6h46m
|
||||
3% 857.7KB/s 6h46m
|
||||
3% 857.8KB/s 6h46m
|
||||
3% 857.8KB/s 6h46m
|
||||
3% 857.8KB/s 6h46m
|
||||
3% 857.9KB/s 6h46m
|
||||
3% 857.9KB/s 6h46m
|
||||
3% 858.0KB/s 6h46m
|
||||
3% 858.0KB/s 6h46m
|
||||
3% 858.1KB/s 6h46m
|
||||
3% 858.1KB/s 6h45m
|
||||
3% 858.1KB/s 6h45mmux_client_request_session: read from master failed: Broken pipe
|
||||
|
||||
"""]]
|
14
doc/bugs/Visual_glitch_while_xmpp_pairing.mdwn
Normal file
14
doc/bugs/Visual_glitch_while_xmpp_pairing.mdwn
Normal file
|
@ -0,0 +1,14 @@
|
|||
### Please describe the problem.
|
||||
When pairing with xmpp buddies, the well does not expand to fit the whole buddy list
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
Go to the pairing menu
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
5.20140717 from the homebrew bottle
|
||||
|
||||
### Please provide any additional information below.
|
||||
|
||||
![image of bug](http://i.imgur.com/fZe1ERD.png)
|
||||
|
||||
> [[fixed|done]] --[[Joey]]
|
39
doc/bugs/Windows_build_has_hardcoded_paths.mdwn
Normal file
39
doc/bugs/Windows_build_has_hardcoded_paths.mdwn
Normal file
|
@ -0,0 +1,39 @@
|
|||
### Please describe the problem.
|
||||
|
||||
The windows build seems to be hardcoded to finding git at c:\program files\Git\
|
||||
I have git in another directory. Git-annex does not find it.
|
||||
|
||||
### What steps will reproduce the problem?
|
||||
|
||||
Install git-annex. Run the webapp.
|
||||
Get error "Internal Server Error
|
||||
You need to install git in order to use git-annex!"
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
|
||||
5.20140817-g71c2250.
|
||||
Windows XP.
|
||||
|
||||
### 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.
|
||||
"""]]
|
||||
|
||||
[[!meta title="git-annex on windows does not find msgit if user does not let msysgit add itsselt to PATH"]]
|
||||
|
||||
> I don't think it's any better for git-annex's installer to prompt for the
|
||||
> path to git, than it is for msysgit's installer to prompt for adding it
|
||||
> to the system path.
|
||||
>
|
||||
> The best fix would be to bundle msysgit into the git-annex installer
|
||||
> along with all the other stuff. But, that adds build-time complications
|
||||
> I would rather avoid.
|
||||
>
|
||||
> For now, I am going to treat this as a documentation problem;
|
||||
> I've updated the install page to be clear that msysgit needs to be
|
||||
> installed into PATH. [[done]] --[[Joey]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="24.159.78.125"
|
||||
subject="comment 1"
|
||||
date="2014-08-20T14:37:30Z"
|
||||
content="""
|
||||
git-annex does not hardcode any paths, and certianly not the path to git. Your system probably does not have the location you installed git added to the PATH. In that case, git-annex may do what windows programs do and look for git.exe in the same directory it was installed into.
|
||||
"""]]
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="Hans_Ryding"
|
||||
ip="81.229.194.7"
|
||||
subject="Quite right"
|
||||
date="2014-08-21T08:54:50Z"
|
||||
content="""
|
||||
Incorrect assumption from my part.
|
||||
I reinstalled git into the expected path (C:\program files\Git)
|
||||
and the problem is still there.
|
||||
|
||||
Running git-annex from command-line works.
|
||||
(I tried running git-annex test. It had 23 failed tests,
|
||||
most of them because of inability to access the remote: origin.
|
||||
But it ran just fine.)
|
||||
Running the web-app gives the error listed above.
|
||||
"""]]
|
|
@ -0,0 +1,9 @@
|
|||
[[!comment format=mdwn
|
||||
username="Hans_Ryding"
|
||||
ip="81.229.194.7"
|
||||
subject="Change the name of the bug"
|
||||
date="2014-08-21T09:14:16Z"
|
||||
content="""
|
||||
I can't seem to change the name of the bug to something more appropriate.
|
||||
Maybe you can?
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawmBmv0HhwTFxkpxlf8ifTlMOHnIwHCHTYs"
|
||||
nickname="y"
|
||||
subject="path on windows"
|
||||
date="2014-08-23T22:02:07Z"
|
||||
content="""
|
||||
I think I have a related problem on win7 sp1.
|
||||
|
||||
When first installing msys git, there's a screen asking for how to set the PATH variable. I chose the option not to update the windows PATH variable, which is the default. Then I installed git annex. Then launching the git-annex-autostart.vbs as well as the webapp one gets an object not found error (on line 2). launching git-annex from git bash with full path yielded an error about not finding git.
|
||||
|
||||
Then I proceeded and reinstalled git on top of itself and picked the option to only add git and bash to windows path and it worked.
|
||||
"""]]
|
|
@ -0,0 +1,22 @@
|
|||
[[!comment format=mdwn
|
||||
username="Hans_Ryding"
|
||||
ip="81.229.194.7"
|
||||
subject="Relying on path is not best practice in a Windows environment"
|
||||
date="2014-08-25T16:16:33Z"
|
||||
content="""
|
||||
Unlike under POSIX environments
|
||||
generally applications under windows don't add themselves to path,
|
||||
or to a directory already in path.
|
||||
|
||||
Generally applications announce their location using the registry.
|
||||
Under either HKEY_LOCAL_MACHINE\SOFTWARE,
|
||||
or in case of software installed for one particular user only
|
||||
under HKEY_CURRENT_USER\SOFTWARE.
|
||||
|
||||
Git however AFAIK does not.
|
||||
Most likely the best thing to do is to prompt the user when installing git-annex
|
||||
where git is, and store this variable.
|
||||
|
||||
Note that in both my installs I installed git-annex into the git directory,
|
||||
and the git-annex webapp still couldn't find it.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawmBmv0HhwTFxkpxlf8ifTlMOHnIwHCHTYs"
|
||||
nickname="y"
|
||||
subject="path on windows"
|
||||
date="2014-08-26T12:18:39Z"
|
||||
content="""
|
||||
To add to my comment I also installed git-annex in the same directory as the msys git distrib in both cases.
|
||||
"""]]
|
|
@ -0,0 +1,22 @@
|
|||
### Please describe the problem.
|
||||
After having added new content (SHA1E backend), when trying to commit, git commit fails with the following error:
|
||||
|
||||
[[!format sh """
|
||||
(Recording state in git...)
|
||||
error: invalid object 100644 5d471129a031f0f493de3736eaea6f2f4056aeee for '000/091/WORM-s1493-m1321288671--scrapbook%data%20111114173520%horiz-menu-tab-r_001.png.log'
|
||||
fatal: git-write-tree: error building trees
|
||||
git-annex: failed to read sha from git write-tree
|
||||
"""]]
|
||||
|
||||
The commit subsequently fails and the index is left as is. When I did git-annex add, I got the same error, but the additions seem to have been staged, at least.
|
||||
|
||||
What’s curious about this is that I migrated all keys to SHA1E earlier and dropped all WORM keys. git annex info also says that all my keys are SHA1E.
|
||||
|
||||
Can this be related to your changes to the WORM backend? I upgraded to git-annex 5.20140818 today. Rolling back to 5.20140716 didn’t allow me to commit, either, though.
|
||||
|
||||
Any way I could resolve this? I don’t want to git reset for now, since this will leave the added objects in the annex store.
|
||||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
git-annex 5.20140818
|
||||
|
||||
Linux 3.16.1
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="CandyAngel"
|
||||
ip="81.111.193.130"
|
||||
subject="comment 10"
|
||||
date="2014-09-08T08:08:50Z"
|
||||
content="""
|
||||
Removing .git/annex/index is safe, it is a step in getting git-annex to [forget a commit entirely](http://git-annex.branchable.com/forum/How_to_get_git-annex_to_forget_a_commit__63__).
|
||||
"""]]
|
|
@ -0,0 +1,35 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 1"
|
||||
date="2014-08-22T09:27:34Z"
|
||||
content="""
|
||||
git fsck only shows a few dangling blobs from a branch I did earlier and left behind, but otherwise reports no errors.
|
||||
|
||||
git annex fsck --fast ultimately fails with the original error message at some point:
|
||||
|
||||
[[!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
|
||||
|
||||
# nx fsck --fast|egrep -v 'ok$'
|
||||
[2014-08-22 11:14:43 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"ls-files\",\"--cached\",\"-z\",\"--\"]
|
||||
[2014-08-22 11:14:43 CEST] chat: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"check-attr\",\"-z\",\"--stdin\",\"annex.backend\",\"annex.numcopies\",\"--\"]
|
||||
[2014-08-22 11:14:43 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"git-annex\"]
|
||||
[2014-08-22 11:14:43 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
|
||||
[2014-08-22 11:14:43 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"log\",\"refs/heads/git-annex..dda9b068ac5c075e79ab63a531770ad772ae8491\",\"-n1\",\"--pretty=%H\"]
|
||||
[2014-08-22 11:14:43 CEST] chat: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"cat-file\",\"--batch\"]
|
||||
[2014-08-22 11:25:24 CEST] chat: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"hash-object\",\"-w\",\"--stdin-paths\",\"--no-filters\"]
|
||||
[2014-08-22 11:25:24 CEST] feed: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"update-index\",\"-z\",\"--index-info\"]
|
||||
[2014-08-22 11:25:24 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
|
||||
[2014-08-22 11:25:24 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"write-tree\"]
|
||||
error: invalid object 100644 5d471129a031f0f493de3736eaea6f2f4056aeee for '000/091/WORM-s1493-m1321288671--scrapbook%data%20111114173520%horiz-menu-tab-r_001.png.log'
|
||||
fatal: git-write-tree: error building trees
|
||||
git-annex: failed to read sha from git write-tree
|
||||
(Recording state in git...)
|
||||
|
||||
# End of transcript or log.
|
||||
\"\"\"]]
|
||||
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,30 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 2"
|
||||
date="2014-08-22T09:38:03Z"
|
||||
content="""
|
||||
git commit with git-annex debug output enabled:
|
||||
|
||||
|
||||
[[!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-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"diff\",\"--cached\",\"--name-only\",\"-z\",\"--diff-filter=ACMRT\",\"--\",\".\"]
|
||||
[2014-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"diff\",\"--name-only\",\"--diff-filter=T\",\"-z\",\"--cached\",\"--\",\".\"]
|
||||
[2014-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"symbolic-ref\",\"HEAD\"]
|
||||
[2014-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"refs/heads/master\"]
|
||||
[2014-08-22 11:36:46 CEST] chat: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"hash-object\",\"-w\",\"--stdin-paths\",\"--no-filters\"]
|
||||
[2014-08-22 11:36:46 CEST] feed: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"update-index\",\"-z\",\"--index-info\"]
|
||||
[2014-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
|
||||
(Recording state in git...)
|
||||
[2014-08-22 11:36:46 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"write-tree\"]
|
||||
error: invalid object 100644 5d471129a031f0f493de3736eaea6f2f4056aeee for '000/091/WORM-s1493-m1321288671--scrapbook%data%20111114173520%horiz-menu-tab-r_001.png.log'
|
||||
fatal: git-write-tree: error building trees
|
||||
git-annex: failed to read sha from git write-tree
|
||||
|
||||
# End of transcript or log.
|
||||
\"\"\"]]
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,27 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 3"
|
||||
date="2014-08-22T09:58:05Z"
|
||||
content="""
|
||||
Doing a git annex fsck on a new clone of the repository succeded; the problem must somehow with the .git/annex/index then, I presume?
|
||||
|
||||
I did a git reset to restore to the sane state state before adding, but the problem is that I cannot unannex the files I added. :(
|
||||
|
||||
[[!format sh \"\"\"
|
||||
nx unannex scrapbook/data/20140822101558/1.jpg
|
||||
[2014-08-22 11:56:16 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"--head\"]
|
||||
[2014-08-22 11:56:16 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"diff-index\",\"-z\",\"--raw\",\"--no-renames\",\"-l0\",\"--cached\",\"HEAD\"]
|
||||
[2014-08-22 11:56:16 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"ls-files\",\"--cached\",\"-z\",\"--\",\"scrapbook/data/20140822101558/1.jpg\"]
|
||||
[2014-08-22 11:56:16 CEST] call: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"commit\",\"-q\",\"--allow-empty\",\"--no-verify\",\"-m\",\"content removed from git annex\"]
|
||||
[2014-08-22 11:56:16 CEST] chat: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"hash-object\",\"-w\",\"--stdin-paths\",\"--no-filters\"]
|
||||
[2014-08-22 11:56:16 CEST] feed: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"update-index\",\"-z\",\"--index-info\"]
|
||||
[2014-08-22 11:56:16 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
|
||||
(Recording state in git...)
|
||||
[2014-08-22 11:56:16 CEST] read: git [\"--git-dir=/home/seb/Webmirror/.git\",\"--work-tree=/home/seb/Webmirror\",\"write-tree\"]
|
||||
error: invalid object 100644 5d471129a031f0f493de3736eaea6f2f4056aeee for '000/091/WORM-s1493-m1321288671--scrapbook%data%20111114173520%horiz-menu-tab-r_001.png.log'
|
||||
fatal: git-write-tree: error building trees
|
||||
git-annex: failed to read sha from git write-tree
|
||||
\"\"\"]]
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 4"
|
||||
date="2014-08-22T10:15:51Z"
|
||||
content="""
|
||||
The file referred to in the error message seems to be in good shape:
|
||||
|
||||
[[!format sh \"\"\"
|
||||
git --no-pager show git-annex:000/091/WORM-s1493-m1321288671--scrapbook%data%20111114173520%horiz-menu-tab-r_001.png.log
|
||||
1408605730.57892s 0 b25f42de-f4be-4d31-84d1-ab0b71dfec01
|
||||
1408562938.526946s 0 e148ea91-0eb6-4f47-86e9-db2136a15279
|
||||
\"\"\"]]
|
||||
|
||||
Strangely, the SHA1 of the blob is different from the one reported in the write-tree error.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 5"
|
||||
date="2014-08-22T13:07:34Z"
|
||||
content="""
|
||||
I remembered I keep an hourly snapshot regimen and was able to get back the repository from before doing the «add» this morning. Both git fsck and git annex fsck return no errors, and yet, whenever anything is done to the git-annex branch (I tried add and forget), I get the above error.
|
||||
"""]]
|
|
@ -0,0 +1,15 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 6"
|
||||
date="2014-08-22T13:15:06Z"
|
||||
content="""
|
||||
I tried git annex repair on the repo (before doing any adds). It reports no fsck errors, but the repair then dies from a stack overflow.
|
||||
|
||||
[[!format sh \"\"\"
|
||||
Running git fsck ...
|
||||
No problems found.
|
||||
Stack space overflow: current size 8388608 bytes.
|
||||
Use `+RTS -Ksize -RTS' to increase it.
|
||||
\"\"\"]]
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 7"
|
||||
date="2014-08-22T14:00:42Z"
|
||||
content="""
|
||||
I experimented on my snapshot a bit and found out something odd: When I reset the git-annex branch from dda9b06 to git-annex~1 (4246f73) my local file additions succeed, even though git-annex will fast-forward the branch to dda9b06 again before adding (when merging from origin/git-annex). dda9b06 is a large commit in which I dropped many unused WORM keys from another remote.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 8"
|
||||
date="2014-08-22T18:57:37Z"
|
||||
content="""
|
||||
I just checked my other large git annex repo and noticed that here too I could no longer add files to the annex. The same observations as above apply. Here too on the tip of the git-anenx branch I had one huge commit in which I dropped the last of the unused WORM keys from another remote. Resetting the git-annex branch to git-annex~1 allowed me to make additions again, even though the reset tip was subsequently merged in again from the remote tracking branch.
|
||||
"""]]
|
|
@ -0,0 +1,22 @@
|
|||
[[!comment format=mdwn
|
||||
username="zardoz"
|
||||
ip="78.48.163.229"
|
||||
subject="comment 9"
|
||||
date="2014-09-07T14:04:51Z"
|
||||
content="""
|
||||
Any ideas? I noticed one alternative way (cf. the reset workaround
|
||||
above) to make «git annex add» work again is by deleting
|
||||
.git/annex/index*. Is this safe?
|
||||
|
||||
In both repos, I had not even staged annex additions before the index
|
||||
was corrupted; the corruption must somehow have been left-over from
|
||||
earlier actions, altough all previous additions succeeded at the time,
|
||||
before both repositories mysteriously stopped working (in the context
|
||||
of backend-migration).
|
||||
|
||||
I still have the original snapshots around if you’d like to debug
|
||||
this. As noted, «git fsck» succeeds, and all the block-level checksums
|
||||
check out, so the problem can’t be on the block device or file-system
|
||||
level.
|
||||
|
||||
"""]]
|
|
@ -0,0 +1,31 @@
|
|||
~~~~
|
||||
$ git annex version
|
||||
git-annex version: 5.20140818-g10bf03a
|
||||
~~~~
|
||||
|
||||
When repository was initially created, it used "old" hashing from http://git-annex.branchable.com/internals/hashing/ . After some operations, annex was upgraded to "new" format. However, symlinks are still in "old" format and dangling. "git annex fsck", "git annex repair", "git annex pre-commit" - none helps.
|
||||
|
||||
~~~~
|
||||
$ ls -l pics
|
||||
lrwxrwxrwx 1 pfalcon pfalcon 199 Jan 22 2012 IMG_3776.JPG -> ../.git/annex/objects/KM/j6/SHA256E-s688630--5bc2e8beb7a57f6fbcd7d9321cd5283f04448ea475099dac07ae38f002208040.JPG/SHA256E-s688630--5bc2e8beb7a57f6fbcd7d9321cd5283f04448ea475099dac07ae38f002208040.JPG
|
||||
lrwxrwxrwx 1 pfalcon pfalcon 199 Jan 22 2012 renamed2.jpg -> ../.git/annex/objects/7F/z3/SHA256E-s676047--3cd28892ee54aba13e074f230709b2c3b87915ff36efd9be3ddfc603e92ecdda.JPG/SHA256E-s676047--3cd28892ee54aba13e074f230709b2c3b87915ff36efd9be3ddfc603e92ecdda.JPG
|
||||
lrwxrwxrwx 1 pfalcon pfalcon 199 Jan 22 2012 renamed.jpg -> ../.git/annex/objects/W1/vK/SHA256E-s585398--005fe0534d6cc17a3536c1817b091d00249834c338f289ec6569e9f262889251.JPG/SHA256E-s585398--005fe0534d6cc17a3536c1817b091d00249834c338f289ec6569e9f262889251.JPG
|
||||
|
||||
$ find .git/annex/objects/
|
||||
.git/annex/objects/
|
||||
.git/annex/objects/219
|
||||
.git/annex/objects/219/741
|
||||
.git/annex/objects/219/741/SHA256E-s585398--005fe0534d6cc17a3536c1817b091d00249834c338f289ec6569e9f262889251.JPG
|
||||
.git/annex/objects/219/741/SHA256E-s585398--005fe0534d6cc17a3536c1817b091d00249834c338f289ec6569e9f262889251.JPG/SHA256E-s585398--005fe0534d6cc17a3536c1817b091d00249834c338f289ec6569e9f262889251.JPG
|
||||
.git/annex/objects/7a6
|
||||
.git/annex/objects/7a6/632
|
||||
.git/annex/objects/7a6/632/SHA256E-s688630--5bc2e8beb7a57f6fbcd7d9321cd5283f04448ea475099dac07ae38f002208040.JPG
|
||||
.git/annex/objects/7a6/632/SHA256E-s688630--5bc2e8beb7a57f6fbcd7d9321cd5283f04448ea475099dac07ae38f002208040.JPG/SHA256E-s688630--5bc2e8beb7a57f6fbcd7d9321cd5283f04448ea475099dac07ae38f002208040.JPG
|
||||
.git/annex/objects/df3
|
||||
.git/annex/objects/df3/9a8
|
||||
.git/annex/objects/df3/9a8/SHA256E-s676047--3cd28892ee54aba13e074f230709b2c3b87915ff36efd9be3ddfc603e92ecdda.JPG
|
||||
.git/annex/objects/df3/9a8/SHA256E-s676047--3cd28892ee54aba13e074f230709b2c3b87915ff36efd9be3ddfc603e92ecdda.JPG/SHA256E-s676047--3cd28892ee54aba13e074f230709b2c3b87915ff36efd9be3ddfc603e92ecdda.JPG
|
||||
~~~~
|
||||
|
||||
> Unforunately, I cannot see through the attitude problem to a clear bug
|
||||
> report. Lacking time/energy to try to coax one out. [[done]] --[[Joey]]
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Reference in a new issue