Skip to content

Commit 2036569

Browse files
author
Patrick Thomson
authored
Merge pull request github#312 from github/remove-shelly
Remove shelly in favor of streaming-bytestring and utf8-string.
2 parents d6dcfa7 + 8368950 commit 2036569

File tree

4 files changed

+45
-29
lines changed

4 files changed

+45
-29
lines changed

semantic.cabal

+3-1
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,6 @@ common dependencies
6666
, safe-exceptions ^>= 0.1.7.0
6767
, semantic-source ^>= 0.0
6868
, semilattices ^>= 0.0.0.3
69-
, shelly >= 1.5 && <2
7069
, streaming ^>= 0.2.2.0
7170
, streaming-bytestring ^>= 0.1.6
7271
, text ^>= 1.2.3.1
@@ -291,10 +290,12 @@ library
291290
, semantic-tags ^>= 0
292291
, semigroupoids ^>= 5.3.2
293292
, split ^>= 0.2.3.3
293+
, streaming-attoparsec ^>= 1.0.0.1
294294
, streaming-process ^>= 0.1
295295
, stm-chans ^>= 3.0.0.4
296296
, template-haskell ^>= 2.14
297297
, time ^>= 1.8.0.2
298+
, utf8-string ^>= 1.0.1.1
298299
, unliftio-core ^>= 0.1.2.0
299300
, unordered-containers ^>= 0.2.9.0
300301
, vector ^>= 0.12.0.2
@@ -363,6 +364,7 @@ test-suite test
363364
, hspec >= 2.6 && <3
364365
, hspec-core >= 2.6 && <3
365366
, hspec-expectations ^>= 0.8.2
367+
, shelly >= 1.5 && <2
366368
, tasty ^>= 1.2.3
367369
, tasty-golden ^>= 2.3.2
368370
, tasty-hedgehog ^>= 1.0.0.1

src/Data/Blob/IO.hs

+7-6
Original file line numberDiff line numberDiff line change
@@ -13,13 +13,14 @@ module Data.Blob.IO
1313

1414
import Prologue
1515

16-
import Data.Blob
17-
import Data.Language
18-
import Semantic.IO
19-
import qualified Source.Source as Source
20-
import qualified Semantic.Git as Git
2116
import qualified Control.Concurrent.Async as Async
17+
import Data.Blob
2218
import qualified Data.ByteString as B
19+
import Data.Language
20+
import Data.Text.Encoding (decodeUtf8)
21+
import qualified Semantic.Git as Git
22+
import Semantic.IO
23+
import qualified Source.Source as Source
2324
import qualified System.Path as Path
2425
import qualified System.Path.PartClass as Part
2526

@@ -61,7 +62,7 @@ readBlobsFromGitRepo path oid excludePaths includePaths = liftIO . fmap catMaybe
6162
= Just . sourceBlob' path lang oid <$> Git.catFile gitDir oid
6263
blobFromTreeEntry _ _ = pure Nothing
6364

64-
sourceBlob' filepath language (Git.OID oid) source = makeBlob source filepath language oid
65+
sourceBlob' filepath language (Git.OID oid) source = makeBlob source filepath language (decodeUtf8 oid)
6566

6667
readFilePair :: MonadIO m => File -> File -> m BlobPair
6768
readFilePair a b = do

src/Semantic/CLI.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ import Control.Effect.Reader
66
import Control.Exception as Exc (displayException)
77
import Data.Blob
88
import Data.Blob.IO
9+
import qualified Data.ByteString.Char8 as B
910
import Data.Handle
1011
import qualified Data.Language as Language
1112
import Data.List (intercalate)
@@ -200,7 +201,7 @@ graphCommand = command "graph" (info graphArgumentsParser (progDesc "Compute a g
200201
shaReader :: ReadM Git.OID
201202
shaReader = eitherReader parseSha
202203
where parseSha arg = if length arg == 40 || arg == "HEAD"
203-
then Right (Git.OID (T.pack arg))
204+
then Right (Git.OID (B.pack arg))
204205
else Left (arg <> " is not a valid sha1")
205206

206207
filePathReader :: ReadM File

src/Semantic/Git.hs

+33-21
Original file line numberDiff line numberDiff line change
@@ -17,62 +17,74 @@ module Semantic.Git
1717

1818
import Prologue
1919

20-
import Data.Attoparsec.Text (Parser)
21-
import Data.Attoparsec.Text as AP
20+
import Data.Attoparsec.ByteString (Parser)
21+
import Data.Attoparsec.ByteString as AP
22+
import Data.ByteString (ByteString)
23+
import Data.ByteString.Internal (w2c)
24+
import qualified Data.ByteString.UTF8 as UTF8
25+
import qualified Data.ByteString as B
2226
import qualified Data.ByteString.Streaming as ByteStream
27+
import qualified Data.Attoparsec.ByteString.Streaming as AP.Streaming
2328
import Data.Char
2429
import Data.Either (fromRight)
2530
import Data.Text as Text
26-
import Shelly hiding (FilePath)
31+
import Text.Parser.Combinators (sepEndBy)
2732
import qualified Streaming.Process
28-
import qualified System.Process as Process (proc)
33+
import qualified System.Process as Process
2934
import qualified Source.Source as Source
3035

3136
-- | git clone --bare
3237
clone :: Text -> FilePath -> IO ()
33-
clone url path = sh $ do
34-
run_ "git" ["clone", "--bare", url, pack path]
38+
clone url path = Process.callProcess "git"
39+
["clone", "--bare", Text.unpack url, path]
3540

3641
-- | Runs @git cat-file -p@. Throws 'ProcessExitedUnsuccessfully' if the
3742
-- underlying git command returns a nonzero exit code. Loads the contents
3843
-- of the file into memory all at once and strictly.
3944
catFile :: FilePath -> OID -> IO Source.Source
4045
catFile gitDir (OID oid) =
41-
let process = Process.proc "git" ["-C", gitDir, "cat-file", "-p", Text.unpack oid]
46+
let process = Process.proc "git" ["-C", gitDir, "cat-file", "-p", UTF8.toString oid]
4247
consumeStdout stream = Streaming.Process.withProcessOutput stream ByteStream.toStrict_
4348
in Source.fromUTF8 <$> Streaming.Process.withStreamProcess process consumeStdout
4449

4550
-- | git ls-tree -rz
4651
lsTree :: FilePath -> OID -> IO [TreeEntry]
47-
lsTree gitDir (OID sha) = sh $ parseEntries <$> run "git" ["-C", pack gitDir, "ls-tree", "-rz", sha]
52+
lsTree gitDir (OID sha) =
53+
let process = Process.proc "git" ["-C", gitDir, "ls-tree", "-rz", UTF8.toString sha]
54+
allEntries = (entryParser `sepEndBy` AP.word8 0) <* AP.endOfInput
55+
ignoreFailures = fmap (fromRight [] . fst)
56+
in Streaming.Process.withStreamProcess process $
57+
\stream -> Streaming.Process.withProcessOutput stream (ignoreFailures . AP.Streaming.parse allEntries)
4858

49-
sh :: MonadIO m => Sh a -> m a
50-
sh = shelly . silently
5159

5260
-- | Parses an list of entries separated by \NUL, and on failure return []
53-
parseEntries :: Text -> [TreeEntry]
61+
parseEntries :: ByteString -> [TreeEntry]
5462
parseEntries = fromRight [] . AP.parseOnly everything
5563
where
56-
everything = AP.sepBy entryParser "\NUL" <* "\NUL\n" <* AP.endOfInput
64+
everything = AP.sepBy entryParser (AP.word8 0)
5765

5866
-- | Parse the entire input with entryParser, and on failure return a default
5967
-- For testing purposes only
60-
parseEntry :: Text -> Either String TreeEntry
68+
parseEntry :: ByteString -> Either String TreeEntry
6169
parseEntry = AP.parseOnly (entryParser <* AP.endOfInput)
6270

6371
-- | Parses a TreeEntry
6472
entryParser :: Parser TreeEntry
6573
entryParser = TreeEntry
66-
<$> modeParser <* AP.char ' '
67-
<*> typeParser <* AP.char ' '
68-
<*> oidParser <* AP.char '\t'
69-
<*> (unpack <$> AP.takeWhile (/= '\NUL'))
74+
<$> modeParser <* AP.word8 space
75+
<*> typeParser <* AP.word8 space
76+
<*> oidParser <* AP.word8 tab
77+
<*> (UTF8.toString <$> AP.takeWhile (/= nul))
7078
where
71-
typeParser = AP.choice [BlobObject <$ "blob", TreeObject <$ "tree", OtherObjectType <$ AP.takeWhile isAlphaNum]
72-
modeParser = AP.choice [NormalMode <$ "100644", ExecutableMode <$ "100755", SymlinkMode <$ "120000", TreeMode <$ "040000", OtherMode <$ AP.takeWhile isAlphaNum]
73-
oidParser = OID <$> AP.takeWhile isHexDigit
79+
char = fromIntegral @Int @Word8 . ord
80+
space = char ' '
81+
tab = char '\t'
82+
nul = char '\NUL'
83+
typeParser = AP.choice [BlobObject <$ "blob", TreeObject <$ "tree", OtherObjectType <$ AP.takeWhile (isAlphaNum . w2c)]
84+
modeParser = AP.choice [NormalMode <$ "100644", ExecutableMode <$ "100755", SymlinkMode <$ "120000", TreeMode <$ "040000", OtherMode <$ AP.takeWhile (isAlphaNum . w2c)]
85+
oidParser = OID <$> AP.takeWhile (isHexDigit . w2c)
7486

75-
newtype OID = OID Text
87+
newtype OID = OID ByteString
7688
deriving (Eq, Show, Ord)
7789

7890
data ObjectMode

0 commit comments

Comments
 (0)