1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 07:55:12 +03:00

Fix up PHP eval specs

This commit is contained in:
Timothy Clem 2018-04-02 11:37:01 -07:00
parent eb883770df
commit 55fa6480d6
3 changed files with 9 additions and 11 deletions

View File

@ -59,7 +59,7 @@ tracePythonFile path = runAnalysis @(Tracing [] (Evaluating Python.Term Value))
evaluateDeadTracePythonFile path = runAnalysis @(DeadCode (Tracing [] (Evaluating Python.Term Value))) . evaluateModule <$> parseFile pythonParser Nothing path
-- PHP
evalPHP = evaluateProject phpParser ["php"]
evalPHPProject = evaluateProject phpParser ["php"]
evalPHPFile = evaluateFile phpParser
-- TypeScript

View File

@ -1,7 +1,6 @@
{-# LANGUAGE OverloadedLists #-}
module Analysis.PHP.Spec (spec) where
import Data.Abstract.Value
import SpecHelpers
@ -31,11 +30,5 @@ spec = parallel $ do
heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "Sub2" [ ("f", addr 3) ]
where
ns n = Just . Latest . Just . injValue . Namespace n
addr = Address . Precise
fixtures = "test/fixtures/php/analysis/"
evaluate entry = evaluateFiles phpParser (takeDirectory entry)
[ fixtures <> entry
, fixtures <> "foo.php"
, fixtures <> "bar.php"
]
evaluate entry = evalPHPProject (fixtures <> entry)

View File

@ -5,6 +5,8 @@ module SpecHelpers (
, parseFilePath
, readFilePair
, readFileVerbatim
, addr
, ns
, verbatim
, Verbatim(..)
, ) where
@ -44,7 +46,7 @@ import Test.LeanCheck as X
import qualified Data.ByteString as B
import qualified Semantic.IO as IO
import Data.Abstract.Value
-- | Returns an s-expression formatted diff for the specified FilePath pair.
diffFilePaths :: Both FilePath -> IO ByteString
@ -52,7 +54,7 @@ diffFilePaths paths = readFilePair paths >>= runTask . diffBlobPair SExpressionD
-- | Returns an s-expression parse tree for the specified FilePath.
parseFilePath :: FilePath -> IO ByteString
parseFilePath path = IO.readFile path (IO.languageForFilePath path) >>= pure . fromJust >>= runTask . parseBlob SExpressionTermRenderer
parseFilePath path = (fromJust <$> IO.readFile path (IO.languageForFilePath path)) >>= runTask . parseBlob SExpressionTermRenderer
-- | Read two files to a BlobPair.
readFilePair :: Both FilePath -> IO BlobPair
@ -62,6 +64,9 @@ readFilePair paths = let paths' = fmap (\p -> (p, IO.languageForFilePath p)) pat
readFileVerbatim :: FilePath -> IO Verbatim
readFileVerbatim = fmap verbatim . B.readFile
ns n = Just . Latest . Just . injValue . Namespace n
addr = Address . Precise
newtype Verbatim = Verbatim ByteString
deriving (Eq)