Merge branch 'master' into adjustedbranch

This commit is contained in:
Joey Hess 2016-03-29 11:07:40 -04:00
commit 70e8d6860e
Failed to extract signature
858 changed files with 1137 additions and 162 deletions

View file

@ -42,6 +42,7 @@ import qualified Git
import qualified Git.Config import qualified Git.Config
import Annex.Fixup import Annex.Fixup
import Git.CatFile import Git.CatFile
import Git.HashObject
import Git.CheckAttr import Git.CheckAttr
import Git.CheckIgnore import Git.CheckIgnore
import qualified Git.Hook import qualified Git.Hook
@ -106,6 +107,7 @@ data AnnexState = AnnexState
, branchstate :: BranchState , branchstate :: BranchState
, repoqueue :: Maybe Git.Queue.Queue , repoqueue :: Maybe Git.Queue.Queue
, catfilehandles :: M.Map FilePath CatFileHandle , catfilehandles :: M.Map FilePath CatFileHandle
, hashobjecthandle :: Maybe HashObjectHandle
, checkattrhandle :: Maybe CheckAttrHandle , checkattrhandle :: Maybe CheckAttrHandle
, checkignorehandle :: Maybe (Maybe CheckIgnoreHandle) , checkignorehandle :: Maybe (Maybe CheckIgnoreHandle)
, forcebackend :: Maybe String , forcebackend :: Maybe String
@ -151,6 +153,7 @@ newState c r = AnnexState
, branchstate = startBranchState , branchstate = startBranchState
, repoqueue = Nothing , repoqueue = Nothing
, catfilehandles = M.empty , catfilehandles = M.empty
, hashobjecthandle = Nothing
, checkattrhandle = Nothing , checkattrhandle = Nothing
, checkignorehandle = Nothing , checkignorehandle = Nothing
, forcebackend = Nothing , forcebackend = Nothing

View file

@ -45,7 +45,8 @@ import qualified Git.Branch
import qualified Git.UnionMerge import qualified Git.UnionMerge
import qualified Git.UpdateIndex import qualified Git.UpdateIndex
import Git.LsTree (lsTreeParams) import Git.LsTree (lsTreeParams)
import Git.HashObject import qualified Git.HashObject
import Annex.HashObject
import Git.Types import Git.Types
import Git.FilePath import Git.FilePath
import Annex.CatFile import Annex.CatFile
@ -342,8 +343,9 @@ genIndex g = Git.UpdateIndex.streamUpdateIndex g
mergeIndex :: JournalLocked -> [Git.Ref] -> Annex () mergeIndex :: JournalLocked -> [Git.Ref] -> Annex ()
mergeIndex jl branches = do mergeIndex jl branches = do
prepareModifyIndex jl prepareModifyIndex jl
h <- catFileHandle hashhandle <- hashObjectHandle
inRepo $ \g -> Git.UnionMerge.mergeIndex h g branches ch <- catFileHandle
inRepo $ \g -> Git.UnionMerge.mergeIndex hashhandle ch g branches
{- Removes any stale git lock file, to avoid git falling over when {- Removes any stale git lock file, to avoid git falling over when
- updating the index. - updating the index.
@ -423,11 +425,10 @@ stageJournal jl = withIndex $ do
let dir = gitAnnexJournalDir g let dir = gitAnnexJournalDir g
(jlogf, jlogh) <- openjlog (jlogf, jlogh) <- openjlog
liftIO $ fileEncoding jlogh liftIO $ fileEncoding jlogh
withJournalHandle $ \jh -> do h <- hashObjectHandle
h <- hashObjectStart g withJournalHandle $ \jh ->
Git.UpdateIndex.streamUpdateIndex g Git.UpdateIndex.streamUpdateIndex g
[genstream dir h jh jlogh] [genstream dir h jh jlogh]
hashObjectStop h
return $ cleanup dir jlogh jlogf return $ cleanup dir jlogh jlogf
where where
genstream dir h jh jlogh streamer = do genstream dir h jh jlogh streamer = do
@ -437,7 +438,7 @@ stageJournal jl = withIndex $ do
Just file -> do Just file -> do
unless (dirCruft file) $ do unless (dirCruft file) $ do
let path = dir </> file let path = dir </> file
sha <- hashFile h path sha <- Git.HashObject.hashFile h path
hPutStrLn jlogh file hPutStrLn jlogh file
streamer $ Git.UpdateIndex.updateIndexLine streamer $ Git.UpdateIndex.updateIndexLine
sha FileBlob (asTopFilePath $ fileJournal file) sha FileBlob (asTopFilePath $ fileJournal file)
@ -549,13 +550,11 @@ performTransitionsLocked jl ts neednewlocalbranch transitionedrefs = do
run changers = do run changers = do
trustmap <- calcTrustMap <$> getRaw trustLog trustmap <- calcTrustMap <$> getRaw trustLog
fs <- branchFiles fs <- branchFiles
hasher <- inRepo hashObjectStart
forM_ fs $ \f -> do forM_ fs $ \f -> do
content <- getRaw f content <- getRaw f
apply changers hasher f content trustmap apply changers f content trustmap
liftIO $ hashObjectStop hasher apply [] _ _ _ = return ()
apply [] _ _ _ _ = return () apply (changer:rest) file content trustmap =
apply (changer:rest) hasher file content trustmap =
case changer file content trustmap of case changer file content trustmap of
RemoveFile -> do RemoveFile -> do
Annex.Queue.addUpdateIndex Annex.Queue.addUpdateIndex
@ -564,12 +563,12 @@ performTransitionsLocked jl ts neednewlocalbranch transitionedrefs = do
-- transitions on it. -- transitions on it.
return () return ()
ChangeFile content' -> do ChangeFile content' -> do
sha <- inRepo $ hashObject BlobObject content' sha <- hashBlob content'
Annex.Queue.addUpdateIndex $ Git.UpdateIndex.pureStreamer $ Annex.Queue.addUpdateIndex $ Git.UpdateIndex.pureStreamer $
Git.UpdateIndex.updateIndexLine sha FileBlob (asTopFilePath file) Git.UpdateIndex.updateIndexLine sha FileBlob (asTopFilePath file)
apply rest hasher file content' trustmap apply rest file content' trustmap
PreserveFile -> PreserveFile ->
apply rest hasher file content trustmap apply rest file content trustmap
checkBranchDifferences :: Git.Ref -> Annex () checkBranchDifferences :: Git.Ref -> Annex ()
checkBranchDifferences ref = do checkBranchDifferences ref = do

View file

@ -11,6 +11,7 @@ import Annex.Common
import Annex import Annex
import Annex.CatFile import Annex.CatFile
import Annex.CheckAttr import Annex.CheckAttr
import Annex.HashObject
import Annex.CheckIgnore import Annex.CheckIgnore
import qualified Annex.Queue import qualified Annex.Queue
@ -64,4 +65,5 @@ mergeState st = do
closehandles = do closehandles = do
catFileStop catFileStop
checkAttrStop checkAttrStop
hashObjectStop
checkIgnoreStop checkIgnoreStop

47
Annex/HashObject.hs Normal file
View file

@ -0,0 +1,47 @@
{- git hash-object interface, with handle automatically stored in the Annex monad
-
- Copyright 2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Annex.HashObject (
hashFile,
hashBlob,
hashObjectHandle,
hashObjectStop,
) where
import Annex.Common
import qualified Git.HashObject
import qualified Annex
import Git.Types
hashObjectHandle :: Annex Git.HashObject.HashObjectHandle
hashObjectHandle = maybe startup return =<< Annex.getState Annex.hashobjecthandle
where
startup = do
h <- inRepo $ Git.HashObject.hashObjectStart
Annex.changeState $ \s -> s { Annex.hashobjecthandle = Just h }
return h
hashObjectStop :: Annex ()
hashObjectStop = maybe noop stop =<< Annex.getState Annex.hashobjecthandle
where
stop h = do
liftIO $ Git.HashObject.hashObjectStop h
Annex.changeState $ \s -> s { Annex.hashobjecthandle = Nothing }
return ()
hashFile :: FilePath -> Annex Sha
hashFile f = do
h <- hashObjectHandle
liftIO $ Git.HashObject.hashFile h f
{- Note that the content will be written to a temp file.
- So it may be faster to use Git.HashObject.hashObject for large
- blob contents. -}
hashBlob :: String -> Annex Sha
hashBlob content = do
h <- hashObjectHandle
liftIO $ Git.HashObject.hashBlob h content

View file

@ -18,11 +18,11 @@ module Annex.Link where
import Annex.Common import Annex.Common
import qualified Annex import qualified Annex
import qualified Git.HashObject
import qualified Git.UpdateIndex import qualified Git.UpdateIndex
import qualified Annex.Queue import qualified Annex.Queue
import Git.Types import Git.Types
import Git.FilePath import Git.FilePath
import Annex.HashObject
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
import Data.Int import Data.Int
@ -105,12 +105,7 @@ addAnnexLink linktarget file = do
{- Injects a symlink target into git, returning its Sha. -} {- Injects a symlink target into git, returning its Sha. -}
hashSymlink :: LinkTarget -> Annex Sha hashSymlink :: LinkTarget -> Annex Sha
hashSymlink linktarget = inRepo $ Git.HashObject.hashObject BlobObject $ hashSymlink linktarget = hashBlob (toInternalGitPath linktarget)
toInternalGitPath linktarget
hashSymlink' :: Git.HashObject.HashObjectHandle -> LinkTarget -> Annex Sha
hashSymlink' h linktarget = liftIO $ Git.HashObject.hashBlob h $
toInternalGitPath linktarget
{- Stages a symlink to an annexed object, using a Sha of its target. -} {- Stages a symlink to an annexed object, using a Sha of its target. -}
stageSymlink :: FilePath -> Sha -> Annex () stageSymlink :: FilePath -> Sha -> Annex ()
@ -120,8 +115,7 @@ stageSymlink file sha =
{- Injects a pointer file content into git, returning its Sha. -} {- Injects a pointer file content into git, returning its Sha. -}
hashPointerFile :: Key -> Annex Sha hashPointerFile :: Key -> Annex Sha
hashPointerFile key = inRepo $ Git.HashObject.hashObject BlobObject $ hashPointerFile key = hashBlob (formatPointer key)
formatPointer key
hashPointerFile' :: Git.HashObject.HashObjectHandle -> Key -> Annex Sha hashPointerFile' :: Git.HashObject.HashObjectHandle -> Key -> Annex Sha
hashPointerFile' h = liftIO . Git.HashObject.hashBlob h . formatPointer hashPointerFile' h = liftIO . Git.HashObject.hashBlob h . formatPointer
@ -162,7 +156,9 @@ formatPointer :: Key -> String
formatPointer k = formatPointer k =
toInternalGitPath (pathSeparator:objectDir </> keyFile k) ++ "\n" toInternalGitPath (pathSeparator:objectDir </> keyFile k) ++ "\n"
{- Checks if a file is a pointer to a key. -} {- Checks if a worktree file is a pointer to a key.
-
- Unlocked files whose content is present are not detected by this. -}
isPointerFile :: FilePath -> IO (Maybe Key) isPointerFile :: FilePath -> IO (Maybe Key)
isPointerFile f = catchDefaultIO Nothing $ do isPointerFile f = catchDefaultIO Nothing $ do
b <- L.take maxPointerSz <$> L.readFile f b <- L.take maxPointerSz <$> L.readFile f

View file

@ -19,7 +19,7 @@ import qualified Git.LsFiles
import qualified Git.Ref import qualified Git.Ref
import Git.UpdateIndex import Git.UpdateIndex
import Git.Sha import Git.Sha
import Git.HashObject import Annex.HashObject
import Git.Types import Git.Types
import Git.FilePath import Git.FilePath
import Annex.WorkTree import Annex.WorkTree
@ -340,38 +340,36 @@ applyView' mkviewedfile getfilemetadata view = do
(l, clean) <- inRepo $ Git.LsFiles.inRepo [top] (l, clean) <- inRepo $ Git.LsFiles.inRepo [top]
liftIO . nukeFile =<< fromRepo gitAnnexViewIndex liftIO . nukeFile =<< fromRepo gitAnnexViewIndex
uh <- withViewIndex $ inRepo Git.UpdateIndex.startUpdateIndex uh <- withViewIndex $ inRepo Git.UpdateIndex.startUpdateIndex
hasher <- inRepo hashObjectStart
forM_ l $ \f -> do forM_ l $ \f -> do
relf <- getTopFilePath <$> inRepo (toTopFilePath f) relf <- getTopFilePath <$> inRepo (toTopFilePath f)
go uh hasher relf =<< lookupFile f go uh relf =<< lookupFile f
liftIO $ do liftIO $ do
hashObjectStop hasher
void $ stopUpdateIndex uh void $ stopUpdateIndex uh
void clean void clean
genViewBranch view genViewBranch view
where where
genviewedfiles = viewedFiles view mkviewedfile -- enables memoization genviewedfiles = viewedFiles view mkviewedfile -- enables memoization
go uh hasher f (Just k) = do go uh f (Just k) = do
metadata <- getCurrentMetaData k metadata <- getCurrentMetaData k
let metadata' = getfilemetadata f `unionMetaData` metadata let metadata' = getfilemetadata f `unionMetaData` metadata
forM_ (genviewedfiles f metadata') $ \fv -> do forM_ (genviewedfiles f metadata') $ \fv -> do
f' <- fromRepo $ fromTopFilePath $ asTopFilePath fv f' <- fromRepo $ fromTopFilePath $ asTopFilePath fv
stagesymlink uh hasher f' =<< calcRepo (gitAnnexLink f' k) stagesymlink uh f' =<< calcRepo (gitAnnexLink f' k)
go uh hasher f Nothing go uh f Nothing
| "." `isPrefixOf` f = do | "." `isPrefixOf` f = do
s <- liftIO $ getSymbolicLinkStatus f s <- liftIO $ getSymbolicLinkStatus f
if isSymbolicLink s if isSymbolicLink s
then stagesymlink uh hasher f =<< liftIO (readSymbolicLink f) then stagesymlink uh f =<< liftIO (readSymbolicLink f)
else do else do
sha <- liftIO $ Git.HashObject.hashFile hasher f sha <- hashFile f
let blobtype = if isExecutable (fileMode s) let blobtype = if isExecutable (fileMode s)
then ExecutableBlob then ExecutableBlob
else FileBlob else FileBlob
liftIO . Git.UpdateIndex.streamUpdateIndex' uh liftIO . Git.UpdateIndex.streamUpdateIndex' uh
=<< inRepo (Git.UpdateIndex.stageFile sha blobtype f) =<< inRepo (Git.UpdateIndex.stageFile sha blobtype f)
| otherwise = noop | otherwise = noop
stagesymlink uh hasher f linktarget = do stagesymlink uh f linktarget = do
sha <- hashSymlink' hasher linktarget sha <- hashSymlink linktarget
liftIO . Git.UpdateIndex.streamUpdateIndex' uh liftIO . Git.UpdateIndex.streamUpdateIndex' uh
=<< inRepo (Git.UpdateIndex.stageSymlink f sha) =<< inRepo (Git.UpdateIndex.stageSymlink f sha)

View file

@ -27,6 +27,7 @@ import qualified Remote
import qualified Annex.Branch import qualified Annex.Branch
import Annex.Link import Annex.Link
import Annex.CatFile import Annex.CatFile
import Annex.WorkTree
import Types.RefSpec import Types.RefSpec
import Git.Types import Git.Types
import Git.Sha import Git.Sha
@ -215,10 +216,7 @@ withKeysReferenced' mdir initial a = do
Just dir -> inRepo $ LsFiles.inRepo [dir] Just dir -> inRepo $ LsFiles.inRepo [dir]
go v [] = return v go v [] = return v
go v (f:fs) = do go v (f:fs) = do
mk <- getM id mk <- lookupFile f
[ isAnnexLink f
, liftIO (isPointerFile f)
]
case mk of case mk of
Nothing -> go v fs Nothing -> go v fs
Just k -> do Just k -> do

View file

@ -30,12 +30,14 @@ import Git.FilePath
-} -}
merge :: Ref -> Ref -> Repo -> IO () merge :: Ref -> Ref -> Repo -> IO ()
merge x y repo = do merge x y repo = do
h <- catFileStart repo hashhandle <- hashObjectStart repo
ch <- catFileStart repo
streamUpdateIndex repo streamUpdateIndex repo
[ lsTree x repo [ lsTree x repo
, mergeTrees x y h repo , mergeTrees x y hashhandle ch repo
] ]
catFileStop h catFileStop ch
hashObjectStop hashhandle
{- Merges a list of branches into the index. Previously staged changes in {- Merges a list of branches into the index. Previously staged changes in
- the index are preserved (and participate in the merge). - the index are preserved (and participate in the merge).
@ -45,17 +47,18 @@ merge x y repo = do
- harder to calculate a single union merge involving all the refs, as well - harder to calculate a single union merge involving all the refs, as well
- as the index. - as the index.
-} -}
mergeIndex :: CatFileHandle -> Repo -> [Ref] -> IO () mergeIndex :: HashObjectHandle -> CatFileHandle -> Repo -> [Ref] -> IO ()
mergeIndex h repo bs = forM_ bs $ \b -> mergeIndex hashhandle ch repo bs = forM_ bs $ \b ->
streamUpdateIndex repo [mergeTreeIndex b h repo] streamUpdateIndex repo [mergeTreeIndex b hashhandle ch repo]
{- For merging two trees. -} {- For merging two trees. -}
mergeTrees :: Ref -> Ref -> CatFileHandle -> Repo -> Streamer mergeTrees :: Ref -> Ref -> HashObjectHandle -> CatFileHandle -> Repo -> Streamer
mergeTrees (Ref x) (Ref y) h = doMerge h $ "diff-tree":diffOpts ++ [x, y, "--"] mergeTrees (Ref x) (Ref y) hashhandle ch = doMerge hashhandle ch
("diff-tree":diffOpts ++ [x, y, "--"])
{- For merging a single tree into the index. -} {- For merging a single tree into the index. -}
mergeTreeIndex :: Ref -> CatFileHandle -> Repo -> Streamer mergeTreeIndex :: Ref -> HashObjectHandle -> CatFileHandle -> Repo -> Streamer
mergeTreeIndex (Ref r) h = doMerge h $ mergeTreeIndex (Ref r) hashhandle ch = doMerge hashhandle ch $
"diff-index" : diffOpts ++ ["--cached", r, "--"] "diff-index" : diffOpts ++ ["--cached", r, "--"]
diffOpts :: [String] diffOpts :: [String]
@ -63,26 +66,26 @@ diffOpts = ["--raw", "-z", "-r", "--no-renames", "-l0"]
{- Streams update-index changes to perform a merge, {- Streams update-index changes to perform a merge,
- using git to get a raw diff. -} - using git to get a raw diff. -}
doMerge :: CatFileHandle -> [String] -> Repo -> Streamer doMerge :: HashObjectHandle -> CatFileHandle -> [String] -> Repo -> Streamer
doMerge ch differ repo streamer = do doMerge hashhandle ch differ repo streamer = do
(diff, cleanup) <- pipeNullSplit (map Param differ) repo (diff, cleanup) <- pipeNullSplit (map Param differ) repo
go diff go diff
void $ cleanup void $ cleanup
where where
go [] = noop go [] = noop
go (info:file:rest) = mergeFile info file ch repo >>= go (info:file:rest) = mergeFile info file hashhandle ch >>=
maybe (go rest) (\l -> streamer l >> go rest) maybe (go rest) (\l -> streamer l >> go rest)
go (_:[]) = error $ "parse error " ++ show differ go (_:[]) = error $ "parse error " ++ show differ
{- Given an info line from a git raw diff, and the filename, generates {- Given an info line from a git raw diff, and the filename, generates
- a line suitable for update-index that union merges the two sides of the - a line suitable for update-index that union merges the two sides of the
- diff. -} - diff. -}
mergeFile :: String -> FilePath -> CatFileHandle -> Repo -> IO (Maybe String) mergeFile :: String -> FilePath -> HashObjectHandle -> CatFileHandle -> IO (Maybe String)
mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of mergeFile info file hashhandle h = case filter (/= nullSha) [Ref asha, Ref bsha] of
[] -> return Nothing [] -> return Nothing
(sha:[]) -> use sha (sha:[]) -> use sha
shas -> use shas -> use
=<< either return (\s -> hashObject BlobObject (unlines s) repo) =<< either return (\s -> hashBlob hashhandle (unlines s))
=<< calcMerge . zip shas <$> mapM getcontents shas =<< calcMerge . zip shas <$> mapM getcontents shas
where where
[_colonmode, _bmode, asha, bsha, _status] = words info [_colonmode, _bmode, asha, bsha, _status] = words info

View file

@ -122,8 +122,8 @@ ddarRemoteCall :: DdarRepo -> Char -> [CommandParam] -> Annex (String, [CommandP
ddarRemoteCall ddarrepo cmd params ddarRemoteCall ddarrepo cmd params
| ddarLocal ddarrepo = return ("ddar", localParams) | ddarLocal ddarrepo = return ("ddar", localParams)
| otherwise = do | otherwise = do
os <- sshOptions (host, Nothing) (ddarRepoConfig ddarrepo) remoteParams os <- sshOptions (host, Nothing) (ddarRepoConfig ddarrepo) []
return ("ssh", os) return ("ssh", os ++ remoteParams)
where where
(host, ddarrepo') = splitRemoteDdarRepo ddarrepo (host, ddarrepo') = splitRemoteDdarRepo ddarrepo
localParams = Param [cmd] : Param (ddarRepoLocation ddarrepo) : params localParams = Param [cmd] : Param (ddarRepoLocation ddarrepo) : params
@ -158,8 +158,8 @@ ddarDirectoryExists ddarrepo
Left _ -> Right False Left _ -> Right False
Right status -> Right $ isDirectory status Right status -> Right $ isDirectory status
| otherwise = do | otherwise = do
ps <- sshOptions (host, Nothing) (ddarRepoConfig ddarrepo) params ps <- sshOptions (host, Nothing) (ddarRepoConfig ddarrepo) []
exitCode <- liftIO $ safeSystem "ssh" ps exitCode <- liftIO $ safeSystem "ssh" (ps ++ params)
case exitCode of case exitCode of
ExitSuccess -> return $ Right True ExitSuccess -> return $ Right True
ExitFailure 1 -> return $ Right False ExitFailure 1 -> return $ Right False

15
debian/changelog vendored
View file

@ -1,4 +1,11 @@
git-annex (6.20160230) UNRELEASED; urgency=medium git-annex (6.20160319) UNRELEASED; urgency=medium
* ddar remote: fix ssh calls
Thanks, Robie Basak
-- Joey Hess <id@joeyh.name> Wed, 23 Mar 2016 11:42:36 -0400
git-annex (6.20160318) unstable; urgency=medium
* metadata: Added -r to remove all current values of a field. * metadata: Added -r to remove all current values of a field.
* Fix data loss that can occur when annex.pidlock is set in a repository. * Fix data loss that can occur when annex.pidlock is set in a repository.
@ -12,8 +19,12 @@ git-annex (6.20160230) UNRELEASED; urgency=medium
* Fix OSX dmg to include libraries needed by bundled gpg, * Fix OSX dmg to include libraries needed by bundled gpg,
lost in last release. lost in last release.
* Always try to thaw content, even when annex.crippledfilesystem is set. * Always try to thaw content, even when annex.crippledfilesystem is set.
* Correct git-annex info to include unlocked files in v6 repository.
* Sped up git-annex add in direct mode and v6 by using
git hash-object --stdin-paths.
* Sped up git-annex merge by using git hash-object --stdin-paths.
-- Joey Hess <id@joeyh.name> Mon, 29 Feb 2016 13:00:30 -0400 -- Joey Hess <id@joeyh.name> Fri, 18 Mar 2016 11:30:36 -0400
git-annex (6.20160229) unstable; urgency=medium git-annex (6.20160229) unstable; urgency=medium

6
debian/control vendored
View file

@ -31,7 +31,7 @@ Build-Depends:
libghc-stm-dev (>= 2.3), libghc-stm-dev (>= 2.3),
libghc-dbus-dev (>= 0.10.7) [linux-any], libghc-dbus-dev (>= 0.10.7) [linux-any],
libghc-fdo-notify-dev (>= 0.3) [linux-any], libghc-fdo-notify-dev (>= 0.3) [linux-any],
libghc-yesod-dev (>= 1.2.6.1) [i386 amd64 arm64 armhf kfreebsd-amd64 kfreebsd-i386 mips mips64el mipsel powerpc ppc64el s390x] libghc-yesod-dev (>= 1.2.6.1) [i386 amd64 arm64 armhf kfreebsd-amd64 kfreebsd-i386 mips mips64el mipsel powerpc ppc64el s390x],
libghc-yesod-core-dev (>= 1.2.19) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-yesod-core-dev (>= 1.2.19) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
libghc-yesod-form-dev (>= 1.3.15) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-yesod-form-dev (>= 1.3.15) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
libghc-yesod-static-dev (>= 1.2.4) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-yesod-static-dev (>= 1.2.4) [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
@ -42,7 +42,7 @@ Build-Depends:
libghc-warp-tls-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-warp-tls-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
libghc-wai-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-wai-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
libghc-wai-extra-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x], libghc-wai-extra-dev [i386 amd64 arm64 armhf kfreebsd-i386 kfreebsd-amd64 mips mips64el mipsel powerpc ppc64el s390x],
libghc-dav-dev (>= 1.0) libghc-dav-dev (>= 1.0),
libghc-persistent-dev, libghc-persistent-dev,
libghc-persistent-template-dev, libghc-persistent-template-dev,
libghc-persistent-sqlite-dev, libghc-persistent-sqlite-dev,
@ -85,7 +85,7 @@ Build-Depends:
openssh-client, openssh-client,
git-remote-gcrypt (>= 0.20130908-6), git-remote-gcrypt (>= 0.20130908-6),
Maintainer: Richard Hartmann <richih@debian.org> Maintainer: Richard Hartmann <richih@debian.org>
Standards-Version: 3.9.6 Standards-Version: 3.9.7
Vcs-Git: git://git.kitenet.net/git-annex Vcs-Git: git://git.kitenet.net/git-annex
Homepage: http://git-annex.branchable.com/ Homepage: http://git-annex.branchable.com/
XS-Testsuite: autopkgtest XS-Testsuite: autopkgtest

View file

@ -0,0 +1,8 @@
[[!comment format=mdwn
username="divergentdave@5c17d06f6d67c6f157b76a4cc95ca764b7d2f899"
nickname="divergentdave"
subject="comment 2"
date="2016-03-21T04:13:15Z"
content="""
Each app has one subfolder inside /data that is private to that app (and user) alone. Generally, you can't read or enumerate /data itself. There is a function in the Java API to get the current app's internal storage folder, see https://developer.android.com/reference/android/content/Context.html#getFilesDir%28%29.
"""]]

View file

@ -0,0 +1,20 @@
### Please describe the problem.
I'm trying to get an Android development environment set up, but I am running into conflicting library versions inside of the chroot. The package installation script now finishes, but I run into a link-time error during `cabal configure` because it is pulling in two different versions of the unix package for some reason. Please let me know if there is any information I can get from my build environment that would help diagnosing the issue.
### What steps will reproduce the problem?
Run `buildchroot`, `install-haskell-packages`, `make android`
### What version of git-annex are you using? On what operating system?
Attempting to build from source, cross-compiling for Android on Debian Jessie.
### Please provide any additional information below.
[[!format sh """
Linking ./dist/setup/setup ...
/usr/lib/ghc/unix-2.6.0.1/libHSunix-2.6.0.1.a(execvpe.o): In function `pPrPr_disableITimers':
(.text+0x300): multiple definition of `pPrPr_disableITimers'
/home/builder/.cabal/lib/i386-linux-ghc-7.6.3/unix-2.7.1.0/libHSunix-2.7.1.0.a(ghcrts.o):ghcrts.c:(.text+0x0): first defined here
collect2: error: ld returned 1 exit status
Makefile:225: recipe for target 'android' failed
make: *** [android] Error 1
"""]]

View file

@ -0,0 +1,12 @@
### Please describe the problem.
git-annex version: 6.20160126
Problem happens on Mavericks, not on Yosemite with same version.
Can do a relative or absolute path on a git annex add.
But on the git annex copy to an S3 remote, if I use an absolute path for the file descriptor (e.g. /Users/name/git_directory/test.txt) it will not report an error, but will also not print the "copied..." string. A subsequent call with a relative path (e.g. test.txt) will work, show the copied message and indeed show up on S3.
Good news: It's working great on Yosemite!

View file

@ -0,0 +1,23 @@
[[!comment format=mdwn
username="joey"
subject="""comment 1"""
date="2016-03-14T17:34:21Z"
content="""
Using absolute paths to files is an unusual thing to do with git in my
experience. But, git does seem to support it, at least some of the time.
I think that git-annex's support for it comes down to what `git ls-files`
does. For example:
joey@darkstar:~/tmp/me> git ls-files ~/tmp/me/foo
foo
Since git-annex uses git ls-files, it sees a relative file and so
all or most all git-annex commands can work with the absolute file input.
Does git ls-files convert the absolute path to a relative path
when you run it on the Mavericks system?
What version of git is installed on the Mavericks system? Is
git-annex installed from the git-annex app, or from homebrew, or how?
"""]]

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