1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 00:42:33 +03:00

Merge pull request #291 from github/abolish-the-handle-binary

Don’t mangle non-ASCII characters from `git ls-tree` and `git cat-file`.
This commit is contained in:
Patrick Thomson 2019-09-30 16:25:18 -04:00 committed by GitHub
commit 30aa5cc111
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 42 additions and 20 deletions

View File

@ -22,7 +22,6 @@ import Data.Char
import Data.Either (fromRight) import Data.Either (fromRight)
import Data.Text as Text import Data.Text as Text
import Shelly hiding (FilePath) import Shelly hiding (FilePath)
import System.IO (hSetBinaryMode)
-- | git clone --bare -- | git clone --bare
clone :: Text -> FilePath -> IO () clone :: Text -> FilePath -> IO ()
@ -39,7 +38,7 @@ lsTree :: FilePath -> OID -> IO [TreeEntry]
lsTree gitDir (OID sha) = sh $ parseEntries <$> run "git" ["-C", pack gitDir, "ls-tree", "-rz", sha] lsTree gitDir (OID sha) = sh $ parseEntries <$> run "git" ["-C", pack gitDir, "ls-tree", "-rz", sha]
sh :: MonadIO m => Sh a -> m a sh :: MonadIO m => Sh a -> m a
sh = shelly . silently . onCommandHandles (initOutputHandles (`hSetBinaryMode` True)) sh = shelly . silently
-- | Parses an list of entries separated by \NUL, and on failure return [] -- | Parses an list of entries separated by \NUL, and on failure return []
parseEntries :: Text -> [TreeEntry] parseEntries :: Text -> [TreeEntry]

View File

@ -1,20 +1,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Semantic.IO.Spec (spec) where module Semantic.IO.Spec (spec) where
import Prelude hiding (readFile) import Prelude hiding (readFile)
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Data.List import Data.List
import System.Directory import Data.String
import System.IO.Temp import qualified Data.Text as Text
import Data.String import System.Directory
import System.IO.Temp
import Data.Blob import Data.Blob
import Data.Handle import Data.Handle
import SpecHelpers hiding (readFile)
import qualified Semantic.Git as Git import qualified Semantic.Git as Git
import Shelly (shelly, silently, cd, run_) import Shelly (cd, run_, shelly, silently, touchfile, writefile)
import SpecHelpers hiding (readFile)
import System.Path ((</>))
import qualified System.Path as Path import qualified System.Path as Path
import System.Path ((</>))
makeGitRepo :: FilePath -> IO () makeGitRepo :: FilePath -> IO ()
@ -22,14 +25,25 @@ makeGitRepo dir = shelly . silently $ do
cd (fromString dir) cd (fromString dir)
let git = run_ "git" let git = run_ "git"
git ["init"] git ["init"]
run_ "touch" ["foo.py", "bar.rb"] touchfile "bar.py"
git ["add", "foo.py", "bar.rb"] writefile "日本語.rb" "# coding: utf-8\n日本語 = 'hello'"
git ["add", "日本語.rb", "bar.py"]
git ["config", "user.name", "'Test'"] git ["config", "user.name", "'Test'"]
git ["config", "user.email", "'test@test.test'"] git ["config", "user.email", "'test@test.test'"]
git ["commit", "-am", "'test commit'"] git ["commit", "-am", "'test commit'"]
spec :: Spec spec :: Spec
spec = do spec = do
describe "catFile" $ do
hasGit <- runIO $ isJust <$> findExecutable "git"
when hasGit . it "should not corrupt the output of files with UTF-8 identifiers" $ do
result <- liftIO . withSystemTempDirectory "semantic-temp-git-repo" $ \dir -> do
makeGitRepo dir
trees <- Git.lsTree (dir <> "/.git") (Git.OID "HEAD")
Just it <- pure $ find (\p -> "日本語" `isInfixOf` Git.treeEntryPath p) trees
Git.catFile (dir <> "/.git") (Git.treeEntryOid it)
("日本語" `Text.isInfixOf` result) `shouldBe` True
describe "lsTree" $ do describe "lsTree" $ do
hasGit <- runIO $ isJust <$> findExecutable "git" hasGit <- runIO $ isJust <$> findExecutable "git"
when hasGit . it "should read all tree entries from a repo" $ do when hasGit . it "should read all tree entries from a repo" $ do
@ -47,8 +61,8 @@ spec = do
makeGitRepo dir makeGitRepo dir
readBlobsFromGitRepoPath (Path.absDir dir </> Path.relDir ".git") (Git.OID "HEAD") [] [] readBlobsFromGitRepoPath (Path.absDir dir </> Path.relDir ".git") (Git.OID "HEAD") [] []
let files = sortOn fileLanguage (blobFile <$> blobs) let files = sortOn fileLanguage (blobFile <$> blobs)
files `shouldBe` [ File "foo.py" Python files `shouldBe` [ File "bar.py" Python
, File "bar.rb" Ruby , File "日本語.rb" Ruby
] ]
when hasGit . it "should read from a git directory with --only" $ do when hasGit . it "should read from a git directory with --only" $ do
@ -56,18 +70,18 @@ spec = do
blobs <- liftIO . withSystemTempDirectory "semantic-temp-git-repo" $ \dir -> do blobs <- liftIO . withSystemTempDirectory "semantic-temp-git-repo" $ \dir -> do
let pdir = Path.absDir dir let pdir = Path.absDir dir
makeGitRepo dir makeGitRepo dir
readBlobsFromGitRepoPath (pdir </> Path.relDir ".git") (Git.OID "HEAD") [] [Path.relFile "foo.py"] readBlobsFromGitRepoPath (pdir </> Path.relDir ".git") (Git.OID "HEAD") [] [Path.relFile "日本語.rb"]
let files = sortOn fileLanguage (blobFile <$> blobs) let files = sortOn fileLanguage (blobFile <$> blobs)
files `shouldBe` [ File "foo.py" Python ] files `shouldBe` [ File "日本語.rb" Ruby ]
when hasGit . it "should read from a git directory with --exclude" $ do when hasGit . it "should read from a git directory with --exclude" $ do
-- This temporary directory will be cleaned after use. -- This temporary directory will be cleaned after use.
blobs <- liftIO . withSystemTempDirectory "semantic-temp-git-repo" $ \dir -> do blobs <- liftIO . withSystemTempDirectory "semantic-temp-git-repo" $ \dir -> do
makeGitRepo dir makeGitRepo dir
readBlobsFromGitRepoPath (Path.absDir dir </> Path.relDir ".git") (Git.OID "HEAD") [Path.relFile "foo.py"] [] readBlobsFromGitRepoPath (Path.absDir dir </> Path.relDir ".git") (Git.OID "HEAD") [Path.relFile "日本語.rb"] []
let files = sortOn fileLanguage (blobFile <$> blobs) let files = sortOn fileLanguage (blobFile <$> blobs)
files `shouldBe` [ File "bar.rb" Ruby ] files `shouldBe` [ File "bar.py" Python ]
describe "readFile" $ do describe "readFile" $ do
it "returns a blob for extant files" $ do it "returns a blob for extant files" $ do

View File

@ -85,6 +85,11 @@ spec = do
runTagging blob symbolsToSummarize tree `shouldBe` runTagging blob symbolsToSummarize tree `shouldBe`
[ Tag "foo" Method (Span (Pos 2 1) (Pos 3 4)) "def foo" (Just "# Public: foo") ] [ Tag "foo" Method (Span (Pos 2 1) (Pos 3 4)) "def foo" (Just "# Public: foo") ]
it "correctly tags files containing multibyte UTF-8 characters" $ do
(blob, tree) <- parseTestFile rubyParser (Path.relFile "test/fixtures/ruby/tags/unicode_identifiers.rb")
runTagging blob symbolsToSummarize tree `shouldBe`
[ Tag "日本語" Method (Span (Pos 2 1) (Pos 4 4)) "def 日本語" (Just "# coding: utf-8")]
it "produces tags for methods and classes with docs" $ do it "produces tags for methods and classes with docs" $ do
(blob, tree) <- parseTestFile rubyParser (Path.relFile "test/fixtures/ruby/tags/class_module.rb") (blob, tree) <- parseTestFile rubyParser (Path.relFile "test/fixtures/ruby/tags/class_module.rb")
runTagging blob symbolsToSummarize tree `shouldBe` runTagging blob symbolsToSummarize tree `shouldBe`

View File

@ -0,0 +1,4 @@
# coding: utf-8
def
"hello"
end