1
1
mirror of https://github.com/github/semantic.git synced 2024-11-26 09:07:39 +03:00

Getting some of these tests to work

This commit is contained in:
Patrick Thomson 2020-06-10 11:11:33 -04:00
parent 1ec68909f7
commit 1a6447c18e
4 changed files with 25 additions and 17 deletions

View File

@ -53,6 +53,7 @@ stack_snapshot(
"array",
"async",
"attoparsec",
"bazel-runfiles",
"bifunctors",
"bytestring",
"containers",

View File

@ -137,8 +137,8 @@ haskell_test(
),
compiler_flags = STANDARD_GHC_WARNINGS + [
"-XStrictData",
"-Wno-missing-deriving-strategies",
],
data = glob(include = ["test/fixtures/**/*.json"]),
src_strip_prefix = "test",
deps = semantic_common_dependencies + [
":base",
@ -148,6 +148,7 @@ haskell_test(
"//semantic-tags:lib",
"@stackage//:Glob",
"@stackage//:HUnit",
"@stackage//:bazel-runfiles",
"@stackage//:bifunctors",
"@stackage//:hedgehog",
"@stackage//:hspec",

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ImplicitParams #-}
module Semantic.IO.Spec (spec) where
@ -9,13 +10,20 @@ import Data.Blob as Blob
import Data.Handle
import SpecHelpers
import qualified System.Path as Path
import qualified Bazel.Runfiles as Bazel
spec :: Spec
spec :: (?runfiles :: Bazel.Runfiles) => Spec
spec = do
let fp x = Bazel.rlocation ?runfiles ("semantic/semantic/" <> x)
let blobsFromFilePath path = do
h <- openFileForReading (fp path)
blobs <- readBlobPairsFromHandle h
pure blobs
describe "readFile" $ do
it "returns a blob for extant files" $ do
Just blob <- readBlobFromFile (File (Path.absRel "semantic.cabal") lowerBound Unknown)
blobFilePath blob `shouldBe` "semantic.cabal"
let path = Bazel.rlocation ?runfiles "semantic/semantic/test/fixtures/cli/diff.json"
Just blob <- readBlobFromFile (File (Path.absRel path) lowerBound Unknown)
blobFilePath blob `shouldBe` path
it "throws for absent files" $ do
readBlobFromFile (File (Path.absRel "/dev/doesnotexist") lowerBound Unknown) `shouldThrow` anyIOException
@ -45,7 +53,7 @@ spec = do
it "returns blobs for unsupported language" $ do
h <- openFileForReading "test/fixtures/cli/diff-unsupported-language.json"
h <- openFileForReading (fp "test/fixtures/cli/diff-unsupported-language.json")
blobs <- readBlobPairsFromHandle h
let b' = Blob.fromSource (Path.relFile "test.kt") Unknown "fun main(args: Array<String>) {\nprintln(\"hi\")\n}\n"
blobs `shouldBe` [Insert b']
@ -55,32 +63,27 @@ spec = do
blobs `shouldBe` [Compare a b]
it "throws on blank input" $ do
h <- openFileForReading "test/fixtures/cli/blank.json"
h <- openFileForReading (fp "test/fixtures/cli/blank.json")
readBlobPairsFromHandle h `shouldThrow` jsonException
it "throws if language field not given" $ do
h <- openFileForReading "test/fixtures/cli/diff-no-language.json"
h <- openFileForReading (fp "test/fixtures/cli/diff-no-language.json")
readBlobsFromHandle h `shouldThrow` jsonException
it "throws if null on before and after" $ do
h <- openFileForReading "test/fixtures/cli/diff-null-both-sides.json"
h <- openFileForReading (fp "test/fixtures/cli/diff-null-both-sides.json")
readBlobPairsFromHandle h `shouldThrow` jsonException
describe "readBlobsFromHandle" $ do
it "returns blobs for valid JSON encoded parse input" $ do
h <- openFileForReading "test/fixtures/cli/parse.json"
h <- openFileForReading (fp "test/fixtures/cli/parse.json")
blobs <- readBlobsFromHandle h
let a = Blob.fromSource (Path.relFile "method.rb") Ruby "def foo; end"
blobs `shouldBe` [a]
it "throws on blank input" $ do
h <- openFileForReading "test/fixtures/cli/blank.json"
h <- openFileForReading (fp "test/fixtures/cli/blank.json")
readBlobsFromHandle h `shouldThrow` jsonException
where blobsFromFilePath path = do
h <- openFileForReading path
blobs <- readBlobPairsFromHandle h
pure blobs
jsonException :: Selector InvalidJSONException
jsonException = const True

View File

@ -30,6 +30,7 @@ import qualified Semantic.Spec
import qualified Semantic.CLI.Spec
import qualified Semantic.IO.Spec
import qualified Semantic.Stat.Spec
import qualified Bazel.Runfiles as Bazel
import Semantic.Config (defaultOptions, optionsLogLevel)
import Semantic.Task (withOptions, TaskSession(..))
import Test.Hspec
@ -49,7 +50,7 @@ tests =
-- We can't bring this out of the IO monad until we divest
-- from hspec, since testSpec operates in IO.
allTests :: (?session :: TaskSession) => IO TestTree
allTests :: (?session :: TaskSession, ?runfiles :: Bazel.Runfiles) => IO TestTree
allTests = do
asTastySpecs <- Tasty.testSpecs legacySpecs
let allSpecs = tests <> asTastySpecs
@ -61,7 +62,7 @@ allTests = do
-- documentation: "hspec and tasty serve similar purposes; consider
-- using one or the other.") Instead, create a new TestTree value
-- in your spec module and add it to the above 'tests' list.
legacySpecs :: (?session :: TaskSession) => Spec
legacySpecs :: (?session :: TaskSession, ?runfiles :: Bazel.Runfiles) => Spec
legacySpecs = parallel $ do
describe "Analysis.Go" Analysis.Go.Spec.spec
describe "Analysis.PHP" Analysis.PHP.Spec.spec
@ -88,6 +89,8 @@ legacySpecs = parallel $ do
main :: IO ()
main = do
runfiles <- Bazel.create
withOptions defaultOptions { optionsLogLevel = Nothing } $ \ config logger statter ->
let ?session = TaskSession config "-" False logger statter
?runfiles = runfiles
in allTests >>= defaultMain