1
1
mirror of https://github.com/github/semantic.git synced 2024-12-29 18:06:14 +03:00

Add a test for catFile such that we ensure UTF-8 output isn't mangled.

This commit is contained in:
Patrick Thomson 2019-09-30 13:08:09 -04:00
parent d7b76d3be4
commit 9d889e9ca8

View File

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