diff options
author | Joey Hess <joey@kitenet.net> | 2011-12-13 15:22:43 -0400 |
---|---|---|
committer | Joey Hess <joey@kitenet.net> | 2011-12-13 15:24:23 -0400 |
commit | 9db8ec210f8491de78cd7e83b94c50ead8049e72 (patch) | |
tree | 539d2a49f1599fdd4855570d046f710809062a8e /Git | |
parent | 25b2cc4148e4cc8f7435cdbcf4b124cc317c1305 (diff) |
split out two more Git modules
Diffstat (limited to 'Git')
-rw-r--r-- | Git/CheckAttr.hs | 44 | ||||
-rw-r--r-- | Git/Filename.hs | 84 | ||||
-rw-r--r-- | Git/LsTree.hs | 3 |
3 files changed, 130 insertions, 1 deletions
diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs new file mode 100644 index 000000000..e9269b1ed --- /dev/null +++ b/Git/CheckAttr.hs @@ -0,0 +1,44 @@ +{- git check-attr interface + - + - Copyright 2010, 2011 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Git.CheckAttr where + +import System.Exit + +import Common +import Git +import qualified Git.Filename + +{- Efficiently looks up a gitattributes value for each file in a list. -} +lookup :: String -> [FilePath] -> Repo -> IO [(FilePath, String)] +lookup attr files repo = do + -- git check-attr needs relative filenames input; it will choke + -- on some absolute filenames. This also means it will output + -- all relative filenames. + cwd <- getCurrentDirectory + let relfiles = map (relPathDirToFile cwd . absPathFrom cwd) files + (_, fromh, toh) <- hPipeBoth "git" (toCommand params) + _ <- forkProcess $ do + hClose fromh + hPutStr toh $ join "\0" relfiles + hClose toh + exitSuccess + hClose toh + (map topair . lines) <$> hGetContents fromh + where + params = gitCommandLine + [ Param "check-attr" + , Param attr + , Params "-z --stdin" + ] repo + topair l = (file, value) + where + file = Git.Filename.decode $ join sep $ take end bits + value = bits !! end + end = length bits - 1 + bits = split sep l + sep = ": " ++ attr ++ ": " diff --git a/Git/Filename.hs b/Git/Filename.hs new file mode 100644 index 000000000..69f36d086 --- /dev/null +++ b/Git/Filename.hs @@ -0,0 +1,84 @@ +{- Some git commands output encoded filenames, in a rather annoyingly complex + - C-style encoding. + - + - Copyright 2010, 2011 Joey Hess <joey@kitenet.net> + - + - Licensed under the GNU GPL version 3 or higher. + -} + +module Git.Filename where + +import qualified Codec.Binary.UTF8.String +import Data.Char +import Data.Word (Word8) +import Text.Printf + +decode :: String -> FilePath +decode [] = [] +decode f@(c:s) + -- encoded strings will be inside double quotes + | c == '"' = unescape ("", middle) + | otherwise = f + where + e = '\\' + middle = init s + unescape (b, []) = b + -- look for escapes starting with '\' + unescape (b, v) = b ++ beginning ++ unescape (handle rest) + where + pair = span (/= e) v + beginning = fst pair + rest = snd pair + isescape x = x == e + -- \NNN is an octal encoded character + handle (x:n1:n2:n3:rest) + | isescape x && alloctal = (fromoctal, rest) + where + alloctal = isOctDigit n1 && + isOctDigit n2 && + isOctDigit n3 + fromoctal = [chr $ readoctal [n1, n2, n3]] + readoctal o = read $ "0o" ++ o :: Int + -- \C is used for a few special characters + handle (x:nc:rest) + | isescape x = ([echar nc], rest) + where + echar 'a' = '\a' + echar 'b' = '\b' + echar 'f' = '\f' + echar 'n' = '\n' + echar 'r' = '\r' + echar 't' = '\t' + echar 'v' = '\v' + echar a = a + handle n = ("", n) + +{- Should not need to use this, except for testing decode. -} +encode :: FilePath -> String +encode s = foldl (++) "\"" (map echar s) ++ "\"" + where + e c = '\\' : [c] + echar '\a' = e 'a' + echar '\b' = e 'b' + echar '\f' = e 'f' + echar '\n' = e 'n' + echar '\r' = e 'r' + echar '\t' = e 't' + echar '\v' = e 'v' + echar '\\' = e '\\' + echar '"' = e '"' + echar x + | ord x < 0x20 = e_num x -- low ascii + | ord x >= 256 = e_utf x + | ord x > 0x7E = e_num x -- high ascii + | otherwise = [x] -- printable ascii + where + showoctal i = '\\' : printf "%03o" i + e_num c = showoctal $ ord c + -- unicode character is decomposed to + -- Word8s and each is shown in octal + e_utf c = showoctal =<< (Codec.Binary.UTF8.String.encode [c] :: [Word8]) + +{- for quickcheck -} +prop_idempotent_deencode :: String -> Bool +prop_idempotent_deencode s = s == decode (encode s) diff --git a/Git/LsTree.hs b/Git/LsTree.hs index 8aa16a308..342a125eb 100644 --- a/Git/LsTree.hs +++ b/Git/LsTree.hs @@ -17,6 +17,7 @@ import System.Posix.Types import qualified Data.ByteString.Lazy.Char8 as L import Git +import qualified Git.Filename import Utility.SafeCommand data TreeItem = TreeItem @@ -38,7 +39,7 @@ parseLsTree l = TreeItem { mode = fst $ head $ readOct $ L.unpack m , typeobj = L.unpack t , sha = L.unpack s - , file = decodeGitFile $ L.unpack f + , file = Git.Filename.decode $ L.unpack f } where -- l = <mode> SP <type> SP <sha> TAB <file> |