Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.

Commit eaf1378

Browse files
author
Patrick Thomson
authored
Merge pull request #98 from lalaithion/gitparsing
Use Attoparsec for parsing git output instead of manually splitting Text
2 parents 0257625 + aa02a62 commit eaf1378

File tree

2 files changed

+53
-26
lines changed

2 files changed

+53
-26
lines changed

src/Semantic/Git.hs

Lines changed: 35 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -9,12 +9,19 @@ module Semantic.Git
99
, ObjectType(..)
1010
, ObjectMode(..)
1111
, OID(..)
12+
13+
-- Testing Purposes
14+
, parseEntries
15+
, parseEntry
1216
) where
1317

1418
import Control.Monad.IO.Class
15-
import Data.Text as Text
16-
import Shelly hiding (FilePath)
17-
import System.IO (hSetBinaryMode)
19+
import Data.Attoparsec.Text (Parser)
20+
import Data.Attoparsec.Text as AP
21+
import Data.Char
22+
import Data.Text as Text
23+
import Shelly hiding (FilePath)
24+
import System.IO (hSetBinaryMode)
1825

1926
-- | git clone --bare
2027
clone :: Text -> FilePath -> IO ()
@@ -24,22 +31,38 @@ clone url path = sh $ do
2431
-- | git cat-file -p
2532
catFile :: FilePath -> OID -> IO Text
2633
catFile gitDir (OID oid) = sh $ do
27-
run "git" [pack ("--git-dir=" <> gitDir), "cat-file", "-p", oid]
34+
run "git" ["-C", pack gitDir, "cat-file", "-p", oid]
2835

2936
-- | git ls-tree -rz
3037
lsTree :: FilePath -> OID -> IO [TreeEntry]
31-
lsTree gitDir (OID sha) = sh $ do
32-
out <- run "git" [pack ("--git-dir=" <> gitDir), "ls-tree", "-rz", sha]
33-
pure $ mkEntry <$> splitOn "\NUL" out
34-
where
35-
mkEntry row | [mode, ty, rest] <- splitOn " " row
36-
, [oid, path] <- splitOn "\t" rest
37-
= TreeEntry (objectMode mode) (objectType ty) (OID oid) (unpack path)
38-
| otherwise = nullTreeEntry
38+
lsTree gitDir (OID sha) = sh $ parseEntries <$> run "git" ["-C", pack gitDir, "ls-tree", "-rz", sha]
3939

4040
sh :: MonadIO m => Sh a -> m a
4141
sh = shelly . silently . onCommandHandles (initOutputHandles (`hSetBinaryMode` True))
4242

43+
-- | Parses an list of entries separated by \NUL, and on failure return []
44+
parseEntries :: Text -> [TreeEntry]
45+
parseEntries = either (const []) id . AP.parseOnly everything
46+
where
47+
everything = AP.sepBy entryParser "\NUL" <* "\NUL\n" <* AP.endOfInput
48+
49+
-- | Parse the entire input with entryParser, and on failure return a default
50+
-- For testing purposes only
51+
parseEntry :: Text -> Either String TreeEntry
52+
parseEntry = AP.parseOnly (entryParser <* AP.endOfInput)
53+
54+
-- | Parses a TreeEntry
55+
entryParser :: Parser TreeEntry
56+
entryParser = TreeEntry
57+
<$> modeParser <* AP.char ' '
58+
<*> typeParser <* AP.char ' '
59+
<*> oidParser <* AP.char '\t'
60+
<*> (unpack <$> AP.takeWhile (/= '\NUL'))
61+
where
62+
typeParser = AP.choice [BlobObject <$ "blob", TreeObject <$ "tree"]
63+
modeParser = AP.choice [NormalMode <$ "100644", ExecutableMode <$ "100755", SymlinkMode <$ "120000", TreeMode <$ "040000"]
64+
oidParser = OID <$> AP.takeWhile isHexDigit
65+
4366
newtype OID = OID Text
4467
deriving (Eq, Show, Ord)
4568

@@ -51,24 +74,12 @@ data ObjectMode
5174
| OtherMode
5275
deriving (Eq, Show)
5376

54-
objectMode :: Text -> ObjectMode
55-
objectMode "100644" = NormalMode
56-
objectMode "100755" = ExecutableMode
57-
objectMode "120000" = SymlinkMode
58-
objectMode "040000" = TreeMode
59-
objectMode _ = OtherMode
60-
6177
data ObjectType
6278
= BlobObject
6379
| TreeObject
6480
| OtherObjectType
6581
deriving (Eq, Show)
6682

67-
objectType :: Text -> ObjectType
68-
objectType "blob" = BlobObject
69-
objectType "tree" = TreeObject
70-
objectType _ = OtherObjectType
71-
7283
data TreeEntry
7384
= TreeEntry
7485
{ treeEntryMode :: ObjectMode
@@ -77,5 +88,3 @@ data TreeEntry
7788
, treeEntryPath :: FilePath
7889
} deriving (Eq, Show)
7990

80-
nullTreeEntry :: TreeEntry
81-
nullTreeEntry = TreeEntry OtherMode OtherObjectType (OID mempty) mempty

test/Semantic/Spec.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Semantic.Spec (spec) where
33
import Data.Diff
44
import Data.Patch
55
import Semantic.Api hiding (Blob)
6+
import Semantic.Git
67
import System.Exit
78

89
import SpecHelpers
@@ -24,5 +25,22 @@ spec = parallel $ do
2425
it "renders with the specified renderer" $ do
2526
output <- fmap runBuilder . runTaskOrDie $ parseTermBuilder TermSExpression [methodsBlob]
2627
output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n"
28+
29+
describe "git ls-tree parsing" $ do
30+
it "parses a git output string" $ do
31+
let input = "100644 tree abcdef\t/this/is/the/path"
32+
let expected = Right $ TreeEntry NormalMode TreeObject (OID "abcdef") "/this/is/the/path"
33+
parseEntry input `shouldBe` expected
34+
35+
it "allows whitespace in the path" $ do
36+
let input = "100644 tree 12345\t/this\n/is\t/the /path\r"
37+
let expected = Right $ TreeEntry NormalMode TreeObject (OID "12345") "/this\n/is\t/the /path\r"
38+
parseEntry input `shouldBe` expected
39+
40+
it "parses many outputs separated by \\NUL" $ do
41+
let input = "100644 tree abcdef\t/this/is/the/path\NUL120000 blob 17776\t/dev/urandom\NUL\n"
42+
let expected = [ TreeEntry NormalMode TreeObject (OID "abcdef") "/this/is/the/path", TreeEntry SymlinkMode BlobObject (OID "17776") "/dev/urandom"]
43+
parseEntries input `shouldBe` expected
44+
2745
where
2846
methodsBlob = makeBlob "def foo\nend\n" "methods.rb" Ruby mempty

0 commit comments

Comments
 (0)