1
1
mirror of https://github.com/github/semantic.git synced 2025-01-05 22:28:10 +03:00
semantic/test/Analysis/PHP/Spec.hs

40 lines
1.6 KiB
Haskell
Raw Normal View History

2018-03-20 00:53:47 +03:00
{-# LANGUAGE OverloadedLists #-}
module Analysis.PHP.Spec (spec) where
2018-04-21 17:22:09 +03:00
import Data.Abstract.Evaluatable (EvalError(..), runAnalysis)
import qualified Language.PHP.Assignment as PHP
2018-04-24 02:47:13 +03:00
import qualified Data.Language as Language
2018-04-21 17:22:09 +03:00
import SpecHelpers
spec :: Spec
spec = parallel $ do
2018-03-23 18:57:02 +03:00
describe "PHP" $ do
it "evaluates include and require" $ do
env <- environment . snd <$> evaluate "main.php"
env `shouldBe` [ ("foo", addr 0)
, ("bar", addr 1) ]
2018-03-21 02:46:32 +03:00
2018-03-23 18:57:02 +03:00
it "evaluates include_once and require_once" $ do
env <- environment . snd <$> evaluate "main_once.php"
env `shouldBe` [ ("foo", addr 0)
, ("bar", addr 1) ]
2018-03-23 18:57:02 +03:00
it "evaluates namespaces" $ do
res <- snd <$> evaluate "namespaces.php"
environment res `shouldBe` [ ("NS1", addr 0)
, ("Foo", addr 6) ]
heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "NS1" [ ("Sub1", addr 1)
, ("b", addr 4)
, ("c", addr 5)
]
heapLookup (Address (Precise 1)) (heap res) `shouldBe` ns "Sub1" [ ("Sub2", addr 2) ]
heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "Sub2" [ ("f", addr 3) ]
where
fixtures = "test/fixtures/php/analysis/"
2018-04-02 21:37:01 +03:00
evaluate entry = evalPHPProject (fixtures <> entry)
evalPHPProject path = runAnalysis @(TestEvaluating PHP.Term) <$> evaluateProjectEntry phpParser Language.PHP Nothing path