mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Remove the CHECK-JQ directive.
This commit is contained in:
parent
bfec95a992
commit
f78d90aaae
@ -4,12 +4,10 @@
|
||||
module Directive ( Directive (..)
|
||||
, readDirectivesFromFile
|
||||
, describe
|
||||
, toProcess
|
||||
) where
|
||||
|
||||
import Analysis.Concrete (Concrete (..))
|
||||
import Control.Algebra
|
||||
import Control.Applicative
|
||||
import Control.Monad
|
||||
import Control.Monad.Trans.Resource (ResourceT, runResourceT)
|
||||
import Core.Core (Core)
|
||||
@ -27,7 +25,6 @@ import qualified Streaming.Prelude as Stream
|
||||
import Syntax.Term (Term)
|
||||
import qualified System.Path as Path
|
||||
import qualified System.Path.PartClass as Path.Class
|
||||
import System.Process
|
||||
import qualified Text.Parser.Token.Style as Style
|
||||
import Text.Trifecta (CharParsing, TokenParsing (..))
|
||||
import qualified Text.Trifecta as Trifecta
|
||||
@ -39,13 +36,11 @@ describe to the test suite how to query the results of a given test
|
||||
case. A directive that looks like this:
|
||||
|
||||
@
|
||||
# CHECK-JQ: has("mach")
|
||||
# CHECK-RESULT: key: value
|
||||
@
|
||||
|
||||
would, after converting the contents of the file to a Core expression,
|
||||
dump that expression to JSON and pipe said JSON to @jq -e
|
||||
'has("mach")@, which will return an error code unless the passed JSON
|
||||
is a hash containing the @"mach"@ key.
|
||||
would test that the value for @key@ in the result evaluates to the given
|
||||
concrete value.
|
||||
|
||||
This syntax was inspired by LLVM's
|
||||
[FileCheck](https://llvm.org/docs/CommandGuide/FileCheck.html). This
|
||||
@ -56,8 +51,7 @@ significantly and has been a successful strategy for the LLVM and Rust
|
||||
projects.
|
||||
|
||||
-}
|
||||
data Directive = JQ ByteString -- | @# CHECK-JQ: expr@
|
||||
| Tree (Term Core Name) -- | @# CHECK-TREE: core@
|
||||
data Directive = Tree (Term Core Name) -- | @# CHECK-TREE: core@
|
||||
| Result Text (Concrete (Term (Core.Ann Source.Span :+: Core))) -- | @# CHECK-RESULT key: expected
|
||||
| Fails -- | @# CHECK-FAILS@ fails unless translation fails.
|
||||
deriving (Eq, Show)
|
||||
@ -81,17 +75,11 @@ readDirectivesFromFile
|
||||
describe :: Directive -> String
|
||||
describe Fails = "<expect failure>"
|
||||
describe (Tree t) = Core.Pretty.showCore t
|
||||
describe (JQ b) = ByteString.unpack b
|
||||
describe (Result t e) = T.unpack t <> ": " <> show e
|
||||
|
||||
fails :: CharParsing m => m Directive
|
||||
fails = Fails <$ Trifecta.string "# CHECK-FAILS"
|
||||
|
||||
jq :: (Monad m, CharParsing m) => m Directive
|
||||
jq = do
|
||||
void $ Trifecta.string "# CHECK-JQ: "
|
||||
JQ . ByteString.pack <$> many (Trifecta.noneOf "\n")
|
||||
|
||||
tree :: (Monad m, TokenParsing m) => m Directive
|
||||
tree = do
|
||||
void $ Trifecta.string "# CHECK-TREE: "
|
||||
@ -113,12 +101,8 @@ concrete = Trifecta.choice
|
||||
]
|
||||
|
||||
directive :: (Monad m, TokenParsing m) => m Directive
|
||||
directive = Trifecta.choice [ fails, result, jq, tree ]
|
||||
directive = Trifecta.choice [ fails, result, tree ]
|
||||
|
||||
parseDirective :: ByteString -> Either String Directive
|
||||
parseDirective = Trifecta.foldResult (Left . show) Right
|
||||
. Trifecta.parseByteString (directive <* Trifecta.eof) mempty
|
||||
|
||||
toProcess :: Directive -> CreateProcess
|
||||
toProcess (JQ d) = proc "jq" ["-e", ByteString.unpack d]
|
||||
toProcess x = error ("can't call toProcess on " <> show x)
|
||||
|
@ -8,11 +8,9 @@ module Instances () where
|
||||
-- we should keep track of them in a dedicated file.
|
||||
|
||||
import Analysis.File
|
||||
import Analysis.ScopeGraph
|
||||
import Core.Name (Name (..))
|
||||
import Data.Aeson
|
||||
import qualified Data.Map as Map
|
||||
import Data.Text (Text, pack)
|
||||
import Data.Text (pack)
|
||||
import qualified System.Path as Path
|
||||
|
||||
deriving newtype instance ToJSON Name
|
||||
@ -27,21 +25,3 @@ instance ToJSON a => ToJSON (File a) where
|
||||
|
||||
instance ToJSON Path.AbsRelFile where
|
||||
toJSON p = toJSON (pack (Path.toString p))
|
||||
|
||||
instance ToJSON Ref where
|
||||
toJSON (Ref path span) = object
|
||||
[ "kind" .= ("ref" :: Text)
|
||||
, "path" .= path
|
||||
, "span" .= span
|
||||
]
|
||||
|
||||
instance ToJSON Decl where
|
||||
toJSON Decl{declSymbol, declPath, declSpan} = object
|
||||
[ "kind" .= ("decl" :: Text)
|
||||
, "symbol" .= declSymbol
|
||||
, "path" .= declPath
|
||||
, "span" .= declSpan
|
||||
]
|
||||
|
||||
instance ToJSON ScopeGraph where
|
||||
toJSON (ScopeGraph sc) = toJSON . Map.mapKeys declSymbol $ sc
|
||||
|
@ -5,23 +5,17 @@ module Main (main) where
|
||||
import Analysis.Concrete (Concrete)
|
||||
import qualified Analysis.Concrete as Concrete
|
||||
import Analysis.File
|
||||
import Analysis.ScopeGraph
|
||||
import Control.Algebra
|
||||
import Control.Carrier.Fail.Either
|
||||
import Control.Carrier.Reader
|
||||
import Control.Monad hiding (fail)
|
||||
import Control.Monad.Catch
|
||||
import Control.Monad.IO.Class
|
||||
import Core.Core
|
||||
import qualified Core.Eval as Eval
|
||||
import Core.Name
|
||||
import qualified Core.Parser
|
||||
import Core.Pretty
|
||||
import qualified Data.Aeson as Aeson
|
||||
import qualified Data.Aeson.Encode.Pretty as Aeson
|
||||
import qualified Data.ByteString.Char8 as ByteString
|
||||
import qualified Data.ByteString.Lazy.Char8 as ByteString.Lazy
|
||||
import qualified Data.ByteString.Streaming.Char8 as ByteStream
|
||||
import Data.Foldable
|
||||
import Data.Function
|
||||
import qualified Data.IntMap as IntMap
|
||||
@ -34,8 +28,6 @@ import qualified Language.Python.Core as Py
|
||||
import Language.Python.Failure
|
||||
import Prelude hiding (fail)
|
||||
import Source.Span
|
||||
import Streaming
|
||||
import qualified Streaming.Process
|
||||
import Syntax.Term
|
||||
import Syntax.Var (closed)
|
||||
import System.Directory
|
||||
@ -43,7 +35,6 @@ import System.Exit
|
||||
import System.Path ((</>))
|
||||
import qualified System.Path as Path
|
||||
import qualified System.Path.Directory as Path
|
||||
import Text.Show.Pretty (ppShow)
|
||||
import qualified Text.Trifecta as Trifecta
|
||||
import qualified TreeSitter.Python as TSP
|
||||
import qualified TreeSitter.Unmarshal as TS
|
||||
@ -62,32 +53,6 @@ parsePrelude = do
|
||||
Right r -> pure r
|
||||
Left s -> HUnit.assertFailure ("Couldn't parse prelude: " <> s)
|
||||
|
||||
assertJQExpressionSucceeds :: Show a => Directive.Directive -> a -> Term (Ann Span :+: Core) Name -> HUnit.Assertion
|
||||
assertJQExpressionSucceeds directive tree core = do
|
||||
prelude <- parsePrelude
|
||||
let allTogether = (named' "__semantic_prelude" :<- prelude) >>>= core
|
||||
|
||||
bod <- case scopeGraph Eval.eval [File (Path.absRel "<interactive>") (Span (Pos 1 1) (Pos 1 1)) allTogether] of
|
||||
(heap, [File _ _ (Right result)]) -> pure $ Aeson.object
|
||||
[ "scope" Aeson..= heap
|
||||
, "heap" Aeson..= result
|
||||
]
|
||||
other -> HUnit.assertFailure ("Couldn't run scope dumping mechanism: " <> showCore (stripAnnotations allTogether) <> "\n" <> show other)
|
||||
|
||||
let ignore = ByteStream.effects . hoist ByteStream.effects
|
||||
sgJSON = ByteStream.fromLazy $ Aeson.encode bod
|
||||
jqPipeline = Streaming.Process.withStreamingProcess (Directive.toProcess directive) sgJSON ignore
|
||||
errorMsg = "jq(1) returned non-zero exit code"
|
||||
dirMsg = "jq expression: " <> show directive
|
||||
jsonMsg = "JSON value: " <> ByteString.Lazy.unpack (Aeson.encodePretty bod)
|
||||
astMsg = "AST (pretty): " <> ppShow tree
|
||||
treeMsg = "Core expr (pretty): " <> showCore (stripAnnotations core)
|
||||
treeMsg' = "Core expr (Show): " <> ppShow (stripAnnotations core)
|
||||
|
||||
|
||||
catch @_ @Streaming.Process.ProcessExitedUnsuccessfully jqPipeline $ \err -> do
|
||||
HUnit.assertFailure (unlines [errorMsg, dirMsg, jsonMsg, astMsg, treeMsg, treeMsg', show err])
|
||||
|
||||
-- handles CHECK-RESULT directives
|
||||
assertEvaluatesTo :: Term (Ann Span :+: Core) Name -> Text -> Concrete (Term (Ann Span :+: Core)) -> HUnit.Assertion
|
||||
assertEvaluatesTo core k val = do
|
||||
@ -137,7 +102,6 @@ checkPythonFile fp = HUnit.testCaseSteps (Path.toString fp) $ \step -> withFroze
|
||||
(Right (Left err), _) -> HUnit.assertFailure ("Compilation failed: " <> err)
|
||||
(Right (Right _), Directive.Fails) -> HUnit.assertFailure "Expected translation to fail"
|
||||
(Right (Right item), Directive.Result k v) -> assertEvaluatesTo item k v
|
||||
(Right (Right item), Directive.JQ _) -> assertJQExpressionSucceeds directive result item
|
||||
(Right (Right item), Directive.Tree t) -> assertTreeEqual (stripAnnotations item) t
|
||||
|
||||
milestoneFixtures :: IO Tasty.TestTree
|
||||
|
@ -1 +0,0 @@
|
||||
# CHECK-JQ: .scope | has("__semantic_prelude") # prelude should be present
|
@ -1,2 +1 @@
|
||||
# CHECK-JQ: .scope | has("__semantic_prelude")
|
||||
pass
|
||||
|
@ -1,4 +1,3 @@
|
||||
# CHECK-JQ: .scope | has("hello") and has("goodbye")
|
||||
# CHECK-TREE: { hello <- #unit; goodbye <- #unit; #record { hello: hello, goodbye: goodbye }}
|
||||
# CHECK-RESULT hello: #unit
|
||||
hello = ()
|
||||
|
@ -1,5 +1,3 @@
|
||||
# CHECK-JQ: .scope.zilch[0].b[0].span == { start: [8, 8], end: [ 8, 16 ] }
|
||||
# CHECK-JQ: .scope.result[0].a[0].span == { start: [5, 8], end: [ 5, 16 ] }
|
||||
|
||||
def const(a, b):
|
||||
def result():
|
||||
|
Loading…
Reference in New Issue
Block a user