diff options
author | Joey Hess <joey@kitenet.net> | 2012-02-07 14:12:39 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2012-02-07 14:12:39 -0400 |
commit | b51d7de6085603599f97e7c69038328f036cd861 (patch) | |
tree | 472a3f604edb4a532c448d969f58ca801d2a3fb3 | |
parent | b8140f3fc2586603da9b92bad2346ecf4cba99c7 (diff) | |
parent | 7d04f3ad58a3789d77b1e90e502a27d66a90e0d3 (diff) |
Merge branch 'ghc7.4'
-rw-r--r-- | Command/Uninit.hs | 4 | ||||
-rw-r--r-- | Command/Unused.hs | 7 | ||||
-rw-r--r-- | Git/Branch.hs | 15 | ||||
-rw-r--r-- | Git/CheckAttr.hs | 32 | ||||
-rw-r--r-- | Git/Command.hs | 32 | ||||
-rw-r--r-- | Git/HashObject.hs | 1 | ||||
-rw-r--r-- | Git/LsTree.hs | 21 | ||||
-rw-r--r-- | Git/Queue.hs | 6 | ||||
-rw-r--r-- | Git/Ref.hs | 6 | ||||
-rw-r--r-- | Git/UnionMerge.hs | 17 | ||||
-rw-r--r-- | Messages.hs | 15 | ||||
-rw-r--r-- | Utility/Misc.hs | 8 | ||||
-rw-r--r-- | Utility/StatFS.hsc | 9 | ||||
-rw-r--r-- | Utility/Touch.hsc | 9 | ||||
-rw-r--r-- | debian/changelog | 2 | ||||
-rw-r--r-- | debian/control | 2 | ||||
-rw-r--r-- | doc/install.mdwn | 2 |
17 files changed, 89 insertions, 99 deletions
diff --git a/Command/Uninit.hs b/Command/Uninit.hs index ec6d0abf3..d6283a77d 100644 --- a/Command/Uninit.hs +++ b/Command/Uninit.hs @@ -7,8 +7,6 @@ module Command.Uninit where -import qualified Data.ByteString.Lazy.Char8 as B - 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 . B.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 ffd4bef45..1c82b9ae4 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 @@ -161,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 @@ -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 98811a987..cd9188228 100644 --- a/Git/Branch.hs +++ b/Git/Branch.hs @@ -7,8 +7,6 @@ module Git.Branch where -import qualified Data.ByteString.Lazy.Char8 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 eedaf6642..3e9375159 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 ec701c1f0..3d859ed28 100644 --- a/Git/Command.hs +++ b/Git/Command.hs @@ -7,7 +7,8 @@ module Git.Command where -import qualified Data.ByteString.Lazy.Char8 as L +import qualified Data.Text.Lazy as L +import qualified Data.Text.Lazy.IO as L import Common import Git @@ -38,41 +39,40 @@ 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 String pipeRead params repo = assertLocal repo $ do (_, h) <- hPipeFrom "git" $ toCommand $ gitCommandLine params repo - hSetBinaryMode h True - L.hGetContents h + fileEncoding h + 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] -> 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.hPut 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 <$> pipeNullSplitB params repo - -{- For when Strings are not needed. -} -pipeNullSplitB ::[CommandParam] -> Repo -> IO [L.ByteString] -pipeNullSplitB params repo = filter (not . L.null) . L.split '\0' <$> - pipeRead params repo +pipeNullSplit params repo = + filter (not . null) . split sep <$> pipeRead params repo + where + sep = "\0" {- Reaps any zombie git processes. -} reap :: IO () diff --git a/Git/HashObject.hs b/Git/HashObject.hs index f5e6d50cd..ae498278f 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 diff --git a/Git/LsTree.hs b/Git/LsTree.hs index aae7f1263..8f9066f0f 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.ByteString.Lazy.Char8 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 <$> - pipeNullSplitB [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.ByteString -> 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 = <mode> SP <type> SP <sha> TAB <file> -- 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 25c5b073c..c71605ad5 100644 --- a/Git/Queue.hs +++ b/Git/Queue.hs @@ -18,8 +18,8 @@ import qualified Data.Map as M import System.IO import System.Cmd.Utils import Data.String.Utils -import Utility.SafeCommand +import Utility.SafeCommand import Common import Git import Git.Command @@ -90,4 +90,6 @@ runAction repo action files = where params = toCommand $ gitCommandLine (Param (getSubcommand action):getParams action) repo - feedxargs h = hPutStr h $ join "\0" files + feedxargs h = do + fileEncoding h + hPutStr h $ join "\0" files diff --git a/Git/Ref.hs b/Git/Ref.hs index 557d24a37..f483aede0 100644 --- a/Git/Ref.hs +++ b/Git/Ref.hs @@ -7,8 +7,6 @@ module Git.Ref where -import qualified Data.ByteString.Lazy.Char8 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 4b335e47b..be8eb10d9 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 @@ -56,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 @@ -106,21 +108,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 <$> 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.ByteString -> 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"] @@ -130,7 +133,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, [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 1294e44f6..982b9313c 100644 --- a/Messages.hs +++ b/Messages.hs @@ -119,18 +119,13 @@ 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 avoids ghc's output layer crashing on invalid encoded characters in + - filenames when printing them out. + -} setupConsole :: IO () setupConsole = do - hSetBinaryMode stdout True - hSetBinaryMode stderr True + 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 3ac5ca5c0..9c284c826 100644 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -9,6 +9,14 @@ module Utility.Misc where import System.IO import Control.Monad +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. -} diff --git a/Utility/StatFS.hsc b/Utility/StatFS.hsc index 937571dfa..51a6bda1e 100644 --- a/Utility/StatFS.hsc +++ b/Utility/StatFS.hsc @@ -50,8 +50,11 @@ 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) +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 <sys/param.h> @@ -105,7 +108,7 @@ getFileSystemStats path = return Nothing #else allocaBytes (#size struct statfs) $ \vfs -> - useAsCString (pack 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 fd3320cd1..24ccd17a6 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 -> - withCString 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 -> - withCString file $ \f -> do + withFilePath file $ \f -> do pokeArray ptr [atime, mtime] r <- syscall f ptr if (r /= 0) diff --git a/debian/changelog b/debian/changelog index 96234d927..30b7090be 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 <joeyh@debian.org> Tue, 24 Jan 2012 16:21:55 -0400 diff --git a/debian/control b/debian/control index c3ddad932..5d5956de8 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 b48914197..8de24d40d 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) |