Merge branch 'master' into s3-aws
Conflicts: git-annex.cabal
This commit is contained in:
commit
ef01ff1e77
128 changed files with 1219 additions and 511 deletions
|
@ -353,11 +353,8 @@ toDirectGen k f = do
|
|||
void $ addAssociatedFile k f
|
||||
modifyContent loc $ do
|
||||
thawContent loc
|
||||
replaceFileOr f
|
||||
(liftIO . moveFile loc)
|
||||
$ \tmp -> do -- rollback
|
||||
liftIO (moveFile tmp loc)
|
||||
freezeContent loc
|
||||
liftIO (replaceFileFrom loc f)
|
||||
`catchIO` (\_ -> freezeContent loc)
|
||||
fromdirect loc = do
|
||||
replaceFile f $
|
||||
liftIO . void . copyFileExternal loc
|
||||
|
|
|
@ -30,14 +30,21 @@ replaceFileOr :: FilePath -> (FilePath -> Annex ()) -> (FilePath -> Annex ()) ->
|
|||
replaceFileOr file action rollback = do
|
||||
tmpdir <- fromRepo gitAnnexTmpMiscDir
|
||||
void $ createAnnexDirectory tmpdir
|
||||
bracket (liftIO $ setup tmpdir) rollback $ \tmpfile -> do
|
||||
action tmpfile
|
||||
liftIO $ catchIO (rename tmpfile file) (fallback tmpfile)
|
||||
tmpfile <- liftIO $ setup tmpdir
|
||||
go tmpfile `catchNonAsync` (const $ rollback tmpfile)
|
||||
where
|
||||
setup tmpdir = do
|
||||
(tmpfile, h) <- openTempFileWithDefaultPermissions tmpdir "tmp"
|
||||
hClose h
|
||||
return tmpfile
|
||||
fallback tmpfile _ = do
|
||||
createDirectoryIfMissing True $ parentDir file
|
||||
moveFile tmpfile file
|
||||
go tmpfile = do
|
||||
action tmpfile
|
||||
liftIO $ replaceFileFrom tmpfile file
|
||||
|
||||
replaceFileFrom :: FilePath -> FilePath -> IO ()
|
||||
replaceFileFrom src dest = go `catchIO` fallback
|
||||
where
|
||||
go = moveFile src dest
|
||||
fallback _ = do
|
||||
createDirectoryIfMissing True $ parentDir dest
|
||||
go
|
||||
|
|
|
@ -12,6 +12,7 @@ module Annex.Transfer (
|
|||
upload,
|
||||
download,
|
||||
runTransfer,
|
||||
alwaysRunTransfer,
|
||||
noRetry,
|
||||
forwardRetry,
|
||||
) where
|
||||
|
@ -46,12 +47,23 @@ download u key f d a _witness = runTransfer (Transfer Download u key) f d a
|
|||
- no transfer information or lock file is used.
|
||||
-}
|
||||
runTransfer :: Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex Bool) -> Annex Bool
|
||||
runTransfer t file shouldretry a = do
|
||||
runTransfer = runTransfer' False
|
||||
|
||||
{- Like runTransfer, but ignores any existing transfer lock file for the
|
||||
- transfer, allowing re-running a transfer that is already in progress.
|
||||
-
|
||||
- Note that this may result in confusing progress meter display in the
|
||||
- webapp, if multiple processes are writing to the transfer info file. -}
|
||||
alwaysRunTransfer :: Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex Bool) -> Annex Bool
|
||||
alwaysRunTransfer = runTransfer' True
|
||||
|
||||
runTransfer' :: Bool -> Transfer -> Maybe FilePath -> RetryDecider -> (MeterUpdate -> Annex Bool) -> Annex Bool
|
||||
runTransfer' ignorelock t file shouldretry a = do
|
||||
info <- liftIO $ startTransferInfo file
|
||||
(meter, tfile, metervar) <- mkProgressUpdater t info
|
||||
mode <- annexFileMode
|
||||
(fd, inprogress) <- liftIO $ prep tfile mode info
|
||||
if inprogress
|
||||
if inprogress && not ignorelock
|
||||
then do
|
||||
showNote "transfer already in progress"
|
||||
return False
|
||||
|
|
|
@ -42,6 +42,7 @@ import Utility.Gpg
|
|||
import Annex.UUID
|
||||
import Assistant.Ssh
|
||||
import Config
|
||||
import Logs.Web (webUUID)
|
||||
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Map as M
|
||||
|
@ -191,26 +192,29 @@ postEditNewCloudRepositoryR :: UUID -> Handler Html
|
|||
postEditNewCloudRepositoryR uuid = connectionNeeded >> editForm True (RepoUUID uuid)
|
||||
|
||||
editForm :: Bool -> RepoId -> Handler Html
|
||||
editForm new (RepoUUID uuid) = page "Edit repository" (Just Configuration) $ do
|
||||
mremote <- liftAnnex $ Remote.remoteFromUUID uuid
|
||||
when (mremote == Nothing) $
|
||||
whenM ((/=) uuid <$> liftAnnex getUUID) $
|
||||
error "unknown remote"
|
||||
curr <- liftAnnex $ getRepoConfig uuid mremote
|
||||
liftAnnex $ checkAssociatedDirectory curr mremote
|
||||
((result, form), enctype) <- liftH $
|
||||
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ editRepositoryAForm mremote curr
|
||||
case result of
|
||||
FormSuccess input -> liftH $ do
|
||||
setRepoConfig uuid mremote curr input
|
||||
liftAnnex $ checkAssociatedDirectory input mremote
|
||||
redirect DashboardR
|
||||
_ -> do
|
||||
let istransfer = repoGroup curr == RepoGroupStandard TransferGroup
|
||||
config <- liftAnnex $ M.lookup uuid <$> readRemoteLog
|
||||
let repoInfo = getRepoInfo mremote config
|
||||
let repoEncryption = getRepoEncryption mremote config
|
||||
$(widgetFile "configurators/edit/repository")
|
||||
editForm new (RepoUUID uuid)
|
||||
| uuid == webUUID = page "The web" (Just Configuration) $ do
|
||||
$(widgetFile "configurators/edit/webrepository")
|
||||
| otherwise = page "Edit repository" (Just Configuration) $ do
|
||||
mremote <- liftAnnex $ Remote.remoteFromUUID uuid
|
||||
when (mremote == Nothing) $
|
||||
whenM ((/=) uuid <$> liftAnnex getUUID) $
|
||||
error "unknown remote"
|
||||
curr <- liftAnnex $ getRepoConfig uuid mremote
|
||||
liftAnnex $ checkAssociatedDirectory curr mremote
|
||||
((result, form), enctype) <- liftH $
|
||||
runFormPostNoToken $ renderBootstrap3 bootstrapFormLayout $ editRepositoryAForm mremote curr
|
||||
case result of
|
||||
FormSuccess input -> liftH $ do
|
||||
setRepoConfig uuid mremote curr input
|
||||
liftAnnex $ checkAssociatedDirectory input mremote
|
||||
redirect DashboardR
|
||||
_ -> do
|
||||
let istransfer = repoGroup curr == RepoGroupStandard TransferGroup
|
||||
config <- liftAnnex $ M.lookup uuid <$> readRemoteLog
|
||||
let repoInfo = getRepoInfo mremote config
|
||||
let repoEncryption = getRepoEncryption mremote config
|
||||
$(widgetFile "configurators/edit/repository")
|
||||
editForm _new r@(RepoName _) = page "Edit repository" (Just Configuration) $ do
|
||||
mr <- liftAnnex (repoIdRemote r)
|
||||
let repoInfo = getRepoInfo mr Nothing
|
||||
|
|
|
@ -36,7 +36,7 @@ backend = Backend
|
|||
keyValue :: KeySource -> Annex (Maybe Key)
|
||||
keyValue source = do
|
||||
stat <- liftIO $ getFileStatus $ contentLocation source
|
||||
n <- genKeyName $ keyFilename source
|
||||
n <- genKeyName $ takeFileName $ keyFilename source
|
||||
return $ Just $ stubKey
|
||||
{ keyName = n
|
||||
, keyBackendName = name backend
|
||||
|
|
|
@ -46,7 +46,7 @@ import Prelude hiding (log)
|
|||
|
||||
import Utility.Monad
|
||||
import Utility.Misc
|
||||
import Utility.Exception
|
||||
import Utility.Exception hiding (try)
|
||||
import Utility.Path
|
||||
import Utility.FileSystemEncoding
|
||||
|
||||
|
|
|
@ -200,7 +200,7 @@ tryScan r
|
|||
where
|
||||
p = proc cmd $ toCommand params
|
||||
|
||||
configlist = Ssh.onRemote r (pipedconfig, Nothing) "configlist" [] []
|
||||
configlist = Ssh.onRemote r (pipedconfig, return Nothing) "configlist" [] []
|
||||
manualconfiglist = do
|
||||
gc <- Annex.getRemoteGitConfig r
|
||||
sshparams <- Ssh.toRepo r gc [Param sshcmd]
|
||||
|
|
|
@ -47,3 +47,11 @@ fieldTransfer direction key a = do
|
|||
(\u -> runTransfer (Transfer direction (toUUID u) key) afile noRetry a)
|
||||
=<< Fields.getField Fields.remoteUUID
|
||||
liftIO $ exitBool ok
|
||||
where
|
||||
{- Allow the key to be sent to the remote even if there seems to be
|
||||
- another transfer of that key going on to that remote.
|
||||
- That one may be stale, etc.
|
||||
-}
|
||||
runner
|
||||
| direction == Upload = alwaysRunTransfer
|
||||
| otherwise = runTransfer
|
||||
|
|
|
@ -62,13 +62,16 @@ start basesz ws = do
|
|||
ks <- mapM randKey (keySizes basesz fast)
|
||||
rs <- catMaybes <$> mapM (adjustChunkSize r) (chunkSizes basesz fast)
|
||||
rs' <- concat <$> mapM encryptionVariants rs
|
||||
next $ perform rs' ks
|
||||
unavailrs <- catMaybes <$> mapM Remote.mkUnavailable [r]
|
||||
next $ perform rs' unavailrs ks
|
||||
|
||||
perform :: [Remote] -> [Key] -> CommandPerform
|
||||
perform rs ks = do
|
||||
perform :: [Remote] -> [Remote] -> [Key] -> CommandPerform
|
||||
perform rs unavailrs ks = do
|
||||
st <- Annex.getState id
|
||||
let tests = testGroup "Remote Tests" $
|
||||
[ testGroup (desc r k) (test st r k) | k <- ks, r <- rs ]
|
||||
let tests = testGroup "Remote Tests" $ concat
|
||||
[ [ testGroup "unavailable remote" (testUnavailable st r (Prelude.head ks)) | r <- unavailrs ]
|
||||
, [ testGroup (desc r k) (test st r k) | k <- ks, r <- rs ]
|
||||
]
|
||||
ok <- case tryIngredients [consoleTestReporter] mempty tests of
|
||||
Nothing -> error "No tests found!?"
|
||||
Just act -> liftIO act
|
||||
|
@ -155,6 +158,28 @@ test st r k =
|
|||
store = Remote.storeKey r k Nothing nullMeterUpdate
|
||||
remove = Remote.removeKey r k
|
||||
|
||||
testUnavailable :: Annex.AnnexState -> Remote -> Key -> [TestTree]
|
||||
testUnavailable st r k =
|
||||
[ check (== Right False) "removeKey" $
|
||||
Remote.removeKey r k
|
||||
, check (== Right False) "storeKey" $
|
||||
Remote.storeKey r k Nothing nullMeterUpdate
|
||||
, check (`notElem` [Right True, Right False]) "checkPresent" $
|
||||
Remote.checkPresent r k
|
||||
, check (== Right False) "retrieveKeyFile" $
|
||||
getViaTmp k $ \dest ->
|
||||
Remote.retrieveKeyFile r k Nothing dest nullMeterUpdate
|
||||
, check (== Right False) "retrieveKeyFileCheap" $
|
||||
getViaTmp k $ \dest ->
|
||||
Remote.retrieveKeyFileCheap r k dest
|
||||
]
|
||||
where
|
||||
check checkval desc a = testCase desc $ do
|
||||
v <- Annex.eval st $ do
|
||||
Annex.setOutput QuietOutput
|
||||
either (Left . show) Right <$> tryNonAsync a
|
||||
checkval v @? ("(got: " ++ show v ++ ")")
|
||||
|
||||
cleanup :: [Remote] -> [Key] -> Bool -> CommandCleanup
|
||||
cleanup rs ks ok = do
|
||||
forM_ rs $ \r -> forM_ ks (Remote.removeKey r)
|
||||
|
|
|
@ -26,12 +26,17 @@ seek = withFilesInGit $ whenAnnexed start
|
|||
{- The unlock subcommand replaces the symlink with a copy of the file's
|
||||
- content. -}
|
||||
start :: FilePath -> Key -> CommandStart
|
||||
start file key = stopUnless (inAnnex key) $ do
|
||||
start file key = do
|
||||
showStart "unlock" file
|
||||
ifM (checkDiskSpace Nothing key 0)
|
||||
( next $ perform file key
|
||||
ifM (inAnnex key)
|
||||
( ifM (checkDiskSpace Nothing key 0)
|
||||
( next $ perform file key
|
||||
, do
|
||||
warning "not enough disk space to copy file"
|
||||
next $ next $ return False
|
||||
)
|
||||
, do
|
||||
warning "not enough disk space to copy file"
|
||||
warning "content not present; cannot unlock"
|
||||
next $ next $ return False
|
||||
)
|
||||
|
||||
|
|
16
Creds.hs
16
Creds.hs
|
@ -23,7 +23,7 @@ import Annex.Perms
|
|||
import Utility.FileMode
|
||||
import Crypto
|
||||
import Types.Remote (RemoteConfig, RemoteConfigKey)
|
||||
import Remote.Helper.Encryptable (remoteCipher, embedCreds)
|
||||
import Remote.Helper.Encryptable (remoteCipher, remoteCipher', embedCreds)
|
||||
import Utility.Env (getEnv)
|
||||
|
||||
import qualified Data.ByteString.Lazy.Char8 as L
|
||||
|
@ -85,15 +85,19 @@ getRemoteCredPair c storage = maybe fromcache (return . Just) =<< fromenv
|
|||
fromcache = maybe fromconfig (return . Just) =<< readCacheCredPair storage
|
||||
fromconfig = case credPairRemoteKey storage of
|
||||
Just key -> do
|
||||
mcipher <- remoteCipher c
|
||||
case (M.lookup key c, mcipher) of
|
||||
(Nothing, _) -> return Nothing
|
||||
(Just enccreds, Just cipher) -> do
|
||||
mcipher <- remoteCipher' c
|
||||
case (mcipher, M.lookup key c) of
|
||||
(_, Nothing) -> return Nothing
|
||||
(Just (_cipher, SharedCipher {}), Just bcreds) ->
|
||||
-- When using a shared cipher, the
|
||||
-- creds are not stored encrypted.
|
||||
fromcreds $ fromB64 bcreds
|
||||
(Just (cipher, _), Just enccreds) -> do
|
||||
creds <- liftIO $ decrypt cipher
|
||||
(feedBytes $ L.pack $ fromB64 enccreds)
|
||||
(readBytes $ return . L.unpack)
|
||||
fromcreds creds
|
||||
(Just bcreds, Nothing) ->
|
||||
(Nothing, Just bcreds) ->
|
||||
fromcreds $ fromB64 bcreds
|
||||
Nothing -> return Nothing
|
||||
fromcreds creds = case decodeCredPair creds of
|
||||
|
|
6
Makefile
6
Makefile
|
@ -187,7 +187,8 @@ no-th-webapp-stage1: Build/EvilSplicer
|
|||
# Some additional dependencies needed by the expanded splices.
|
||||
sed -i 's/^ Build-Depends: / Build-Depends: yesod-routes, yesod-core, shakespeare-css, shakespeare-js, shakespeare, blaze-markup, file-embed, wai-app-static, /' tmp/no-th-tree/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 -XMagicHash /i' tmp/no-th-tree/git-annex.cabal
|
||||
sed -i 's/GHC-Options: \(.*\)-Wall/GHC-Options: \1-Wall -fno-warn-unused-imports /i' tmp/no-th-tree/git-annex.cabal
|
||||
sed -i 's/Extensions: /Extensions: MagicHash /i' tmp/no-th-tree/git-annex.cabal
|
||||
|
||||
# Run on the arm system, after stage1
|
||||
no-th-webapp-stage2:
|
||||
|
@ -216,7 +217,8 @@ android: Build/EvilSplicer
|
|||
# Some additional dependencies needed by the expanded splices.
|
||||
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 -XMagicHash /i' tmp/androidtree/git-annex.cabal
|
||||
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
|
||||
# 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.
|
||||
|
|
|
@ -72,6 +72,7 @@ gen r u c gc = do
|
|||
, remotetype = remote
|
||||
, availability = if bupLocal buprepo then LocallyAvailable else GloballyAvailable
|
||||
, readonly = False
|
||||
, mkUnavailable = return Nothing
|
||||
}
|
||||
return $ Just $ specialRemote' specialcfg c
|
||||
(simplyPrepare $ store this buprepo)
|
||||
|
|
|
@ -69,6 +69,7 @@ gen r u c gc = do
|
|||
, remotetype = remote
|
||||
, availability = if ddarLocal ddarrepo then LocallyAvailable else GloballyAvailable
|
||||
, readonly = False
|
||||
, mkUnavailable = return Nothing
|
||||
}
|
||||
ddarrepo = fromMaybe (error "missing ddarrepo") $ remoteAnnexDdarRepo gc
|
||||
specialcfg = (specialRemoteCfg c)
|
||||
|
|
|
@ -65,7 +65,9 @@ gen r u c gc = do
|
|||
localpath = Just dir,
|
||||
readonly = False,
|
||||
availability = LocallyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = gen r u c $
|
||||
gc { remoteAnnexDirectory = Just "/dev/null" }
|
||||
}
|
||||
where
|
||||
dir = fromMaybe (error "missing directory") $ remoteAnnexDirectory gc
|
||||
|
@ -196,5 +198,8 @@ checkKey d (LegacyChunks _) k = Legacy.checkKey d locations k
|
|||
checkKey d _ k = liftIO $
|
||||
ifM (anyM doesFileExist (locations d k))
|
||||
( return True
|
||||
, error $ "directory " ++ d ++ " is not accessible"
|
||||
, ifM (doesDirectoryExist d)
|
||||
( return False
|
||||
, error $ "directory " ++ d ++ " is not accessible"
|
||||
)
|
||||
)
|
||||
|
|
|
@ -65,7 +65,9 @@ gen r u c gc = do
|
|||
gitconfig = gc,
|
||||
readonly = False,
|
||||
availability = avail,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = gen r u c $
|
||||
gc { remoteAnnexExternalType = Just "!dne!" }
|
||||
}
|
||||
where
|
||||
externaltype = fromMaybe (error "missing externaltype") (remoteAnnexExternalType gc)
|
||||
|
|
|
@ -120,6 +120,7 @@ gen' r u c gc = do
|
|||
, readonly = Git.repoIsHttp r
|
||||
, availability = availabilityCalc r
|
||||
, remotetype = remote
|
||||
, mkUnavailable = return Nothing
|
||||
}
|
||||
return $ Just $ specialRemote' specialcfg c
|
||||
(simplyPrepare $ store this rsyncopts)
|
||||
|
@ -255,7 +256,7 @@ setupRepo gcryptid r
|
|||
|
||||
{- Ask git-annex-shell to configure the repository as a gcrypt
|
||||
- repository. May fail if it is too old. -}
|
||||
gitannexshellsetup = Ssh.onRemote r (boolSystem, False)
|
||||
gitannexshellsetup = Ssh.onRemote r (boolSystem, return False)
|
||||
"gcryptsetup" [ Param gcryptid ] []
|
||||
|
||||
denyNonFastForwards = "receive.denyNonFastForwards"
|
||||
|
@ -389,7 +390,7 @@ getGCryptId fast r
|
|||
| Git.repoIsLocal r || Git.repoIsLocalUnknown r = extract <$>
|
||||
liftIO (catchMaybeIO $ Git.Config.read r)
|
||||
| not fast = extract . liftM fst <$> getM (eitherToMaybe <$>)
|
||||
[ Ssh.onRemote r (Git.Config.fromPipe r, Left undefined) "configlist" [] []
|
||||
[ Ssh.onRemote r (Git.Config.fromPipe r, return (Left undefined)) "configlist" [] []
|
||||
, getConfigViaRsync r
|
||||
]
|
||||
| otherwise = return (Nothing, r)
|
||||
|
|
|
@ -55,6 +55,7 @@ import Creds
|
|||
import Control.Concurrent
|
||||
import Control.Concurrent.MSampleVar
|
||||
import qualified Data.Map as M
|
||||
import Network.URI
|
||||
|
||||
remote :: RemoteType
|
||||
remote = RemoteType {
|
||||
|
@ -156,8 +157,22 @@ gen r u c gc
|
|||
, readonly = Git.repoIsHttp r
|
||||
, availability = availabilityCalc r
|
||||
, remotetype = remote
|
||||
, mkUnavailable = unavailable r u c gc
|
||||
}
|
||||
|
||||
unavailable :: Git.Repo -> UUID -> RemoteConfig -> RemoteGitConfig -> Annex (Maybe Remote)
|
||||
unavailable r u c gc = gen r' u c gc
|
||||
where
|
||||
r' = case Git.location r of
|
||||
Git.Local { Git.gitdir = d } ->
|
||||
r { Git.location = Git.LocalUnknown d }
|
||||
Git.Url url -> case uriAuthority url of
|
||||
Just auth ->
|
||||
let auth' = auth { uriRegName = "!dne!" }
|
||||
in r { Git.location = Git.Url (url { uriAuthority = Just auth' })}
|
||||
Nothing -> r { Git.location = Git.Unknown }
|
||||
_ -> r -- already unavailable
|
||||
|
||||
{- Checks relatively inexpensively if a repository is available for use. -}
|
||||
repoAvail :: Git.Repo -> Annex Bool
|
||||
repoAvail r
|
||||
|
@ -180,7 +195,7 @@ tryGitConfigRead :: Git.Repo -> Annex Git.Repo
|
|||
tryGitConfigRead r
|
||||
| haveconfig r = return r -- already read
|
||||
| Git.repoIsSsh r = store $ do
|
||||
v <- Ssh.onRemote r (pipedconfig, Left undefined) "configlist" [] []
|
||||
v <- Ssh.onRemote r (pipedconfig, return (Left undefined)) "configlist" [] []
|
||||
case v of
|
||||
Right r'
|
||||
| haveconfig r' -> return r'
|
||||
|
@ -298,8 +313,8 @@ inAnnex rmt key
|
|||
)
|
||||
checkremote = Ssh.inAnnex r key
|
||||
checklocal = guardUsable r (cantCheck r) $
|
||||
fromMaybe (cantCheck r)
|
||||
<$> onLocal rmt (Annex.Content.inAnnexSafe key)
|
||||
maybe (cantCheck r) return
|
||||
=<< onLocal rmt (Annex.Content.inAnnexSafe key)
|
||||
|
||||
keyUrls :: Remote -> Key -> [String]
|
||||
keyUrls r key = map tourl locs'
|
||||
|
|
|
@ -65,7 +65,8 @@ gen r u c gc = new <$> remoteCost gc veryExpensiveRemoteCost
|
|||
localpath = Nothing,
|
||||
readonly = False,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = return Nothing
|
||||
}
|
||||
specialcfg = (specialRemoteCfg c)
|
||||
-- Disabled until jobList gets support for chunks.
|
||||
|
|
|
@ -348,11 +348,12 @@ checkPresentChunks checker u chunkconfig encryptor basek
|
|||
v <- check basek
|
||||
case v of
|
||||
Right True -> return True
|
||||
Left e -> checklists (Just e) =<< chunkKeysOnly u basek
|
||||
_ -> checklists Nothing =<< chunkKeysOnly u basek
|
||||
| otherwise = checklists Nothing =<< chunkKeys u chunkconfig basek
|
||||
where
|
||||
checklists Nothing [] = return False
|
||||
checklists (Just deferrederror) [] = error deferrederror
|
||||
checklists (Just deferrederror) [] = throwM deferrederror
|
||||
checklists d (l:ls)
|
||||
| not (null l) = do
|
||||
v <- checkchunks l
|
||||
|
@ -362,14 +363,14 @@ checkPresentChunks checker u chunkconfig encryptor basek
|
|||
Right False -> checklists Nothing ls
|
||||
| otherwise = checklists d ls
|
||||
|
||||
checkchunks :: [Key] -> Annex (Either String Bool)
|
||||
checkchunks :: [Key] -> Annex (Either SomeException Bool)
|
||||
checkchunks [] = return (Right True)
|
||||
checkchunks (k:ks) = do
|
||||
v <- check k
|
||||
case v of
|
||||
Right True -> checkchunks ks
|
||||
Right False -> return $ Right False
|
||||
Left e -> return $ Left $ show e
|
||||
Left e -> return $ Left e
|
||||
|
||||
check = tryNonAsync . checker . encryptor
|
||||
|
||||
|
|
|
@ -71,18 +71,21 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c
|
|||
{- Gets encryption Cipher. The decrypted Ciphers are cached in the Annex
|
||||
- state. -}
|
||||
remoteCipher :: RemoteConfig -> Annex (Maybe Cipher)
|
||||
remoteCipher c = go $ extractCipher c
|
||||
remoteCipher = fmap fst <$$> remoteCipher'
|
||||
|
||||
remoteCipher' :: RemoteConfig -> Annex (Maybe (Cipher, StorableCipher))
|
||||
remoteCipher' c = go $ extractCipher c
|
||||
where
|
||||
go Nothing = return Nothing
|
||||
go (Just encipher) = do
|
||||
cache <- Annex.getState Annex.ciphers
|
||||
case M.lookup encipher cache of
|
||||
Just cipher -> return $ Just cipher
|
||||
Just cipher -> return $ Just (cipher, encipher)
|
||||
Nothing -> do
|
||||
showNote "gpg"
|
||||
cipher <- liftIO $ decryptCipher encipher
|
||||
Annex.changeState (\s -> s { Annex.ciphers = M.insert encipher cipher cache })
|
||||
return $ Just cipher
|
||||
return $ Just (cipher, encipher)
|
||||
|
||||
{- Checks if the remote's config allows storing creds in the remote's config.
|
||||
-
|
||||
|
|
|
@ -69,7 +69,7 @@ git_annex_shell r command params fields
|
|||
- a specified error value. -}
|
||||
onRemote
|
||||
:: Git.Repo
|
||||
-> (FilePath -> [CommandParam] -> IO a, a)
|
||||
-> (FilePath -> [CommandParam] -> IO a, Annex a)
|
||||
-> String
|
||||
-> [CommandParam]
|
||||
-> [(Field, String)]
|
||||
|
@ -78,7 +78,7 @@ onRemote r (with, errorval) command params fields = do
|
|||
s <- git_annex_shell r command params fields
|
||||
case s of
|
||||
Just (c, ps) -> liftIO $ with c ps
|
||||
Nothing -> return errorval
|
||||
Nothing -> errorval
|
||||
|
||||
{- Checks if a remote contains a key. -}
|
||||
inAnnex :: Git.Repo -> Key -> Annex Bool
|
||||
|
@ -86,14 +86,14 @@ inAnnex r k = do
|
|||
showChecking r
|
||||
onRemote r (check, cantCheck r) "inannex" [Param $ key2file k] []
|
||||
where
|
||||
check c p = dispatch <$> safeSystem c p
|
||||
dispatch ExitSuccess = True
|
||||
dispatch (ExitFailure 1) = False
|
||||
check c p = dispatch =<< safeSystem c p
|
||||
dispatch ExitSuccess = return True
|
||||
dispatch (ExitFailure 1) = return False
|
||||
dispatch _ = cantCheck r
|
||||
|
||||
{- Removes a key from a remote. -}
|
||||
dropKey :: Git.Repo -> Key -> Annex Bool
|
||||
dropKey r key = onRemote r (boolSystem, False) "dropkey"
|
||||
dropKey r key = onRemote r (boolSystem, return False) "dropkey"
|
||||
[ Params "--quiet --force"
|
||||
, Param $ key2file key
|
||||
]
|
||||
|
|
|
@ -58,7 +58,9 @@ gen r u c gc = do
|
|||
gitconfig = gc,
|
||||
readonly = False,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = gen r u c $
|
||||
gc { remoteAnnexHookType = Just "!dne!" }
|
||||
}
|
||||
where
|
||||
hooktype = fromMaybe (error "missing hooktype") $ remoteAnnexHookType gc
|
||||
|
|
|
@ -82,6 +82,7 @@ gen r u c gc = do
|
|||
, readonly = False
|
||||
, availability = if islocal then LocallyAvailable else GloballyAvailable
|
||||
, remotetype = remote
|
||||
, mkUnavailable = return Nothing
|
||||
}
|
||||
where
|
||||
specialcfg = (specialRemoteCfg c)
|
||||
|
|
|
@ -82,7 +82,8 @@ gen r u c gc = do
|
|||
localpath = Nothing,
|
||||
readonly = False,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = gen r u (M.insert "host" "!dne!" c) gc
|
||||
}
|
||||
|
||||
s3Setup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID)
|
||||
|
|
|
@ -83,7 +83,8 @@ gen r u c gc = do
|
|||
localpath = Nothing,
|
||||
readonly = False,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = return Nothing
|
||||
}
|
||||
|
||||
tahoeSetup :: Maybe UUID -> Maybe CredPair -> RemoteConfig -> Annex (RemoteConfig, UUID)
|
||||
|
|
|
@ -61,7 +61,8 @@ gen r _ c gc =
|
|||
repo = r,
|
||||
readonly = True,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = return Nothing
|
||||
}
|
||||
|
||||
downloadKey :: Key -> AssociatedFile -> FilePath -> MeterUpdate -> Annex Bool
|
||||
|
|
|
@ -70,7 +70,8 @@ gen r u c gc = new <$> remoteCost gc expensiveRemoteCost
|
|||
localpath = Nothing,
|
||||
readonly = False,
|
||||
availability = GloballyAvailable,
|
||||
remotetype = remote
|
||||
remotetype = remote,
|
||||
mkUnavailable = gen r u (M.insert "url" "http://!dne!/" c) gc
|
||||
}
|
||||
chunkconfig = getChunkConfig c
|
||||
|
||||
|
|
|
@ -95,7 +95,10 @@ data RemoteA a = Remote {
|
|||
-- a Remote can be globally available. (Ie, "in the cloud".)
|
||||
availability :: Availability,
|
||||
-- the type of the remote
|
||||
remotetype :: RemoteTypeA a
|
||||
remotetype :: RemoteTypeA a,
|
||||
-- For testing, makes a version of this remote that is not
|
||||
-- available for use. All its actions should fail.
|
||||
mkUnavailable :: a (Maybe (RemoteA a))
|
||||
}
|
||||
|
||||
instance Show (RemoteA a) where
|
||||
|
|
|
@ -52,11 +52,11 @@ catchMsgIO a = do
|
|||
|
||||
{- catch specialized for IO errors only -}
|
||||
catchIO :: MonadCatch m => m a -> (IOException -> m a) -> m a
|
||||
catchIO = catch
|
||||
catchIO = M.catch
|
||||
|
||||
{- try specialized for IO errors only -}
|
||||
tryIO :: MonadCatch m => m a -> m (Either IOException a)
|
||||
tryIO = try
|
||||
tryIO = M.try
|
||||
|
||||
{- bracket with setup and cleanup actions lifted to IO.
|
||||
-
|
||||
|
|
|
@ -119,8 +119,8 @@ feedRead params passphrase feeder reader = do
|
|||
#else
|
||||
-- store the passphrase in a temp file for gpg
|
||||
withTmpFile "gpg" $ \tmpfile h -> do
|
||||
hPutStr h passphrase
|
||||
hClose h
|
||||
liftIO $ hPutStr h passphrase
|
||||
liftIO $ hClose h
|
||||
let passphrasefile = [Param "--passphrase-file", File tmpfile]
|
||||
go $ passphrasefile ++ params
|
||||
#endif
|
||||
|
|
|
@ -40,6 +40,10 @@ import Common
|
|||
import System.PosixCompat.Types
|
||||
import Utility.QuickCheck
|
||||
|
||||
#ifdef mingw32_HOST_OS
|
||||
import Data.Word (Word64)
|
||||
#endif
|
||||
|
||||
data InodeCachePrim = InodeCachePrim FileID FileOffset EpochTime
|
||||
deriving (Show, Eq, Ord)
|
||||
|
||||
|
@ -204,6 +208,11 @@ instance Arbitrary InodeCache where
|
|||
<*> arbitrary
|
||||
in InodeCache <$> prim
|
||||
|
||||
#ifdef mingw32_HOST_OS
|
||||
instance Arbitrary FileID where
|
||||
arbitrary = fromIntegral <$> (arbitrary :: Gen Word64)
|
||||
#endif
|
||||
|
||||
prop_read_show_inodecache :: InodeCache -> Bool
|
||||
prop_read_show_inodecache c = case readInodeCache (showInodeCache c) of
|
||||
Nothing -> False
|
||||
|
|
125
Utility/Url.hs
125
Utility/Url.hs
|
@ -1,6 +1,6 @@
|
|||
{- Url downloading.
|
||||
-
|
||||
- Copyright 2011,2013 Joey Hess <joey@kitenet.net>
|
||||
- Copyright 2011-2014 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- License: BSD-2-clause
|
||||
-}
|
||||
|
@ -21,10 +21,11 @@ module Utility.Url (
|
|||
|
||||
import Common
|
||||
import Network.URI
|
||||
import qualified Network.Browser as Browser
|
||||
import Network.HTTP
|
||||
import Data.Either
|
||||
import Network.HTTP.Conduit
|
||||
import Network.HTTP.Types
|
||||
import Data.Default
|
||||
import qualified Data.CaseInsensitive as CI
|
||||
import qualified Data.ByteString.UTF8 as B8
|
||||
|
||||
import qualified Build.SysConfig
|
||||
|
||||
|
@ -60,33 +61,26 @@ check url expected_size = go <$$> exists url
|
|||
Nothing -> (True, True)
|
||||
|
||||
{- Checks that an url exists and could be successfully downloaded,
|
||||
- also returning its size if available.
|
||||
-
|
||||
- For a file: url, check it directly.
|
||||
-
|
||||
- Uses curl otherwise, when available, since curl handles https better
|
||||
- than does Haskell's Network.Browser.
|
||||
-}
|
||||
- also returning its size if available. -}
|
||||
exists :: URLString -> UrlOptions -> IO (Bool, Maybe Integer)
|
||||
exists url uo = case parseURIRelaxed url of
|
||||
Just u
|
||||
| uriScheme u == "file:" -> do
|
||||
s <- catchMaybeIO $ getFileStatus (unEscapeString $ uriPath u)
|
||||
case s of
|
||||
Just stat -> return (True, Just $ fromIntegral $ fileSize stat)
|
||||
Nothing -> dne
|
||||
| otherwise -> if Build.SysConfig.curl
|
||||
then do
|
||||
Just u -> case parseUrl (show u) of
|
||||
Just req -> existsconduit req `catchNonAsync` const dne
|
||||
-- http-conduit does not support file:, ftp:, etc urls,
|
||||
-- so fall back to reading files and using curl.
|
||||
Nothing
|
||||
| uriScheme u == "file:" -> do
|
||||
s <- catchMaybeIO $ getFileStatus (unEscapeString $ uriPath u)
|
||||
case s of
|
||||
Just stat -> return (True, Just $ fromIntegral $ fileSize stat)
|
||||
Nothing -> dne
|
||||
| Build.SysConfig.curl -> do
|
||||
output <- catchDefaultIO "" $
|
||||
readProcess "curl" $ toCommand curlparams
|
||||
case lastMaybe (lines output) of
|
||||
Just ('2':_:_) -> return (True, extractsize output)
|
||||
Just ('2':_:_) -> return (True, extractlencurl output)
|
||||
_ -> dne
|
||||
else do
|
||||
r <- request u HEAD uo
|
||||
case rspCode r of
|
||||
(2,_,_) -> return (True, size r)
|
||||
_ -> return (False, Nothing)
|
||||
| otherwise -> dne
|
||||
Nothing -> dne
|
||||
where
|
||||
dne = return (False, Nothing)
|
||||
|
@ -98,13 +92,28 @@ exists url uo = case parseURIRelaxed url of
|
|||
, Param "-w", Param "%{http_code}"
|
||||
] ++ concatMap (\h -> [Param "-H", Param h]) (reqHeaders uo) ++ (reqParams uo)
|
||||
|
||||
extractsize s = case lastMaybe $ filter ("Content-Length:" `isPrefixOf`) (lines s) of
|
||||
extractlencurl s = case lastMaybe $ filter ("Content-Length:" `isPrefixOf`) (lines s) of
|
||||
Just l -> case lastMaybe $ words l of
|
||||
Just sz -> readish sz
|
||||
_ -> Nothing
|
||||
_ -> Nothing
|
||||
|
||||
size = liftM Prelude.read . lookupHeader HdrContentLength . rspHeaders
|
||||
|
||||
extractlen resp = readish . B8.toString =<< headMaybe lenheaders
|
||||
where
|
||||
lenheaders = map snd $
|
||||
filter (\(h, _) -> h == hContentLength)
|
||||
(responseHeaders resp)
|
||||
|
||||
existsconduit req = withManager $ \mgr -> do
|
||||
let req' = (addUrlOptions uo req) { method = methodHead }
|
||||
resp <- http req' mgr
|
||||
-- forces processing the response before the
|
||||
-- manager is closed
|
||||
ret <- if responseStatus resp == ok200
|
||||
then return (True, extractlen resp)
|
||||
else liftIO dne
|
||||
liftIO $ closeManager mgr
|
||||
return ret
|
||||
|
||||
-- works for both wget and curl commands
|
||||
addUserAgent :: UrlOptions -> [CommandParam] -> [CommandParam]
|
||||
|
@ -112,6 +121,20 @@ addUserAgent uo ps = case userAgent uo of
|
|||
Nothing -> ps
|
||||
Just ua -> ps ++ [Param "--user-agent", Param ua]
|
||||
|
||||
addUrlOptions :: UrlOptions -> Request -> Request
|
||||
addUrlOptions uo r = r { requestHeaders = requestHeaders r ++ uaheader ++ otherheaders}
|
||||
where
|
||||
uaheader = case userAgent uo of
|
||||
Nothing -> []
|
||||
Just ua -> [(hUserAgent, B8.fromString ua)]
|
||||
otherheaders = map toheader (reqHeaders uo)
|
||||
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)
|
||||
|
||||
{- Used to download large files, such as the contents of keys.
|
||||
-
|
||||
- Uses wget or curl program for its progress bar. (Wget has a better one,
|
||||
|
@ -161,52 +184,6 @@ download' quiet url file uo =
|
|||
| quiet = [Param s]
|
||||
| otherwise = []
|
||||
|
||||
{- Uses Network.Browser to make a http request of an url.
|
||||
- For example, HEAD can be used to check if the url exists,
|
||||
- or GET used to get the url content (best for small urls).
|
||||
-
|
||||
- This does its own redirect following because Browser's is buggy for HEAD
|
||||
- requests.
|
||||
-
|
||||
- Unfortunately, does not handle https, so should only be used
|
||||
- when curl is not available.
|
||||
-}
|
||||
request :: URI -> RequestMethod -> UrlOptions -> IO (Response String)
|
||||
request url requesttype uo = go 5 url
|
||||
where
|
||||
go :: Int -> URI -> IO (Response String)
|
||||
go 0 _ = error "Too many redirects "
|
||||
go n u = do
|
||||
rsp <- Browser.browse $ do
|
||||
maybe noop Browser.setUserAgent (userAgent uo)
|
||||
Browser.setErrHandler ignore
|
||||
Browser.setOutHandler ignore
|
||||
Browser.setAllowRedirects False
|
||||
let req = mkRequest requesttype u :: Request_String
|
||||
snd <$> Browser.request (addheaders req)
|
||||
case rspCode rsp of
|
||||
(3,0,x) | x /= 5 -> redir (n - 1) u rsp
|
||||
_ -> return rsp
|
||||
addheaders req = setHeaders req (rqHeaders req ++ userheaders)
|
||||
userheaders = rights $ map parseHeader (reqHeaders uo)
|
||||
ignore = const noop
|
||||
redir n u rsp = case retrieveHeaders HdrLocation rsp of
|
||||
[] -> return rsp
|
||||
(Header _ newu:_) ->
|
||||
case parseURIReference newu of
|
||||
Nothing -> return rsp
|
||||
Just newURI -> go n $
|
||||
#if defined VERSION_network
|
||||
#if ! MIN_VERSION_network(2,4,0)
|
||||
#define WITH_OLD_URI
|
||||
#endif
|
||||
#endif
|
||||
#ifdef WITH_OLD_URI
|
||||
fromMaybe newURI (newURI `relativeTo` u)
|
||||
#else
|
||||
newURI `relativeTo` u
|
||||
#endif
|
||||
|
||||
{- Allows for spaces and other stuff in urls, properly escaping them. -}
|
||||
parseURIRelaxed :: URLString -> Maybe URI
|
||||
parseURIRelaxed = parseURI . escapeURIString isAllowedInURI
|
||||
|
|
13
debian/changelog
vendored
13
debian/changelog
vendored
|
@ -31,6 +31,19 @@ git-annex (5.20140718) UNRELEASED; urgency=medium
|
|||
due to the nature of bup.
|
||||
* unlock: Better error handling; continue past files that are not available
|
||||
or cannot be unlocked due to disk space, and try all specified files.
|
||||
* Windows: Now uses actual inode equivilants in new direct mode
|
||||
repositories, for safer detection of eg, renaming of files with the same
|
||||
size and mtime.
|
||||
* direct: Fix ugly warning messages.
|
||||
* WORM backend: When adding a file in a subdirectory, avoid including the
|
||||
subdirectory in the key name.
|
||||
* S3, Glacier, WebDAV: Fix bug that prevented accessing the creds
|
||||
when the repository was configured with encryption=shared embedcreds=yes.
|
||||
* direct: Avoid leaving file content in misctemp if interrupted.
|
||||
* git-annex-shell sendkey: Don't fail if a remote asks for a key to be sent
|
||||
that already has a transfer lock file indicating it's being sent to that
|
||||
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
|
||||
|
||||
|
|
4
debian/control
vendored
4
debian/control
vendored
|
@ -16,8 +16,6 @@ Build-Depends:
|
|||
libghc-aws-dev,
|
||||
libghc-conduit-dev,
|
||||
libghc-resourcet-dev,
|
||||
libghc-http-conduit-dev,
|
||||
libghc-http-client-dev,
|
||||
libghc-dav-dev (>= 1.0) [amd64 i386 kfreebsd-amd64 kfreebsd-i386 powerpc],
|
||||
libghc-quickcheck2-dev,
|
||||
libghc-monad-control-dev (>= 0.3),
|
||||
|
@ -50,6 +48,7 @@ Build-Depends:
|
|||
libghc-dns-dev,
|
||||
libghc-case-insensitive-dev,
|
||||
libghc-http-types-dev,
|
||||
libghc-http-conduit-dev,
|
||||
libghc-blaze-builder-dev,
|
||||
libghc-crypto-api-dev,
|
||||
libghc-network-multicast-dev,
|
||||
|
@ -59,7 +58,6 @@ Build-Depends:
|
|||
libghc-gnutls-dev (>= 0.1.4),
|
||||
libghc-xml-types-dev,
|
||||
libghc-async-dev,
|
||||
libghc-http-dev,
|
||||
libghc-feed-dev (>= 0.3.9.2),
|
||||
libghc-regex-tdfa-dev [!mipsel !s390],
|
||||
libghc-regex-compat-dev [mipsel s390],
|
||||
|
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 8"
|
||||
date="2014-08-12T18:00:46Z"
|
||||
content="""
|
||||
Ævar, you can use `git annex add --backend=SHA256` to temporarily override the backend.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-15T17:52:57Z"
|
||||
content="""
|
||||
I'm afraid all I can do to help with this is to say that the git-annex Android app does not do anything I know of to prevent running the programs, such as git, that are included in it. If your user cannot access them, it must be your OS configuration preventing it.
|
||||
"""]]
|
|
@ -0,0 +1,23 @@
|
|||
This is a follow-up to [this
|
||||
qbug](http://git-annex.branchable.com/bugs/WORM_keys_differ_depending_on_working_dir_during_add/).
|
||||
Thank you for your fix there! However, if I understood correctly, you
|
||||
indicated in your reply that the current fix completely removes the
|
||||
relative path component from WORM keys. I gave some thought to this
|
||||
and believe not having the relative path encoded inside WORM keys
|
||||
makes key collisions (and accordingly data-loss) a very dire problem,
|
||||
while they are not of practical concern if the relative path is
|
||||
encoded.
|
||||
|
||||
When relative paths are encoded within the key, a collision can only
|
||||
occur when a file in the same directory is annexed twice within the
|
||||
resolution of the mtime component inside the key (i.e., one second).
|
||||
As such, unless one adds files automatically with a period of < 1s,
|
||||
one can very much be certain that no collisions come up.
|
||||
|
||||
Without relative paths, however, one could never be certain that
|
||||
adding a file will not result in data-loss.
|
||||
|
||||
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.
|
||||
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-15T17:32:15Z"
|
||||
content="""
|
||||
I don't see much difference between (mtime, size, location) and (mtime, size) as far as entropy goes. Consider: A repository with all files in a single directory in the top level is going to have identical probabilities of collision either way. A less special case of a repository that typically has files added to it in a particular directory (\"inbox\", say), is again going to have identical probabilities of collision.
|
||||
|
||||
If you're worried about such collisions, you should not be using WORM. I think that the documentation for it is pretty clear.
|
||||
|
||||
If we really wanted to increase the entropy of worm, we could add a random number to the key, or perhaps the file's (original) inode number.
|
||||
"""]]
|
|
@ -612,3 +612,6 @@ BST] XMPPClient: NetMessager stored Pushing "e57" (ReceivePackDone ExitSuccess)
|
|||
|
||||
# End of transcript or log.
|
||||
"""]]
|
||||
|
||||
> Pretty sure this must have been due to Char8 truncation. So,
|
||||
> [[fixed|done]].
|
||||
|
|
|
@ -55,3 +55,14 @@ $ readlink quux
|
|||
Linux 3.15.8
|
||||
|
||||
git-annex 5.20140716
|
||||
|
||||
> This was a bug. I suspect it got broken a while ago and I didn't noticed
|
||||
> since I rarely use WORM and when I do it's almost always adding files
|
||||
> in the current directory. [[fixed|done]] to take the filename only.
|
||||
>
|
||||
> I don't think it's a problem to have the subdirectory path in the
|
||||
> existing WORM keys, other than the problems you note with this meaning
|
||||
> a later add of the same file will generate a different key. So I have not
|
||||
> done anything to try to fix up existing keys. (If this became a problem,
|
||||
> I could add upgrade code to the WORM backend.)
|
||||
> --[[Joey]]
|
||||
|
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawlU0H3uyacCnqWxjSI_chHBlHu8TDIkTt0"
|
||||
nickname="Matt"
|
||||
subject="cannot connect via google apps domain"
|
||||
date="2014-08-14T15:55:07Z"
|
||||
content="""
|
||||
Having the same issue with our domain: zebradog.com SRV records are correctly specified (as defined here: https://support.google.com/a/answer/34143?hl=en)
|
||||
"""]]
|
|
@ -41,3 +41,5 @@ Similar issues and discussions:
|
|||
* [[forum/Cleaning_up_after_aborted_sync_in_direct_mode/]]
|
||||
* [[bugs/failure_to_return_to_indirect_mode_on_usb/]]
|
||||
* [[forum/git-status_typechange_in_direct_mode/]]
|
||||
|
||||
[[!meta title="git annex lock --force deletes only copy of content after interrupted switch to direct mode"]
|
||||
|
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-12T17:26:46Z"
|
||||
content="""
|
||||
The way it's supposed to work is that `git annex direct` does not set the repository into direct mode until it's entirely done moving files around. So, if it is interrupted at any point, you are left with an indirect mode repository, with some unlocked files. Which can be put back to indirect by `git annex add`, or the conversion restarted with `git annex direct`.
|
||||
|
||||
That seems to work in my tests; I can interrupt `git annex direct` and resume with `git annex direct` with a good result; `git annex add` reverts back to indirect mode. Even `git commit -a` reverts back to indirect mode, thanks to the pre-commit hook. I have tested that all these recovery methods work as intended.
|
||||
|
||||
That leaves `git annex lock --force` (it has to be forced) after an interrupted switch to direct mode. I have reproduced that in this situation, that will delete your file's contents (I cannot reproduce them ending up in misctmp, but [[!commit d8be828734704c78f91029263b59eed75174e665]] may have had something to do with that). In a sense, `git annex lock --force` is doing what you told it to -- git-annex lock throws unlocked file contents away, under the assumption that they might contain modified changes. Since normally, `git annex unlock` makes a copy of the file, there is not normally data loss, unless the unlocked files got modified. But that's why it requires the --force; it can result in data loss.
|
||||
|
||||
I a having a hard time thinking of a modification to `git annex lock` that would make sense. The best I can come up with is, if the file's content is not present in the annex, it could switch to what `git annex add` does, and re-add the file content to the annex if it's unchanged. While, I guess, throwing away the content if it is changed. That seems a bit complicated.
|
||||
|
||||
(BTW, if you do still have the files in misctmp, you can `git annex import` their content back into the repository.)
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-15T17:39:14Z"
|
||||
content="""
|
||||
I still cannot see a way that more than one file's content could end up in misctemp, since `git annex direct` moves just one file there at a time, so max of one should be there if interrupted. However, there was really no reason to be moving files through misctemp at all, so `git annex direct` now moves them into place completely atomically.
|
||||
|
||||
Bug report retitled appropriatly for the `git annex lock --force` suprise.
|
||||
"""]]
|
|
@ -42,3 +42,5 @@ foo
|
|||
git-annex version: 5.20140717
|
||||
git version 2.0.1
|
||||
Linux durian 3.14-1-amd64 #1 SMP Debian 3.14.9-1 (2014-06-30) x86_64 GNU/Linux
|
||||
|
||||
[[!tag confirmed git-bug]]
|
||||
|
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-12T18:24:57Z"
|
||||
content="""
|
||||
Congrats on being the guy with newlines in his filenames.. someone had to do it!
|
||||
|
||||
Similarly, `git annex add` on the file will fail with the same error and leave it where it is and not added.
|
||||
|
||||
The problem here is that while git-annex is careful to use git commands with -z, so it gets \"foo\nbar\" with a literal newline from git ls-files, `git cat-file --batch` speaks a line-based protocol. And, it parses filenames like `git ref-parse` does -- and AFAICS, that does not provide a way to input something like \"foo\\nbar\" with an escaped newline. Normally this doesn't matter, since the whole line of input is taken to be a filename, so there's no need to escape anything, but of course it fails with newlines.
|
||||
|
||||
IMHO, the solution to this is to make `git cat-file --batch` have a -z option that enables NUL-delimited input (and probably output). If you want to see this happen, take it to the git developers..
|
||||
|
||||
(Should git annex import put files back if it fails to add them rather than leaving them sitting in the work tree?)
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-15T17:46:15Z"
|
||||
content="""
|
||||
It seems that this has something to do with an auto `git gc` run being trigged somehow during the repair. Puzzlingly, I cannot find any code that would delete the .git/gc.pid file, unless it somehow shows up as a branch ref or something like that.
|
||||
|
||||
Can you run the command with --debug so we can see which particular git command triggered the git gc?
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-12T17:39:09Z"
|
||||
content="""
|
||||
AFAICS, xmpp.l.google.com is the correct XMPP server; it's what the SRV record for googlemail.com says to use.
|
||||
|
||||
Since it fails with an authentication error, I wonder if google's XMPP is rejecting a user@googlemail.com jid and expects the domain to be @gmail.com or something else. Would that be allowed by the XMPP spec? I don't know.
|
||||
|
||||
|
||||
"""]]
|
|
@ -30,4 +30,4 @@ workaround: `cd .git/annex/; mv transfer transfer.old` on the other side.
|
|||
|
||||
-- [[anarcat]]
|
||||
|
||||
[[!taglink moreinfo]]
|
||||
> [[fixed|done]] --[[Joey]]
|
||||
|
|
|
@ -0,0 +1,47 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://id.koumbit.net/anarcat"
|
||||
ip="72.0.72.144"
|
||||
subject="more info"
|
||||
date="2014-08-11T01:55:28Z"
|
||||
content="""
|
||||
here's another occurence of that bug, with --debug this time:
|
||||
|
||||
[[!format txt \"\"\"
|
||||
anarcat@angela:video$ git annex --debug get films/Example/
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"ls-files\",\"--cached\",\"-z\",\"--\",\"films/Example/\"]
|
||||
get films/Example/Example.mkv [2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"show-ref\",\"git-annex\"]
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"show-ref\",\"--hash\",\"refs/heads/git-annex\"]
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"log\",\"refs/heads/git-annex..7357c09b70e87f35fdc253316520975c94308299\",\"-n1\",\"--pretty=%H\"]
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"log\",\"refs/heads/git-annex..30bd8b2d719734a73cbadba28dbc0c99107c201f\",\"-n1\",\"--pretty=%H\"]
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"log\",\"refs/heads/git-annex..bde2aae11f2dcb3fb648ea5e5019fbab56301855\",\"-n1\",\"--pretty=%H\"]
|
||||
[2014-08-10 21:49:23 EDT] chat: git [\"--git-dir=/home/anarcat/video/.git\",\"--work-tree=/home/anarcat/video\",\"cat-file\",\"--batch\"]
|
||||
[2014-08-10 21:49:23 EDT] read: git [\"config\",\"--null\",\"--list\"]
|
||||
(from origin...) [2014-08-10 21:49:23 EDT] read: ssh [\"-O\",\"stop\",\"-S\",\"anarc.at\",\"-o\",\"ControlMaster=auto\",\"-o\",\"ControlPersist=yes\",\"localhost\"]
|
||||
|
||||
[2014-08-10 21:49:23 EDT] read: rsync [\"--progress\",\"--inplace\",\"--perms\",\"-e\",\"'ssh' '-S' '.git/annex/ssh/anarc.at' '-o' 'ControlMaster=auto' '-o' 'ControlPersist=yes' '-T' 'anarc.at' 'git-annex-shell ''sendkey'' ''/srv/video'' ''SHA256E-s815462420--a9a6eb45540fd7f3f2598453ef0fc948bec9abb764e85624d66c0707cbd93b22.mkv'' --uuid 5adbab10-0f7a-467b-b0d8-5d7af2223103 ''--'' ''remoteuuid=ae3d62e6-49be-4340-ba25-c8736a1637c4'' ''direct='' ''associatedfile=films/Example/Example.mkv'' ''--'''\",\"--\",\"dummy:\",\"/home/anarcat/video/.git/annex/tmp/SHA256E-s815462420--a9a6eb45540fd7f3f2598453ef0fc948bec9abb764e85624d66c0707cbd93b22.mkv\"]
|
||||
protocol version mismatch -- is your shell clean?
|
||||
(see the rsync man page for an explanation)
|
||||
rsync error: protocol incompatibility (code 2) at compat.c(174) [Receiver=3.0.9]
|
||||
|
||||
rsync failed -- run git annex again to resume file transfer
|
||||
|
||||
Unable to access these remotes: origin
|
||||
|
||||
Try making some of these repositories available:
|
||||
31912b57-62a5-475c-87a7-582b5492a216 -- WD green 1.5TB backup drive
|
||||
5adbab10-0f7a-467b-b0d8-5d7af2223103 -- main (anarcat@marcos:/srv/video) [origin]
|
||||
failed
|
||||
git-annex: get: 1 failed
|
||||
\"\"\"]]
|
||||
|
||||
running rsync directly doesn't give me much more info, however, running the `-e` command does:
|
||||
|
||||
[[!format txt \"\"\"
|
||||
anarcat@angela:video$ ssh '-S' '.git/annex/ssh/anarc.at' '-o' 'ControlMaster=auto' '-o' 'ControlPersist=yes' '-T' 'anarc.at' 'git-annex-shell ''sendkey'' ''/srv/video'' ''SHA256E-s815462420--a9a6eb45540fd7f3f2598453ef0fc948bec9abb764e85624d66c0707cbd93b22.mkv'' --uuid 5adbab10-0f7a-467b-b0d8-5d7af2223103 ''--'' ''remoteuuid=ae3d62e6-49be-4340-ba25-c8736a1637c4'' ''direct='' ''associatedfile=films/Example/Example.mkv'' ''--'''
|
||||
(transfer already in progress)
|
||||
\"\"\"]]
|
||||
|
||||
so it seems that the remote thinks the transfer is still in progress.
|
||||
|
||||
to reproduce this, switch between a wired and wireless connexion before interrupting the process.
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 3"
|
||||
date="2014-08-15T18:02:12Z"
|
||||
content="""
|
||||
Right .. Normally it makes sense to prevent redundant transfers, but this is not the case when git-annex-shell sendkey is sending a file to a remote. Especially since the rsync protocol does not transport stderr output over the link to display to the user.
|
||||
|
||||
Should be an easy fix.
|
||||
"""]]
|
|
@ -18,3 +18,5 @@ Now when I try to copy a file to the xxx-s3 remote, I get the following error:
|
|||
git-annex: copy: 1 failed
|
||||
|
||||
Any ideas what might be wrong? Is shared cipher broken somehow?
|
||||
|
||||
> [[fixed|done]] --[[Joey]]
|
|
@ -0,0 +1,14 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-12T19:37:56Z"
|
||||
content="""
|
||||
This is not gpg trying to decrypt some file from the S3 remote. It is trying to decrypt the creds that embedcreds=yes caused to be stored in the git repo.
|
||||
|
||||
I was able to reproduce this using your command line, with the S3 env vars set while running initremote, and then unset for the copy, which causes git-annex to try to get the creds from the git repo, and decrypt them.
|
||||
|
||||
However, since encryption=shared, the encryption key is stored in the git repo, so there is no point at all in encrypting the creds, also stored in the git repo with that key. So `initremote` doesn't. The creds are simply stored base-64 encoded.
|
||||
|
||||
I have fixed this. I will now move this thread to bugs so I can close it.
|
||||
"""]]
|
|
@ -1,8 +1,10 @@
|
|||
### Please describe the problem.
|
||||
|
||||
`git annex whereis` says that there are no copies of any of the files annexed in repositories running in direct mode.
|
||||
`git annex whereis` says that there are no copies of any of the files that have been added in repositories running in direct mode.
|
||||
|
||||
This is the error received:
|
||||
In other words, if I add a file from PC1 in direct mode, `whereis` in PC2 will fail. Instead, if I add the same file from PC1 in indirect mode, `whereis` in PC2 will work correctly and will report that the file is present in PC1.
|
||||
|
||||
This is the error received in PC2:
|
||||
|
||||
$ git annex whereis
|
||||
whereis fileA (0 copies) failed
|
||||
|
@ -81,4 +83,4 @@ echo "Why isn't location info available even after sync? (press Enter)"
|
|||
|
||||
### What version of git-annex are you using? On what operating system?
|
||||
|
||||
git-annex version: 5.20140708-g42df533
|
||||
git-annex version: 5.20140716-g8c14ba8
|
||||
|
|
|
@ -0,0 +1,17 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-12T17:29:16Z"
|
||||
content="""
|
||||
I don't seem to reproduce this bug when I run the script provided.
|
||||
|
||||
<pre>
|
||||
whereis fileA (1 copy)
|
||||
c311d5b9-2f59-4153-a0e5-61707edd28ef -- pc1
|
||||
ok
|
||||
whereis fileB (1 copy)
|
||||
c311d5b9-2f59-4153-a0e5-61707edd28ef -- pc1
|
||||
ok
|
||||
</pre>
|
||||
"""]]
|
|
@ -0,0 +1,14 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-12T17:33:25Z"
|
||||
content="""
|
||||
It seems to me that there are only 3 ways that pc2 could not know that pc1 has the file, in decreasing order of probability:
|
||||
|
||||
1. pc1 has not pushed git-annex branch to origin (or pushed it after pc2 pulled)
|
||||
2. pc2 has not fetched git-annex branch from origin
|
||||
3. an actual bug, such as bad info being written to the git-annex branch or the git-annex branch merge failing
|
||||
|
||||
So, if you have 3 repositories that exhibit a problem like this, those are the things to check.
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://svario.it/gioele"
|
||||
nickname="gioele"
|
||||
subject="comment 3"
|
||||
date="2014-08-13T06:36:52Z"
|
||||
content="""
|
||||
This is strange: I can replicate the problem on three different Ubuntu machines (12.04.5 32 and 64 bit, 14.04 64 bit) using that script.
|
||||
|
||||
I attached to the gist [the execution log in direct mode](https://gist.github.com/gioele/dde462df89edfe17c5e3#file-annex-direct-log) (where the bug is shown), the [log in indirect mode](https://gist.github.com/gioele/dde462df89edfe17c5e3#file-annex-indirect-log) (where the bug does not appear), and a [diff between the two](https://gist.github.com/gioele/dde462df89edfe17c5e3#file-log-diff). I hope this helps.
|
||||
"""]]
|
|
@ -0,0 +1,23 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://svario.it/gioele"
|
||||
nickname="gioele"
|
||||
subject="comment 4"
|
||||
date="2014-08-13T06:40:12Z"
|
||||
content="""
|
||||
Talking about the three possible causes for this bug,
|
||||
|
||||
> 1) pc1 has not pushed git-annex branch to origin (or pushed it after pc2 pulled)
|
||||
|
||||
pc1 pushes using `git annex sync -c annex.alwayscommit=true origin`. This should be enough, isn't it?
|
||||
|
||||
> 2) pc2 has not fetched git-annex branch from origin
|
||||
|
||||
The pc2 repository is created with `git clone localhost:/tmp/annex/Docs.git`, so there branches should all be there. I tried adding a `git fetch --all` to the script but it makes no difference. This is the list of branches in pc2:
|
||||
|
||||
* master
|
||||
remotes/origin/HEAD -> origin/master
|
||||
remotes/origin/master
|
||||
remotes/origin/synced/git-annex
|
||||
remotes/origin/synced/master
|
||||
|
||||
"""]]
|
|
@ -23,3 +23,5 @@ Not much in the logs, I see this:
|
|||
[2014-07-25 08:40:14 BST] TransferWatcher: transfer starting: Download UUID "00000000-0000-0000-0000-000000000001" Chase_Adam_at_Startup_School_NY_2014.mp4 Nothing
|
||||
|
||||
"""]]
|
||||
|
||||
> [[fixed|done]] --[[Joey]]
|
||||
|
|
16
doc/devblog/day_214-215__wrapping_up_recent_work.mdwn
Normal file
16
doc/devblog/day_214-215__wrapping_up_recent_work.mdwn
Normal file
|
@ -0,0 +1,16 @@
|
|||
Yesterday, finished converting S3 to use the aws library. Very happy with
|
||||
the result (no memory leaks! connection caching!), but s3-aws is not merged
|
||||
into master yet. Waiting on a new release of the aws library so as to not
|
||||
break Internet Archive S3 support.
|
||||
|
||||
Today, spent a few hours adding more tests to `testremote`. The new tests
|
||||
take a remote, and construct a modified version that is intentionally
|
||||
unavailable. Then they make sure trying to use it fails in appropriate
|
||||
ways. This was a very good thing to test; two bugs were immediately found
|
||||
and fixed.
|
||||
|
||||
And that wraps up several weeks of hacking on the core of git-annex's
|
||||
remotes support, which started with reworking chunking and kind of took
|
||||
on a life of its own. I plan a release of this new stuff in a week. The
|
||||
next week will be spent catching up on 117 messages of backlog that
|
||||
accumulated while I was in deep coding mode.
|
16
doc/devblog/day_216__various_minor_bugs.mdwn
Normal file
16
doc/devblog/day_216__various_minor_bugs.mdwn
Normal file
|
@ -0,0 +1,16 @@
|
|||
Working on getting caught up with backlog. 73 messages remain.
|
||||
|
||||
Several minor bugs were fixed today. All edge cases. The most edge case one
|
||||
of all, I could not fix: git-annex cannot add a file that has a newline
|
||||
in its filename, because `git cat-file --batch`'s interface does not support such
|
||||
filenames.
|
||||
|
||||
Added a page [[documenting how verify the signatures of git-annex releases|install/verifying_downloads]].
|
||||
|
||||
Over the past couple days, all the autobuilders have been updated to new
|
||||
dependencies needed by the recent work. Except for Windows, which needs to
|
||||
be updated to the new Haskell Platform first, so hopefully soon.
|
||||
|
||||
Turns out that upgrading unix-compat means that inode(like) numbers are
|
||||
available even on Windows, which will make git-annex more robust there.
|
||||
Win win. ;)
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="EskildHustvedt"
|
||||
ip="80.202.103.55"
|
||||
subject="comment 1"
|
||||
date="2014-08-14T05:30:46Z"
|
||||
content="""
|
||||
What exactly does «git-annex cannot add a file that has a space in its filename» mean? git-annex (/assistant) actually can't handle tracking any file that has a space in its filename?
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://launchpad.net/~rorymcc"
|
||||
nickname="rorymcc"
|
||||
subject="comment 2"
|
||||
date="2014-08-11T18:37:46Z"
|
||||
content="""
|
||||
Thanks for your reply. I think I might have done a \"git merge git-annex\" at some point (or many times), because I thought that was what you were supposed to do... :( PEBKAC I'll try to fix up my repository. Thanks.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://launchpad.net/~rorymcc"
|
||||
nickname="rorymcc"
|
||||
subject="comment 3"
|
||||
date="2014-08-11T18:41:05Z"
|
||||
content="""
|
||||
Would just standard \"git rm ./000/\" etc. in master be OK? Instead of hunting down and reverting all the commits?
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 4"
|
||||
date="2014-08-12T17:50:15Z"
|
||||
content="""
|
||||
Sure, it's fine to delete the files. The same info will be committed to git either way.
|
||||
"""]]
|
|
@ -0,0 +1,11 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 6"
|
||||
date="2014-08-12T17:48:34Z"
|
||||
content="""
|
||||
There are a couple of problems with using the haskell code as a library that would need to be addressed:
|
||||
|
||||
* I can't guarantee much about providing every interface in a compatible way going forward. It might make sense to pick out some key interfaces and make those stable, but I don't know what the right choices would be.
|
||||
* If all of git-annex is a library, `cabal build` will build everything a second time. This is annoying when trying to do a fast edit/build/test cycle, but I don't know a way to make cabal not do it. AFAIK cabal build flags cannot be used to disable building a library.
|
||||
"""]]
|
14
doc/forum/__34__Lost__34___data__63___Maybe_a_bug__63__.mdwn
Normal file
14
doc/forum/__34__Lost__34___data__63___Maybe_a_bug__63__.mdwn
Normal file
|
@ -0,0 +1,14 @@
|
|||
Hey,
|
||||
|
||||
I lost some symlinks to my data and I do not know how to recover them. I was in view mode with some tag folders already there. I added _new_ files from outside annex into some folder and 'git annex add' those files.
|
||||
|
||||
What I expected: Git-Annex should add those files to the annex, move the symlinks to the root of the annex (because there is no other way to tell where to put them) and tag them with the specific tag. That is the way I would like to work, first tag, then organize in folder structure.
|
||||
|
||||
Now that seems not to be a scenario which has been respected? Because I don't see my files... anywhere. Not in master branch nor in the view branch (I already did 'git annex vpop'). If that is not supported and never will be git-annex should not accept data from the outside world if it is currently in view mode.
|
||||
|
||||
Now, how do I get my symlinks back? I guess the content is still there, but the links are missing and I don't find any reference or history log to revert that. 'git annex unused' does not show them either.
|
||||
|
||||
I hope somebody can help me :)
|
||||
|
||||
Cheers,
|
||||
Stephan
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="sts"
|
||||
ip="134.147.240.107"
|
||||
subject="comment 1"
|
||||
date="2014-08-11T11:39:44Z"
|
||||
content="""
|
||||
OK, I could find the commit where I have added the data. I can 'git show' the commit and see the keys. I can also checkout the commit and I can see my data. Now I tried to create symlinks based on the keys I found in the commit, so whats the right way?
|
||||
|
||||
git annex examinekey SHA256E-s1390161393--1dcba6e914ad6a9133d374e3c55fbf9a58f036e64298262692c7f8e7cdb65852.mkv
|
||||
SHA256E-s1390161393--1dcba6e914ad6a9133d374e3c55fbf9a58f036e64298262692c7f8e7cdb65852.mkv
|
||||
|
||||
git annex fromkey SHA256E-s1390161393--1dcba6e914ad6a9133d374e3c55fbf9a58f036e64298262692c7f8e7cdb65852.mkv e01.mkv
|
||||
git-annex: key (SHA256E-s1390161393--1dcba6e914ad6a9133d374e3c55fbf9a58f036e64298262692c7f8e7cdb65852.mkv) is not present in backend
|
||||
|
||||
I am not sure what to do now :-/.
|
||||
"""]]
|
|
@ -0,0 +1,12 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-12T17:57:26Z"
|
||||
content="""
|
||||
views are a somewhat new feature that still needs work, and you will find this question of what to do about a file added while in a view in the todo list [[here|design/metadata]].
|
||||
|
||||
Since views are just git branches, you can check out the view branch where you added the file, and it'll still be there. You could merge the branch (probably not a good idea since the filenames are moved around in the view).
|
||||
|
||||
Using `fromkey` will also work, if you have the right key and the content is present in the annex -- I just tested it.
|
||||
"""]]
|
3
doc/forum/armhf_binary.mdwn
Normal file
3
doc/forum/armhf_binary.mdwn
Normal file
|
@ -0,0 +1,3 @@
|
|||
Does a armhf binary tarball exist anywhere? I'm running Ubuntu trusty on a armhf platform (beagleboard), and the repository package is out of date. I might try to get the standalone armel binary working using multiarch, but that seems only slightly less painful than compiling from scratch.
|
||||
|
||||
Or am I better off changing to a debian boot image, and be done with it?
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-15T15:58:02Z"
|
||||
content="""
|
||||
The standalone armel build should work fine on armhf, assuming that the kernel supports EABI, which I'm pretty sure it does (or multiarch armel would not work).
|
||||
"""]]
|
18
doc/forum/gcrypt_os_x_app_vs_brew.mdwn
Normal file
18
doc/forum/gcrypt_os_x_app_vs_brew.mdwn
Normal file
|
@ -0,0 +1,18 @@
|
|||
Gcrypt remotes work when using the git-annex command bundled in the git-annex.app. But gcrypt doesn't work when git-annex is installed via home-brew (brew install git-annex).
|
||||
|
||||
The initial push will work, any subsequent commands (push/pull) will fail with:
|
||||
|
||||
gpg: anonymous recipient; trying secret key...
|
||||
gpg: anonymous recipient; trying secret key...
|
||||
gpg: anonymous recipient; trying secret key...
|
||||
gpg: anonymous recipient; trying secret key...
|
||||
gpg: decryption failed: No secret key
|
||||
gcrypt: Failed to decrypt manifest!
|
||||
|
||||
In both cases (app/brew) it tries the same keys. The app version will use its own version of gpg, which will trigger password prompts. With the brew version gpgtools is used, so I won't get any prompts. (Keychain)
|
||||
|
||||
I tried "echo i | gpg -e -R XX -R XX | gpg -d" with the same recipients as the repo. It works well.
|
||||
|
||||
Has anybody hints or ideas what to try next?
|
||||
|
||||
Best, Jean-Louis
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="Ganwell"
|
||||
ip="178.174.3.221"
|
||||
subject="Problem solved"
|
||||
date="2014-08-14T23:53:05Z"
|
||||
content="""
|
||||
It turns out gpgtools will save to wrong passphrase to the keychain without complaining. Thats why standard gpg worked and gpgtools didn't: There was a typo in the passphrase in the keychain.
|
||||
"""]]
|
|
@ -0,0 +1,8 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 2"
|
||||
date="2014-08-15T16:04:08Z"
|
||||
content="""
|
||||
Note that you can avoid the trying of multiple keys by doing `git config gcrypt.publish-participants true` -- this is done by default by the assistant when setting up new gcrypt remotes. It needs my branch of git-remote-gcrypt, which is included in the osx app, I don't know which one is being used in brew.
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 1"
|
||||
date="2014-08-12T19:49:35Z"
|
||||
content="""
|
||||
If I wanted to share files with someone, I'd set them up with a direct mode repository and link it to my (probably indirect mode) repository.
|
||||
|
||||
The question then becomes, how can this person decide which files to get if they don't want to or cannot get everything. I think that [[tips/File_manager_integration]] is a pretty good answer, although it does involve adding extensions to file managers. At least it involves adding something, rather than convincing a suprisingly large number of people that their ideas about symlinks are wrong. There are other possible answers, like building a file selection UI into the webapp..
|
||||
"""]]
|
|
@ -0,0 +1,16 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://id.koumbit.net/anarcat"
|
||||
ip="70.83.139.100"
|
||||
subject="comment 2"
|
||||
date="2014-08-12T19:56:58Z"
|
||||
content="""
|
||||
the problem with this is that you end up having two copies of the same files (the direct and indirect repositories). also, the switch to direct mode exploded (because i screwed up, granted)....
|
||||
|
||||
i have been thinking more and more than the webapp needs to have some sort of file manager as well, but that seems like a huge undertaking...
|
||||
|
||||
a better file manager integration could certainly allow to improve this experience. for me the requirements would be:
|
||||
|
||||
* \"clone this repo to\" - make a copy of this git annex repo to the specified target
|
||||
* \"annex-copy those files to\" - the above + a file-transfer-like dialog that would track the total file transfer (as opposed to \"begin/end\" of single files, see also [[todo/do_not_bug_me_about_intermediate_files/]])
|
||||
* probably some more stuff
|
||||
"""]]
|
|
@ -3,7 +3,7 @@
|
|||
[[!table format=dsv header=yes data="""
|
||||
detailed instructions | quick install
|
||||
[[OSX]] | [download git-annex.app](http://downloads.kitenet.net/git-annex/OSX/current/)
|
||||
[[Homebrew]] | `brew install git-annex`
|
||||
[[OSX/Homebrew]] | `brew install git-annex`
|
||||
[[Android]] | [download git-annex.apk](http://downloads.kitenet.net/git-annex/android/current/) **beta**
|
||||
[[Linux|linux_standalone]] | [download prebuilt linux tarball](http://downloads.kitenet.net/git-annex/linux/current/)
|
||||
[[Debian]] | `apt-get install git-annex`
|
||||
|
@ -16,14 +16,11 @@ detailed instructions | quick install
|
|||
[[ScientificLinux5]] |
|
||||
[[openSUSE]] |
|
||||
[[Docker]] |
|
||||
[[Windows]] | [download installer](http://downloads.kitenet.net/git-annex/windows/current/) **alpha**
|
||||
[[Windows]] | [download installer](http://downloads.kitenet.net/git-annex/windows/current/) **beta**
|
||||
"""]]
|
||||
|
||||
The downloaded package's integrity can be verified by the public PGP key. On Linux,
|
||||
|
||||
$ wget https://downloads.kitenet.net/git-annex/gpg-pubkey.asc
|
||||
$ gpg --import gpg-pubey.asc
|
||||
$ gpg --verify git-annex-standalone-*.tar.gz.sig
|
||||
All the downloads above use https for security. For added security, see
|
||||
[[verifying_downloads]].
|
||||
|
||||
## Using cabal
|
||||
|
||||
|
|
|
@ -5,9 +5,9 @@ prebuilt tarball of the most recent release.
|
|||
This tarball should work on most Linux systems. It has basically no
|
||||
dependencies and is self-contained.
|
||||
|
||||
* i386: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-i386.tar.gz)
|
||||
* amd64: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-amd64.tar.gz)
|
||||
* armel: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-armel.tar.gz)
|
||||
* x86-32: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-i386.tar.gz)
|
||||
* x86-64: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-amd64.tar.gz)
|
||||
* arm: [download tarball](https://downloads.kitenet.net/git-annex/linux/current/git-annex-standalone-armel.tar.gz)
|
||||
|
||||
To use, just unpack the tarball, `cd git-annex.linux` and run `./runshell`
|
||||
-- this sets up an environment where you can use `git annex`, as well
|
||||
|
@ -18,7 +18,7 @@ Alternatively, you can unpack the tarball, and add the directory to your
|
|||
PATH. This lets you use `git annex`, without overriding your system's
|
||||
own versions of git, etc.
|
||||
|
||||
The armel version can be installed on NAS devices and other embedded ARM
|
||||
The arm version can be installed on NAS devices and other embedded ARM
|
||||
linux systems.
|
||||
|
||||
* [[tips/Synology_NAS_and_git_annex]]
|
||||
|
@ -29,6 +29,6 @@ linux systems.
|
|||
A daily build is also available, thanks to Mesar Hameed and the University
|
||||
of Bath CS department.
|
||||
|
||||
* i386: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/i386/git-annex-standalone-i386.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/i386/))
|
||||
* amd64: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/amd64/git-annex-standalone-amd64.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/amd64/))
|
||||
* armel: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/armel/git-annex-standalone-armel.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/armel/))
|
||||
* x86-32: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/i386/git-annex-standalone-i386.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/i386/))
|
||||
* x86-64: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/amd64/git-annex-standalone-amd64.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/amd64/))
|
||||
* arm: [download tarball](https://downloads.kitenet.net/git-annex/autobuild/armel/git-annex-standalone-armel.tar.gz) ([build logs](https://downloads.kitenet.net/git-annex/autobuild/armel/))
|
||||
|
|
|
@ -31,25 +31,9 @@ git-annex is now [[available in Homebrew|Homebrew]]!
|
|||
|
||||
## using MacPorts
|
||||
|
||||
Install the Haskell Platform from [[http://hackage.haskell.org/platform/mac.html]].
|
||||
The version provided by Macports is too old to work with current versions of git-annex.
|
||||
Then execute
|
||||
git-annex is not available in MacPorts, but can be built from source using
|
||||
MacPorts tools. See [[MacPorts]].
|
||||
|
||||
<pre>
|
||||
sudo port install git-core ossp-uuid md5sha1sum coreutils gnutls libxml2 libgsasl pkgconfig
|
||||
sudo cabal update
|
||||
PATH=$HOME/bin:$PATH
|
||||
cabal install c2hs git-annex --bindir=$HOME/bin
|
||||
</pre>
|
||||
## building it yourself
|
||||
|
||||
## PATH setup
|
||||
|
||||
Do not forget to add to your PATH variable your ~/bin folder. In your .bashrc, for example:
|
||||
<pre>
|
||||
PATH=$HOME/bin:$PATH
|
||||
</pre>
|
||||
|
||||
See also:
|
||||
|
||||
* [[forum/OSX__39__s_haskell-platform_statically_links_things]]
|
||||
* [[forum/OSX__39__s_default_sshd_behaviour_has_limited_paths_set]]
|
||||
See [[porting]].
|
||||
|
|
27
doc/install/OSX/MacPorts.mdwn
Normal file
27
doc/install/OSX/MacPorts.mdwn
Normal file
|
@ -0,0 +1,27 @@
|
|||
This is not a recommended way to install git-annex. Use [[HomeBrew]] or the
|
||||
prebuilt app bundle instead.
|
||||
|
||||
But if you really want to use MacPorts:
|
||||
|
||||
Install the Haskell Platform from [[http://hackage.haskell.org/platform/mac.html]].
|
||||
The version provided by Macports is too old to work with current versions of git-annex.
|
||||
Then execute
|
||||
|
||||
<pre>
|
||||
sudo port install git-core ossp-uuid md5sha1sum coreutils gnutls libxml2 libgsasl pkgconfig
|
||||
sudo cabal update
|
||||
PATH=$HOME/bin:$PATH
|
||||
cabal install c2hs git-annex --bindir=$HOME/bin
|
||||
</pre>
|
||||
|
||||
## PATH setup
|
||||
|
||||
Do not forget to add to your PATH variable your ~/bin folder. In your .bashrc, for example:
|
||||
<pre>
|
||||
PATH=$HOME/bin:$PATH
|
||||
</pre>
|
||||
|
||||
See also:
|
||||
|
||||
* [[forum/OSX__39__s_haskell-platform_statically_links_things]]
|
||||
* [[forum/OSX__39__s_default_sshd_behaviour_has_limited_paths_set]]
|
|
@ -1,8 +0,0 @@
|
|||
[[!comment format=mdwn
|
||||
username="https://www.google.com/accounts/o8/id?id=AItOawkSq2FDpK2n66QRUxtqqdbyDuwgbQmUWus"
|
||||
nickname="Jimmy"
|
||||
subject="comment 4"
|
||||
date="2012-12-10T17:00:43Z"
|
||||
content="""
|
||||
For those that care, I've updated my autobuilder to the latest version of haskell-platform 2012.4.0.0 and it appears to be building correctly.
|
||||
"""]]
|
|
@ -0,0 +1,10 @@
|
|||
[[!comment format=mdwn
|
||||
username="http://joeyh.name/"
|
||||
ip="209.250.56.7"
|
||||
subject="comment 8"
|
||||
date="2014-08-15T19:26:07Z"
|
||||
content="""
|
||||
@David, the bundle contains the man page since a while.
|
||||
|
||||
@Michael, the best way to get a git-annex that does not use those bundled programs is probably to instead install it using homebrew.
|
||||
"""]]
|
6
doc/install/OSX/porting.mdwn
Normal file
6
doc/install/OSX/porting.mdwn
Normal file
|
@ -0,0 +1,6 @@
|
|||
If you cannot get a OSX build of git-annex suitable for your computer,
|
||||
from eg [[HomeBrew]] or the regular [[OSX]] prebuilt app, you
|
||||
can try building git-annex from source on OSX, using haskell's cabal package
|
||||
manager.
|
||||
|
||||
For general instructions for using cabal, see [[this page|/install/cabal]].
|
Some files were not shown because too many files have changed in this diff Show more
Loading…
Reference in a new issue