diff options
-rw-r--r-- | Command/Uninit.hs | 4 | ||||
-rw-r--r-- | Command/Unused.hs | 5 | ||||
-rw-r--r-- | Git/Branch.hs | 2 | ||||
-rw-r--r-- | Git/Command.hs | 26 | ||||
-rw-r--r-- | Git/LsTree.hs | 6 | ||||
-rw-r--r-- | Git/Queue.hs | 5 | ||||
-rw-r--r-- | Git/Ref.hs | 2 | ||||
-rw-r--r-- | Git/UnionMerge.hs | 9 | ||||
-rw-r--r-- | Messages.hs | 6 |
9 files changed, 36 insertions, 29 deletions
diff --git a/Command/Uninit.hs b/Command/Uninit.hs index ec6d0abf3..878547bc3 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 ffd4bef45..67f743ab0 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 98811a987..546d4a96b 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 ec701c1f0..1650efe13 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 aae7f1263..5c1541819 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 25c5b073c..63c3adee7 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 557d24a37..81560b015 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 4b335e47b..19db32860 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 1294e44f6..844c6bfc5 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 |