From 3d49258e5bed4d9a6ec9e24ddb776f277542664b Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Wed, 1 Feb 2012 16:05:02 -0400 Subject: [PATCH 01/17] attempt at a quick, utf-8 only fix to the ghc 7.4 problem If you have only utf-8 filenames, and need to build git-annex with ghc 7.4, this will work. But, it will crash on non-utf-8 filenames. --- Command/Uninit.hs | 4 ++-- Command/Unused.hs | 5 +++-- Git/Branch.hs | 2 +- Git/Command.hs | 26 +++++++++++++++----------- Git/LsTree.hs | 6 +++--- Git/Queue.hs | 5 +++-- Git/Ref.hs | 2 +- Git/UnionMerge.hs | 9 +++++---- Messages.hs | 6 +++--- 9 files changed, 36 insertions(+), 29 deletions(-) diff --git a/Command/Uninit.hs b/Command/Uninit.hs index ec6d0abf39..878547bc36 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -7,7 +7,7 @@ module Command.Uninit where -import qualified Data.ByteString.Lazy.Char8 as B +import qualified Data.Text.Lazy as L import Common.Annex import Command @@ -29,7 +29,7 @@ check = do when (b == Annex.Branch.name) $ error $ "cannot uninit when the " ++ show b ++ " branch is checked out" where - current_branch = Git.Ref . Prelude.head . lines . B.unpack <$> revhead + current_branch = Git.Ref . Prelude.head . lines . L.unpack <$> revhead revhead = inRepo $ Git.Command.pipeRead [Params "rev-parse --abbrev-ref HEAD"] diff --git a/Command/Unused.hs b/Command/Unused.hs index ffd4bef455..67f743ab08 100644 --- a/Command/Unused.hs +++ b/Command/Unused.hs @@ -10,7 +10,8 @@ module Command.Unused where import qualified Data.Set as S -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L +import qualified Data.Text.Lazy.Encoding as L import Common.Annex import Command @@ -202,7 +203,7 @@ getKeysReferencedInGit ref = do findkeys c [] = return c findkeys c (l:ls) | isSymLink (LsTree.mode l) = do - content <- catFile ref $ LsTree.file l + content <- L.decodeUtf8 <$> catFile ref (LsTree.file l) case fileKey (takeFileName $ L.unpack content) of Nothing -> findkeys c ls Just k -> findkeys (k:c) ls diff --git a/Git/Branch.hs b/Git/Branch.hs index 98811a9876..546d4a96b3 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -7,7 +7,7 @@ module Git.Branch where -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L import Common import Git diff --git a/Git/Command.hs b/Git/Command.hs index ec701c1f09..1650efe13c 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -7,7 +7,10 @@ module Git.Command where -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L +import qualified Data.Text.Lazy.Encoding as L +import qualified Data.Text.Lazy.IO as L +import qualified Data.ByteString.Lazy as B import Common import Git @@ -38,28 +41,27 @@ run subcommand params repo = assertLocal repo $ - Note that this leaves the git process running, and so zombies will - result unless reap is called. -} -pipeRead :: [CommandParam] -> Repo -> IO L.ByteString +pipeRead :: [CommandParam] -> Repo -> IO L.Text pipeRead params repo = assertLocal repo $ do (_, h) <- hPipeFrom "git" $ toCommand $ gitCommandLine params repo - hSetBinaryMode h True - L.hGetContents h + L.decodeUtf8 <$> B.hGetContents h {- Runs a git subcommand, feeding it input. - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} -pipeWrite :: [CommandParam] -> L.ByteString -> Repo -> IO PipeHandle +pipeWrite :: [CommandParam] -> L.Text -> Repo -> IO PipeHandle pipeWrite params s repo = assertLocal repo $ do (p, h) <- hPipeTo "git" (toCommand $ gitCommandLine params repo) - L.hPut h s + L.hPutStr h s hClose h return p {- Runs a git subcommand, feeding it input, and returning its output. - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} -pipeWriteRead :: [CommandParam] -> L.ByteString -> Repo -> IO (PipeHandle, L.ByteString) +pipeWriteRead :: [CommandParam] -> L.Text -> Repo -> IO (PipeHandle, L.Text) pipeWriteRead params s repo = assertLocal repo $ do (p, from, to) <- hPipeBoth "git" (toCommand $ gitCommandLine params repo) hSetBinaryMode from True - L.hPut to s + L.hPutStr to s hClose to c <- L.hGetContents from return (p, c) @@ -67,12 +69,14 @@ pipeWriteRead params s repo = assertLocal repo $ do {- Reads null terminated output of a git command (as enabled by the -z - parameter), and splits it. -} pipeNullSplit :: [CommandParam] -> Repo -> IO [String] -pipeNullSplit params repo = map L.unpack <$> pipeNullSplitB params repo +pipeNullSplit params repo = map L.unpack <$> pipeNullSplitT params repo {- For when Strings are not needed. -} -pipeNullSplitB ::[CommandParam] -> Repo -> IO [L.ByteString] -pipeNullSplitB params repo = filter (not . L.null) . L.split '\0' <$> +pipeNullSplitT ::[CommandParam] -> Repo -> IO [L.Text] +pipeNullSplitT params repo = filter (not . L.null) . L.splitOn sep <$> pipeRead params repo + where + sep = L.pack "\0" {- Reaps any zombie git processes. -} reap :: IO () diff --git a/Git/LsTree.hs b/Git/LsTree.hs index aae7f1263b..5c1541819a 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -14,7 +14,7 @@ module Git.LsTree ( import Numeric import Control.Applicative import System.Posix.Types -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L import Common import Git @@ -31,11 +31,11 @@ data TreeItem = TreeItem {- Lists the contents of a Ref -} lsTree :: Ref -> Repo -> IO [TreeItem] lsTree t repo = map parseLsTree <$> - pipeNullSplitB [Params "ls-tree --full-tree -z -r --", File $ show t] repo + pipeNullSplitT [Params "ls-tree --full-tree -z -r --", File $ show t] repo {- Parses a line of ls-tree output. - (The --long format is not currently supported.) -} -parseLsTree :: L.ByteString -> TreeItem +parseLsTree :: L.Text -> TreeItem parseLsTree l = TreeItem { mode = fst $ Prelude.head $ readOct $ L.unpack m , typeobj = L.unpack t diff --git a/Git/Queue.hs b/Git/Queue.hs index 25c5b073c7..63c3adee7c 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -18,8 +18,9 @@ import qualified Data.Map as M import System.IO import System.Cmd.Utils import Data.String.Utils -import Utility.SafeCommand +import Codec.Binary.UTF8.String +import Utility.SafeCommand import Common import Git import Git.Command @@ -90,4 +91,4 @@ runAction repo action files = where params = toCommand $ gitCommandLine (Param (getSubcommand action):getParams action) repo - feedxargs h = hPutStr h $ join "\0" files + feedxargs h = hPutStr h $ join "\0" $ map encodeString files diff --git a/Git/Ref.hs b/Git/Ref.hs index 557d24a372..81560b0157 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -7,7 +7,7 @@ module Git.Ref where -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L import Common import Git diff --git a/Git/UnionMerge.hs b/Git/UnionMerge.hs index 4b335e47b1..19db328609 100644 --- a/Git/UnionMerge.hs +++ b/Git/UnionMerge.hs @@ -15,7 +15,8 @@ module Git.UnionMerge ( ) where import System.Cmd.Utils -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L +import qualified Data.Text.Lazy.Encoding as L import qualified Data.Set as S import Common @@ -110,11 +111,11 @@ mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of calcMerge . zip shas <$> mapM getcontents shas where [_colonmode, _bmode, asha, bsha, _status] = words info - getcontents s = L.lines <$> catObject h s + getcontents s = L.lines . L.decodeUtf8 <$> catObject h s use sha = return $ Just $ update_index_line sha file {- Injects some content into git, returning its Sha. -} -hashObject :: Repo -> L.ByteString -> IO Sha +hashObject :: Repo -> L.Text -> IO Sha hashObject repo content = getSha subcmd $ do (h, s) <- pipeWriteRead (map Param params) content repo L.length s `seq` do @@ -130,7 +131,7 @@ hashObject repo content = getSha subcmd $ do - When possible, reuses the content of an existing ref, rather than - generating new content. -} -calcMerge :: [(Ref, [L.ByteString])] -> Either Ref [L.ByteString] +calcMerge :: [(Ref, [L.Text])] -> Either Ref [L.Text] calcMerge shacontents | null reuseable = Right $ new | otherwise = Left $ fst $ Prelude.head reuseable diff --git a/Messages.hs b/Messages.hs index 1294e44f69..844c6bfc51 100644 --- a/Messages.hs +++ b/Messages.hs @@ -128,9 +128,9 @@ showRaw s = handle q $ putStrLn s - - NB: Once git-annex gets localized, this will need a rethink. -} setupConsole :: IO () -setupConsole = do - hSetBinaryMode stdout True - hSetBinaryMode stderr True +setupConsole = return () + --hSetBinaryMode stdout True + --hSetBinaryMode stderr True handle :: IO () -> IO () -> Annex () handle json normal = Annex.getState Annex.output >>= go From fb78107f85ffbd83c7c8dad6bfcaa8374387cccc Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 3 Feb 2012 01:38:23 -0400 Subject: [PATCH 02/17] add a check for not utf-8 console --- Messages.hs | 20 +++++++++----------- 1 file changed, 9 insertions(+), 11 deletions(-) diff --git a/Messages.hs b/Messages.hs index 844c6bfc51..ff5287d80c 100644 --- a/Messages.hs +++ b/Messages.hs @@ -119,18 +119,16 @@ showHeader h = handle q $ showRaw :: String -> Annex () showRaw s = handle q $ putStrLn s -{- By default, haskell honors the user's locale in its output to stdout - - and stderr. While that's great for proper unicode support, for git-annex - - all that's really needed is the ability to display simple messages - - (currently untranslated), and importantly, to display filenames exactly - - as they are written on disk, no matter what their encoding. So, force - - raw mode. - - - - NB: Once git-annex gets localized, this will need a rethink. -} +{- This check is done because the code assumes filenames are utf8 encoded, + - using decodeUtf8 and Codec.Binary.UTF8.String.encodeString. So if + - run in a non unicode locale, it will crash or worse, possibly operate + - on the wrong file. + -} setupConsole :: IO () -setupConsole = return () - --hSetBinaryMode stdout True - --hSetBinaryMode stderr True +setupConsole + | show localeEncoding == show utf8 = return () + | otherwise = error $ + "Sorry, only UTF-8 locales are currently supported." handle :: IO () -> IO () -> Annex () handle json normal = Annex.getState Annex.output >>= go From d8fb97806c430be8358b2b77d67c02e876278d2f Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 3 Feb 2012 15:12:41 -0400 Subject: [PATCH 03/17] support all filename encodings with ghc 7.4 Under ghc 7.4, this seems to be able to handle all filename encodings again. Including filename encodings that do not match the LANG setting. I think this will not work with earlier versions of ghc, it uses some ghc internals. Turns out that ghc 7.4 has a special filesystem encoding that it uses when reading/writing filenames (as FilePaths). This encoding is documented to allow "arbitrary undecodable bytes to be round-tripped through it". So, to get FilePaths from eg, git ls-files, set the Handle that is reading from git to use this encoding. Then things basically just work. However, I have not found a way to make Text read using this encoding. Text really does assume unicode. So I had to switch back to using String when reading/writing data to git. Which is a pity, because it's some percent slower, but at least it works. Note that stdout and stderr also have to be set to this encoding, or printing out filenames that contain undecodable bytes causes a crash. IMHO this is a misfeature in ghc, that the user can pass you a filename, which you can readFile, etc, but that default, putStr of filename may cause a crash! Git.CheckAttr gave me special trouble, because the filenames I got back from git, after feeding them in, had further encoding breakage. Rather than try to deal with that, I just zip up the input filenames with the attributes. Which must be returned in the same order queried for this to work. Also of note is an apparent GHC bug I worked around in Git.CheckAttr. It used to forkProcess and feed git from the child process. Unfortunatly, after this forkProcess, accessing the `files` variable from the parent returns []. Not the value that was passed into the function. This screams of a bad bug, that's clobbering a variable, but for now I just avoid forkProcess there to work around it. That forkProcess was itself only added because of a ghc bug, #624389. I've confirmed that the test case for that bug doesn't reproduce it with ghc 7.4. So that's ok, except for the new ghc bug I have not isolated and reported. Why does this simple bit of code magnet the ghc bugs? :) Also, the symlink touching code is currently broken, when used on utf-8 filenames in a non-utf-8 locale, or probably on any filename containing undecodable bytes, and I temporarily commented it out. --- Command/Add.hs | 8 +++++--- Command/Uninit.hs | 4 +--- Command/Unused.hs | 2 +- Git/Branch.hs | 15 ++++++--------- Git/CheckAttr.hs | 32 +++++--------------------------- Git/Command.hs | 26 +++++++++++--------------- Git/LsTree.hs | 21 ++++++++++----------- Git/Queue.hs | 5 +++-- Git/Ref.hs | 6 ++---- Git/UnionMerge.hs | 13 +++++++------ Messages.hs | 13 +++++-------- Utility/Misc.hs | 8 ++++++++ 12 files changed, 64 insertions(+), 89 deletions(-) diff --git a/Command/Add.hs b/Command/Add.hs index 9410601b8b..944525ea5e 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -82,9 +82,11 @@ cleanup file key hascontent = do -- touch the symlink to have the same mtime as the -- file it points to - liftIO $ do - mtime <- modificationTime <$> getFileStatus file - touch file (TimeSpec mtime) False + -- XXX Currently broken on non-utf8 locales when + -- dealing with utf-8 filenames. + --liftIO $ do + --mtime <- modificationTime <$> getFileStatus file + --touch file (TimeSpec mtime) False force <- Annex.getState Annex.force if force diff --git a/Command/Uninit.hs b/Command/Uninit.hs index 878547bc36..d6283a77da 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -7,8 +7,6 @@ module Command.Uninit where -import qualified Data.Text.Lazy as L - import Common.Annex import Command import qualified Git @@ -29,7 +27,7 @@ check = do when (b == Annex.Branch.name) $ error $ "cannot uninit when the " ++ show b ++ " branch is checked out" where - current_branch = Git.Ref . Prelude.head . lines . L.unpack <$> revhead + current_branch = Git.Ref . Prelude.head . lines <$> revhead revhead = inRepo $ Git.Command.pipeRead [Params "rev-parse --abbrev-ref HEAD"] diff --git a/Command/Unused.hs b/Command/Unused.hs index 67f743ab08..1c82b9ae4a 100644 --- a/Command/Unused.hs +++ b/Command/Unused.hs @@ -162,7 +162,7 @@ excludeReferenced l = do refs = map (Git.Ref . snd) . nubBy uniqref . filter ourbranches . - map (separate (== ' ')) . lines . L.unpack + map (separate (== ' ')) . lines uniqref (a, _) (b, _) = a == b ourbranchend = '/' : show Annex.Branch.name ourbranches (_, b) = not $ ourbranchend `isSuffixOf` b diff --git a/Git/Branch.hs b/Git/Branch.hs index 546d4a96b3..cd91882283 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -7,8 +7,6 @@ module Git.Branch where -import qualified Data.Text.Lazy as L - import Common import Git import Git.Sha @@ -19,15 +17,15 @@ current :: Repo -> IO (Maybe Git.Ref) current r = parse <$> pipeRead [Param "symbolic-ref", Param "HEAD"] r where parse v - | L.null v = Nothing - | otherwise = Just $ Git.Ref $ firstLine $ L.unpack v + | null v = Nothing + | otherwise = Just $ Git.Ref $ firstLine v {- Checks if the second branch has any commits not present on the first - branch. -} changed :: Branch -> Branch -> Repo -> IO Bool changed origbranch newbranch repo | origbranch == newbranch = return False - | otherwise = not . L.null <$> diffs + | otherwise = not . null <$> diffs where diffs = pipeRead [ Param "log" @@ -73,15 +71,14 @@ fastForward branch (first:rest) repo = do - with the specified parent refs, and returns the committed sha -} commit :: String -> Branch -> [Ref] -> Repo -> IO Sha commit message branch parentrefs repo = do - tree <- getSha "write-tree" $ asString $ + tree <- getSha "write-tree" $ pipeRead [Param "write-tree"] repo - sha <- getSha "commit-tree" $ asString $ + sha <- getSha "commit-tree" $ ignorehandle $ pipeWriteRead (map Param $ ["commit-tree", show tree] ++ ps) - (L.pack message) repo + message repo run "update-ref" [Param $ show branch, Param $ show sha] repo return sha where ignorehandle a = snd <$> a - asString a = L.unpack <$> a ps = concatMap (\r -> ["-p", show r]) parentrefs diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs index eedaf66420..3e9375159a 100644 --- a/Git/CheckAttr.hs +++ b/Git/CheckAttr.hs @@ -7,12 +7,9 @@ module Git.CheckAttr where -import System.Exit - import Common import Git import Git.Command -import qualified Git.Filename import qualified Git.Version {- Efficiently looks up a gitattributes value for each file in a list. -} @@ -20,13 +17,9 @@ lookup :: String -> [FilePath] -> Repo -> IO [(FilePath, String)] lookup attr files repo = do cwd <- getCurrentDirectory (_, fromh, toh) <- hPipeBoth "git" (toCommand params) - _ <- forkProcess $ do - hClose fromh - hPutStr toh $ join "\0" $ input cwd - hClose toh - exitSuccess - hClose toh - output cwd . lines <$> hGetContents fromh + hPutStr toh $ join "\0" $ input cwd + hClose toh + zip files . map attrvalue . lines <$> hGetContents fromh where params = gitCommandLine [ Param "check-attr" @@ -45,22 +38,7 @@ lookup attr files repo = do input cwd | oldgit = map (absPathFrom cwd) files | otherwise = map (relPathDirToFile cwd . absPathFrom cwd) files - output cwd - | oldgit = map (torel cwd . topair) - | otherwise = map topair - - topair l = (Git.Filename.decode file, value) - where - file = join sep $ beginning bits - value = end bits !! 0 + attrvalue l = end bits !! 0 + where bits = split sep l sep = ": " ++ attr ++ ": " - - torel cwd (file, value) = (relfile, value) - where - relfile - | startswith cwd' file = drop (length cwd') file - | otherwise = relPathDirToFile top' file - top = workTree repo - cwd' = cwd ++ "/" - top' = top ++ "/" diff --git a/Git/Command.hs b/Git/Command.hs index 1650efe13c..3d859ed28d 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -8,9 +8,7 @@ module Git.Command where import qualified Data.Text.Lazy as L -import qualified Data.Text.Lazy.Encoding as L import qualified Data.Text.Lazy.IO as L -import qualified Data.ByteString.Lazy as B import Common import Git @@ -41,10 +39,11 @@ run subcommand params repo = assertLocal repo $ - Note that this leaves the git process running, and so zombies will - result unless reap is called. -} -pipeRead :: [CommandParam] -> Repo -> IO L.Text +pipeRead :: [CommandParam] -> Repo -> IO String pipeRead params repo = assertLocal repo $ do (_, h) <- hPipeFrom "git" $ toCommand $ gitCommandLine params repo - L.decodeUtf8 <$> B.hGetContents h + fileEncoding h + hGetContents h {- Runs a git subcommand, feeding it input. - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} @@ -57,26 +56,23 @@ pipeWrite params s repo = assertLocal repo $ do {- Runs a git subcommand, feeding it input, and returning its output. - You should call either getProcessStatus or forceSuccess on the PipeHandle. -} -pipeWriteRead :: [CommandParam] -> L.Text -> Repo -> IO (PipeHandle, L.Text) +pipeWriteRead :: [CommandParam] -> String -> Repo -> IO (PipeHandle, String) pipeWriteRead params s repo = assertLocal repo $ do (p, from, to) <- hPipeBoth "git" (toCommand $ gitCommandLine params repo) - hSetBinaryMode from True - L.hPutStr to s + fileEncoding to + fileEncoding from + hPutStr to s hClose to - c <- L.hGetContents from + c <- hGetContents from return (p, c) {- Reads null terminated output of a git command (as enabled by the -z - parameter), and splits it. -} pipeNullSplit :: [CommandParam] -> Repo -> IO [String] -pipeNullSplit params repo = map L.unpack <$> pipeNullSplitT params repo - -{- For when Strings are not needed. -} -pipeNullSplitT ::[CommandParam] -> Repo -> IO [L.Text] -pipeNullSplitT params repo = filter (not . L.null) . L.splitOn sep <$> - pipeRead params repo +pipeNullSplit params repo = + filter (not . null) . split sep <$> pipeRead params repo where - sep = L.pack "\0" + sep = "\0" {- Reaps any zombie git processes. -} reap :: IO () diff --git a/Git/LsTree.hs b/Git/LsTree.hs index 5c1541819a..8f9066f0f3 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -14,7 +14,6 @@ module Git.LsTree ( import Numeric import Control.Applicative import System.Posix.Types -import qualified Data.Text.Lazy as L import Common import Git @@ -31,22 +30,22 @@ data TreeItem = TreeItem {- Lists the contents of a Ref -} lsTree :: Ref -> Repo -> IO [TreeItem] lsTree t repo = map parseLsTree <$> - pipeNullSplitT [Params "ls-tree --full-tree -z -r --", File $ show t] repo + pipeNullSplit [Params "ls-tree --full-tree -z -r --", File $ show t] repo {- Parses a line of ls-tree output. - (The --long format is not currently supported.) -} -parseLsTree :: L.Text -> TreeItem +parseLsTree :: String -> TreeItem parseLsTree l = TreeItem - { mode = fst $ Prelude.head $ readOct $ L.unpack m - , typeobj = L.unpack t - , sha = L.unpack s - , file = Git.Filename.decode $ L.unpack f + { mode = fst $ Prelude.head $ readOct m + , typeobj = t + , sha = s + , file = Git.Filename.decode f } where -- l = SP SP TAB -- All fields are fixed, so we can pull them out of -- specific positions in the line. - (m, past_m) = L.splitAt 7 l - (t, past_t) = L.splitAt 4 past_m - (s, past_s) = L.splitAt 40 $ L.tail past_t - f = L.tail past_s + (m, past_m) = splitAt 7 l + (t, past_t) = splitAt 4 past_m + (s, past_s) = splitAt 40 $ Prelude.tail past_t + f = Prelude.tail past_s diff --git a/Git/Queue.hs b/Git/Queue.hs index 63c3adee7c..c71605ad52 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -18,7 +18,6 @@ import qualified Data.Map as M import System.IO import System.Cmd.Utils import Data.String.Utils -import Codec.Binary.UTF8.String import Utility.SafeCommand import Common @@ -91,4 +90,6 @@ runAction repo action files = where params = toCommand $ gitCommandLine (Param (getSubcommand action):getParams action) repo - feedxargs h = hPutStr h $ join "\0" $ map encodeString files + feedxargs h = do + fileEncoding h + hPutStr h $ join "\0" files diff --git a/Git/Ref.hs b/Git/Ref.hs index 81560b0157..f483aede03 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -7,8 +7,6 @@ module Git.Ref where -import qualified Data.Text.Lazy as L - import Common import Git import Git.Command @@ -40,7 +38,7 @@ exists ref = runBool "show-ref" {- Get the sha of a fully qualified git ref, if it exists. -} sha :: Branch -> Repo -> IO (Maybe Sha) -sha branch repo = process . L.unpack <$> showref repo +sha branch repo = process <$> showref repo where showref = pipeRead [Param "show-ref", Param "--hash", -- get the hash @@ -52,7 +50,7 @@ sha branch repo = process . L.unpack <$> showref repo matching :: Ref -> Repo -> IO [(Ref, Branch)] matching ref repo = do r <- pipeRead [Param "show-ref", Param $ show ref] repo - return $ map (gen . L.unpack) (L.lines r) + return $ map gen (lines r) where gen l = let (r, b) = separate (== ' ') l in (Ref r, Ref b) diff --git a/Git/UnionMerge.hs b/Git/UnionMerge.hs index 19db328609..15bff60527 100644 --- a/Git/UnionMerge.hs +++ b/Git/UnionMerge.hs @@ -107,21 +107,22 @@ mergeFile :: String -> FilePath -> CatFileHandle -> Repo -> IO (Maybe String) mergeFile info file h repo = case filter (/= nullSha) [Ref asha, Ref bsha] of [] -> return Nothing (sha:[]) -> use sha - shas -> use =<< either return (hashObject repo . L.unlines) =<< + shas -> use =<< either return (hashObject repo . unlines) =<< calcMerge . zip shas <$> mapM getcontents shas where [_colonmode, _bmode, asha, bsha, _status] = words info - getcontents s = L.lines . L.decodeUtf8 <$> catObject h s + getcontents s = map L.unpack . L.lines . + L.decodeUtf8 <$> catObject h s use sha = return $ Just $ update_index_line sha file {- Injects some content into git, returning its Sha. -} -hashObject :: Repo -> L.Text -> IO Sha +hashObject :: Repo -> String -> IO Sha hashObject repo content = getSha subcmd $ do (h, s) <- pipeWriteRead (map Param params) content repo - L.length s `seq` do + length s `seq` do forceSuccess h reap -- XXX unsure why this is needed - return $ L.unpack s + return s where subcmd = "hash-object" params = [subcmd, "-w", "--stdin"] @@ -131,7 +132,7 @@ hashObject repo content = getSha subcmd $ do - When possible, reuses the content of an existing ref, rather than - generating new content. -} -calcMerge :: [(Ref, [L.Text])] -> Either Ref [L.Text] +calcMerge :: [(Ref, [String])] -> Either Ref [String] calcMerge shacontents | null reuseable = Right $ new | otherwise = Left $ fst $ Prelude.head reuseable diff --git a/Messages.hs b/Messages.hs index ff5287d80c..a0bd20ca3c 100644 --- a/Messages.hs +++ b/Messages.hs @@ -119,16 +119,13 @@ showHeader h = handle q $ showRaw :: String -> Annex () showRaw s = handle q $ putStrLn s -{- This check is done because the code assumes filenames are utf8 encoded, - - using decodeUtf8 and Codec.Binary.UTF8.String.encodeString. So if - - run in a non unicode locale, it will crash or worse, possibly operate - - on the wrong file. +{- This avoids ghc's output layer crashing on invalid encoded characters in + - files when printing them out. -} setupConsole :: IO () -setupConsole - | show localeEncoding == show utf8 = return () - | otherwise = error $ - "Sorry, only UTF-8 locales are currently supported." +setupConsole = do + fileEncoding stdout + fileEncoding stderr handle :: IO () -> IO () -> Annex () handle json normal = Annex.getState Annex.output >>= go diff --git a/Utility/Misc.hs b/Utility/Misc.hs index c9bfcb953a..c4992e1428 100644 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -11,6 +11,14 @@ import System.IO import System.IO.Error (try) import Control.Monad import Control.Applicative +import GHC.IO.Encoding + +{- Sets a Handle to use the filesystem encoding. This causes data + - written or read from it to be encoded/decoded the same + - as ghc 7.4 does to filenames et. This special encoding + - allows "arbitrary undecodable bytes to be round-tripped through it". -} +fileEncoding :: Handle -> IO () +fileEncoding h = hSetEncoding h =<< getFileSystemEncoding {- A version of hgetContents that is not lazy. Ensures file is - all read before it gets closed. -} From f1c7dc12127fcbad411c28df57e9ce194bd66509 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 12:24:00 -0400 Subject: [PATCH 04/17] fix touch and statfs to work on any files in any locale Use withCAString rather than withCString. XXX Actually, this only works in non-unicode locales when presented with unicode characters. Help? --- Command/Add.hs | 6 +++--- Utility/StatFS.hsc | 4 +--- Utility/Touch.hsc | 4 ++-- 3 files changed, 6 insertions(+), 8 deletions(-) diff --git a/Command/Add.hs b/Command/Add.hs index 944525ea5e..f437d160d1 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -84,9 +84,9 @@ cleanup file key hascontent = do -- file it points to -- XXX Currently broken on non-utf8 locales when -- dealing with utf-8 filenames. - --liftIO $ do - --mtime <- modificationTime <$> getFileStatus file - --touch file (TimeSpec mtime) False + liftIO $ do + mtime <- modificationTime <$> getFileStatus file + touch file (TimeSpec mtime) False force <- Annex.getState Annex.force if force diff --git a/Utility/StatFS.hsc b/Utility/StatFS.hsc index 937571dfa0..6b96274637 100644 --- a/Utility/StatFS.hsc +++ b/Utility/StatFS.hsc @@ -50,8 +50,6 @@ module Utility.StatFS ( FileSystemStats(..), getFileSystemStats ) where import Foreign import Foreign.C.Types import Foreign.C.String -import Data.ByteString (useAsCString) -import Data.ByteString.Char8 (pack) #if defined (__FreeBSD__) || defined (__FreeBSD_kernel__) || defined (__APPLE__) # include @@ -105,7 +103,7 @@ getFileSystemStats path = return Nothing #else allocaBytes (#size struct statfs) $ \vfs -> - useAsCString (pack path) $ \cpath -> do + withCAString path $ \cpath -> do res <- c_statfs cpath vfs if res == -1 then return Nothing else do diff --git a/Utility/Touch.hsc b/Utility/Touch.hsc index fd3320cd1d..41d3e17b8e 100644 --- a/Utility/Touch.hsc +++ b/Utility/Touch.hsc @@ -64,7 +64,7 @@ foreign import ccall "utimensat" touchBoth file atime mtime follow = allocaArray 2 $ \ptr -> - withCString file $ \f -> do + withCAString file $ \f -> do pokeArray ptr [atime, mtime] r <- c_utimensat at_fdcwd f ptr flags when (r /= 0) $ throwErrno "touchBoth" @@ -101,7 +101,7 @@ foreign import ccall "lutimes" touchBoth file atime mtime follow = allocaArray 2 $ \ptr -> - withCString file $ \f -> do + withCAString file $ \f -> do pokeArray ptr [atime, mtime] r <- syscall f ptr if (r /= 0) From 586be399523a9a0ae1ed39d34b84c2c78296b457 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 12:58:42 -0400 Subject: [PATCH 05/17] fix file encoding of HashObject --- Git/HashObject.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Git/HashObject.hs b/Git/HashObject.hs index f5e6d50cdf..ae498278f4 100644 --- a/Git/HashObject.hs +++ b/Git/HashObject.hs @@ -16,6 +16,7 @@ import Git.Command hashFiles :: [FilePath] -> Repo -> IO ([Sha], IO ()) hashFiles paths repo = do (pid, fromh, toh) <- hPipeBoth "git" $ toCommand $ git_hash_object repo + fileEncoding toh _ <- forkProcess (feeder toh) hClose toh shas <- map Ref . lines <$> hGetContentsStrict fromh From dc682e53a2971a4e1ca89a997dcb44406aa5be75 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 13:03:33 -0400 Subject: [PATCH 06/17] use fileEncoding for git-update-index input handle --- Git/UnionMerge.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/Git/UnionMerge.hs b/Git/UnionMerge.hs index 15bff60527..be8eb10d99 100644 --- a/Git/UnionMerge.hs +++ b/Git/UnionMerge.hs @@ -57,6 +57,7 @@ update_index repo ls = stream_update_index repo [(`mapM_` ls)] stream_update_index :: Repo -> [Streamer] -> IO () stream_update_index repo as = do (p, h) <- hPipeTo "git" (toCommand $ gitCommandLine params repo) + fileEncoding h forM_ as (stream h) hClose h forceSuccess p From 56470ce3e5a417dd81c985711b7927db0ce9015e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 14:30:28 -0400 Subject: [PATCH 07/17] really fix foreign C functions filename encodings GHC should probably export withFilePath. --- Utility/StatFS.hsc | 7 ++++++- Utility/Touch.hsc | 9 +++++++-- 2 files changed, 13 insertions(+), 3 deletions(-) diff --git a/Utility/StatFS.hsc b/Utility/StatFS.hsc index 6b96274637..51a6bda1e3 100644 --- a/Utility/StatFS.hsc +++ b/Utility/StatFS.hsc @@ -50,6 +50,11 @@ module Utility.StatFS ( FileSystemStats(..), getFileSystemStats ) where import Foreign import Foreign.C.Types import Foreign.C.String +import GHC.IO.Encoding (getFileSystemEncoding) +import GHC.Foreign as GHC + +withFilePath :: FilePath -> (CString -> IO a) -> IO a +withFilePath fp f = getFileSystemEncoding >>= \enc -> GHC.withCString enc fp f #if defined (__FreeBSD__) || defined (__FreeBSD_kernel__) || defined (__APPLE__) # include @@ -103,7 +108,7 @@ getFileSystemStats path = return Nothing #else allocaBytes (#size struct statfs) $ \vfs -> - withCAString path $ \cpath -> do + withFilePath path $ \cpath -> do res <- c_statfs cpath vfs if res == -1 then return Nothing else do diff --git a/Utility/Touch.hsc b/Utility/Touch.hsc index 41d3e17b8e..24ccd17a62 100644 --- a/Utility/Touch.hsc +++ b/Utility/Touch.hsc @@ -16,6 +16,11 @@ module Utility.Touch ( import Foreign import Foreign.C import Control.Monad (when) +import GHC.IO.Encoding (getFileSystemEncoding) +import GHC.Foreign as GHC + +withFilePath :: FilePath -> (CString -> IO a) -> IO a +withFilePath fp f = getFileSystemEncoding >>= \enc -> GHC.withCString enc fp f newtype TimeSpec = TimeSpec CTime @@ -64,7 +69,7 @@ foreign import ccall "utimensat" touchBoth file atime mtime follow = allocaArray 2 $ \ptr -> - withCAString file $ \f -> do + withFilePath file $ \f -> do pokeArray ptr [atime, mtime] r <- c_utimensat at_fdcwd f ptr flags when (r /= 0) $ throwErrno "touchBoth" @@ -101,7 +106,7 @@ foreign import ccall "lutimes" touchBoth file atime mtime follow = allocaArray 2 $ \ptr -> - withCAString file $ \f -> do + withFilePath file $ \f -> do pokeArray ptr [atime, mtime] r <- syscall f ptr if (r /= 0) From 91fc975964d94503fa932256bc8684de13cd9e1e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 14:44:03 -0400 Subject: [PATCH 08/17] note 7.4 needed --- debian/control | 2 +- doc/install.mdwn | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/debian/control b/debian/control index c3ddad9322..5d5956de8d 100644 --- a/debian/control +++ b/debian/control @@ -3,7 +3,7 @@ Section: utils Priority: optional Build-Depends: debhelper (>= 9), - ghc, + ghc (>= 7.4), libghc-missingh-dev, libghc-hslogger-dev, libghc-pcre-light-dev, diff --git a/doc/install.mdwn b/doc/install.mdwn index b48914197f..8de24d40db 100644 --- a/doc/install.mdwn +++ b/doc/install.mdwn @@ -21,7 +21,7 @@ As a haskell package, git-annex can be installed using cabal. For example: To build and use git-annex, you will need: * Haskell stuff - * [The Haskell Platform](http://haskell.org/platform/) + * [The Haskell Platform](http://haskell.org/platform/) (GHC 7.4 or newer) * [MissingH](http://github.com/jgoerzen/missingh/wiki) * [pcre-light](http://hackage.haskell.org/package/pcre-light) * [utf8-string](http://hackage.haskell.org/package/utf8-string) From 90ab17e15394892c6b0a17682d317085bab3e711 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 16:34:13 -0400 Subject: [PATCH 09/17] remove old comment --- Command/Add.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/Command/Add.hs b/Command/Add.hs index f437d160d1..9410601b8b 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -82,8 +82,6 @@ cleanup file key hascontent = do -- touch the symlink to have the same mtime as the -- file it points to - -- XXX Currently broken on non-utf8 locales when - -- dealing with utf-8 filenames. liftIO $ do mtime <- modificationTime <$> getFileStatus file touch file (TimeSpec mtime) False From 10876ca59e296c40f1e992c8521f67a66ec41a1c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 16:37:55 -0400 Subject: [PATCH 10/17] wording --- Messages.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Messages.hs b/Messages.hs index a0bd20ca3c..982b9313cf 100644 --- a/Messages.hs +++ b/Messages.hs @@ -120,7 +120,7 @@ showRaw :: String -> Annex () showRaw s = handle q $ putStrLn s {- This avoids ghc's output layer crashing on invalid encoded characters in - - files when printing them out. + - filenames when printing them out. -} setupConsole :: IO () setupConsole = do From edcd3123d5292e39071a6bd9f8efa86d71e2da2c Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 20:18:20 -0400 Subject: [PATCH 11/17] list of git branches --- doc/download.mdwn | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/doc/download.mdwn b/doc/download.mdwn index e1257d2618..bfde849f80 100644 --- a/doc/download.mdwn +++ b/doc/download.mdwn @@ -15,3 +15,20 @@ From time to time, releases of git-annex are uploaded Some operating systems include git-annex in easily prepackaged form and others need some manual work. See [[install]] for details. + +## git branches + +The git repository has some branches: + +* `debian-stable` contains the latest backport of git-annex to Debian + stable. +* `no-s3` disables the S3 special remote, for systems that lack the + necessary haskell library. +* `old-monad-control` is for systems that don't have a newer monad-control + library. +* `tweak-fetch` adds support for the git tweak-fetch hook, which has + been proposed and implemented but not yet accepted into git. +* `ghc7.4` is for use this that version of ghc. +* `setup` contains configuration for this website +* `pristine-tar` contains [pristine-tar](http://kitenet.net/~joey/code/pristine-tar) + data to create tarballs of any past git-annex release. From 5a82c0dee77a2302fb7ddd0026c6d4e311eb1a07 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 6 Feb 2012 11:52:51 -0400 Subject: [PATCH 12/17] add a tip about using git's assume-unchanged feature to optimize large trees --- doc/tips/assume-unstaged.mdwn | 31 +++++++++++++++++++++++++++++++ 1 file changed, 31 insertions(+) create mode 100644 doc/tips/assume-unstaged.mdwn diff --git a/doc/tips/assume-unstaged.mdwn b/doc/tips/assume-unstaged.mdwn new file mode 100644 index 0000000000..ef74d9bd40 --- /dev/null +++ b/doc/tips/assume-unstaged.mdwn @@ -0,0 +1,31 @@ +[[!meta title="using assume-unstages to speed up git with large trees of annexed files"]] + +Git update-index's assume-unstaged feature can be used to speed +up `git status` and stuff by not statting the whole tree looking for changed +files. + +This feature works quite well with git-annex. Especially because git +annex's files are immutable, so arn't going to change out from under it, +this is a nice fit. If you have a very large tree and `git status` is +annoyingly slow, you can turn it on: + + git config core.ignoreStat true + +When git mv and git rm are used, those changes *do* get noticed, even +on assume-unchanged files. When new files are added, eg by `git annex add`, +they are also noticed. + +There are two gotchas. Both occur because `git add` does not stage +assume-unchanged files. + +1. When an annexed file is moved to a different directory, it updates + the symlink, and runs `git add` on it. So the file will move, + but the changed symlink will not be noticed by git and it will commit a + dangling symlink. +2. When using `git annex migrate`, it changes the symlink and `git adds` + it. Again this won't be committed. + +These can be worked around by running `git update-index --really-refresh` +after performing such operations. I hope that `git add` will be changed +to stage changes to assume-unchanged files, which would remove this +only complication. --[[Joey]] From a84d50a1edc268d4dbdaebeb4d23c76c48d9a506 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Fri, 3 Feb 2012 16:57:07 -0400 Subject: [PATCH 13/17] exception update in test too --- test.hs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/test.hs b/test.hs index 7b25917a11..245dd6706a 100644 --- a/test.hs +++ b/test.hs @@ -11,10 +11,8 @@ import Test.QuickCheck import System.Posix.Directory (changeWorkingDirectory) import System.Posix.Files -import Control.Exception (bracket_, bracket, throw) -import System.IO.Error import System.Posix.Env -import qualified Control.Exception.Extensible as E +import Control.Exception.Extensible import qualified Data.Map as M import System.IO.HVFS (SystemFS(..)) import Text.JSON @@ -695,7 +693,7 @@ test_crypto = "git-annex crypto" ~: intmpclonerepo $ when Build.SysConfig.gpg $ git_annex :: String -> [String] -> IO Bool git_annex command params = do -- catch all errors, including normally fatal errors - r <- E.try (run)::IO (Either E.SomeException ()) + r <- try (run)::IO (Either SomeException ()) case r of Right _ -> return True Left _ -> return False @@ -761,7 +759,7 @@ indir dir a = do -- any type of error and change back to cwd before -- rethrowing. r <- bracket_ (changeToTmpDir dir) (changeWorkingDirectory cwd) - (E.try (a)::IO (Either E.SomeException ())) + (try (a)::IO (Either SomeException ())) case r of Right () -> return () Left e -> throw e @@ -832,14 +830,14 @@ checkunwritable f = do checkwritable :: FilePath -> Assertion checkwritable f = do - r <- try $ writeFile f $ content f + r <- tryIO $ writeFile f $ content f case r of Left _ -> assertFailure $ "unable to modify " ++ f Right _ -> return () checkdangling :: FilePath -> Assertion checkdangling f = do - r <- try $ readFile f + r <- tryIO $ readFile f case r of Left _ -> return () -- expected; dangling link Right _ -> assertFailure $ f ++ " was not a dangling link as expected" From a6c4b107716c61a48fbf1b0431abbcc330c7fd44 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Sat, 4 Feb 2012 01:59:53 -0400 Subject: [PATCH 14/17] add news item --- doc/news/Presentation_at_FOSDEM.mdwn | 4 ++++ 1 file changed, 4 insertions(+) create mode 100644 doc/news/Presentation_at_FOSDEM.mdwn diff --git a/doc/news/Presentation_at_FOSDEM.mdwn b/doc/news/Presentation_at_FOSDEM.mdwn new file mode 100644 index 0000000000..48daf2678d --- /dev/null +++ b/doc/news/Presentation_at_FOSDEM.mdwn @@ -0,0 +1,4 @@ +git-annex will be briefly presented at FOSDEM, on Sunday February 4th at 15:40. +[Details](http://fosdem.org/2012/schedule/event/gitannex). + +Thanks to Richard Hartmann for making this presentation. From a81297065dd2f1a4fb59abcddec852414174200e Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 6 Feb 2012 14:19:44 -0400 Subject: [PATCH 15/17] use "known" instead of "visible" I think it's clearer, also it's the same length as "local" :) --- Command/Status.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/Command/Status.hs b/Command/Status.hs index a1d4eea087..5facaab9be 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -66,8 +66,8 @@ slow_stats = , bad_data_size , local_annex_keys , local_annex_size - , visible_annex_keys - , visible_annex_size + , known_annex_keys + , known_annex_size , backend_usage ] @@ -128,12 +128,12 @@ local_annex_keys :: Stat local_annex_keys = stat "local annex keys" $ json show $ S.size <$> cachedKeysPresent -visible_annex_size :: Stat -visible_annex_size = stat "visible annex size" $ json id $ +known_annex_size :: Stat +known_annex_size = stat "known annex size" $ json id $ keySizeSum <$> cachedKeysReferenced -visible_annex_keys :: Stat -visible_annex_keys = stat "visible annex keys" $ json show $ +known_annex_keys :: Stat +known_annex_keys = stat "known annex keys" $ json show $ S.size <$> cachedKeysReferenced tmp_size :: Stat From 3f4f96228e85fc6762490b99b76026826917d95b Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 6 Feb 2012 14:23:10 -0400 Subject: [PATCH 16/17] changelog --- debian/changelog | 2 ++ 1 file changed, 2 insertions(+) diff --git a/debian/changelog b/debian/changelog index 96234d9272..30b7090bea 100644 --- a/debian/changelog +++ b/debian/changelog @@ -7,6 +7,8 @@ git-annex (3.20120124) UNRELEASED; urgency=low git-annex's existing ability to recover in this situation. This is used by git-annex-shell and other places where changes are made to a remote's location log. + * Modifications to support ghc 7.4's handling of filenames. + This version can only be built with ghc 7.4. -- Joey Hess Tue, 24 Jan 2012 16:21:55 -0400 From 679e2567d09667ef4f90902db8b493e01844e246 Mon Sep 17 00:00:00 2001 From: Joey Hess Date: Mon, 6 Feb 2012 21:37:44 -0400 Subject: [PATCH 17/17] add a bug template --- doc/bugs.mdwn | 2 ++ doc/templates/bugtemplate.mdwn | 12 ++++++++++++ 2 files changed, 14 insertions(+) create mode 100644 doc/templates/bugtemplate.mdwn diff --git a/doc/bugs.mdwn b/doc/bugs.mdwn index 2786e5bf74..b0837eb10b 100644 --- a/doc/bugs.mdwn +++ b/doc/bugs.mdwn @@ -2,3 +2,5 @@ This is git-annex's bug list. Link bugs to [[bugs/done]] when done. [[!inline pages="./bugs/* and !./bugs/done and !link(done) and !*/Discussion" actions=yes postform=yes show=0 archive=yes]] + +[[!edittemplate template=templates/bugtemplate match="bugs/*" silent=yes]] diff --git a/doc/templates/bugtemplate.mdwn b/doc/templates/bugtemplate.mdwn new file mode 100644 index 0000000000..2d35c8f6fb --- /dev/null +++ b/doc/templates/bugtemplate.mdwn @@ -0,0 +1,12 @@ +What steps will reproduce the problem? + + +What is the expected output? What do you see instead? + + +What version of git-annex are you using? On what operating system? + + +Please provide any additional information below. + +