2020-01-24 23:41:49 +03:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
2018-06-29 23:17:27 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
2018-04-27 17:11:54 +03:00
|
|
|
module SpecHelpers
|
|
|
|
( module X
|
2018-05-14 17:27:45 +03:00
|
|
|
, runBuilder
|
2018-03-10 03:24:23 +03:00
|
|
|
, diffFilePaths
|
2017-04-20 02:33:27 +03:00
|
|
|
, parseFilePath
|
2019-05-22 05:28:32 +03:00
|
|
|
, readFilePathPair
|
2019-02-02 02:04:23 +03:00
|
|
|
, runTaskOrDie
|
2019-10-01 00:59:23 +03:00
|
|
|
, runParseWithConfig
|
2019-02-02 02:04:23 +03:00
|
|
|
, TaskSession(..)
|
2018-05-07 00:30:07 +03:00
|
|
|
, testEvaluating
|
2018-06-21 21:52:08 +03:00
|
|
|
, toList
|
2018-07-09 21:26:15 +03:00
|
|
|
, Config
|
|
|
|
, LogQueue
|
|
|
|
, StatQueue
|
2018-11-08 20:55:42 +03:00
|
|
|
, lookupDeclaration
|
2018-12-04 19:24:01 +03:00
|
|
|
, lookupMembers
|
|
|
|
, EdgeLabel(..)
|
2019-10-23 17:16:46 +03:00
|
|
|
, TestEvaluatingResult
|
2019-10-23 17:27:38 +03:00
|
|
|
, TestEvaluatingState
|
2019-10-22 23:16:47 +03:00
|
|
|
, evaluateProject
|
2018-04-27 17:11:54 +03:00
|
|
|
) where
|
2017-04-19 19:12:19 +03:00
|
|
|
|
2020-01-24 23:41:49 +03:00
|
|
|
import qualified Analysis.File as File
|
|
|
|
import Control.Abstract
|
|
|
|
import Control.Carrier.Fresh.Strict
|
|
|
|
import Control.Carrier.Lift
|
|
|
|
import Control.Carrier.Parse.Simple
|
|
|
|
import Control.Carrier.Reader as X
|
|
|
|
import Control.Carrier.Resumable.Either
|
|
|
|
import Control.Carrier.State.Strict
|
2019-11-09 06:43:09 +03:00
|
|
|
import qualified Control.Carrier.Trace.Ignoring as Trace.Ignoring
|
2020-01-24 23:41:49 +03:00
|
|
|
import Control.Exception (displayException)
|
|
|
|
import Control.Monad as X
|
|
|
|
import Data.Abstract.Address.Precise as X
|
|
|
|
import Data.Abstract.Evaluatable
|
|
|
|
import Data.Abstract.FreeVariables as X
|
2019-10-22 23:00:35 +03:00
|
|
|
import qualified Data.Abstract.Heap as Heap
|
2020-01-24 23:41:49 +03:00
|
|
|
import Data.Abstract.Module as X
|
|
|
|
import Data.Abstract.ModuleTable as X hiding (lookup)
|
|
|
|
import Data.Abstract.Name as X
|
2019-10-22 23:00:35 +03:00
|
|
|
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
2020-01-24 23:41:49 +03:00
|
|
|
import Data.Abstract.Value.Concrete (Value (..), ValueError, runValueError)
|
|
|
|
import Data.Blob as X
|
|
|
|
import Data.Blob.IO as X
|
|
|
|
import Data.ByteString as X (ByteString)
|
|
|
|
import Data.ByteString.Builder (Builder, toLazyByteString)
|
|
|
|
import Data.ByteString.Lazy (toStrict)
|
|
|
|
import Data.Edit as X
|
|
|
|
import Data.Foldable (toList)
|
|
|
|
import Data.Functor.Listable as X
|
|
|
|
import Data.Language as X hiding (Precise)
|
|
|
|
import Data.List.NonEmpty as X (NonEmpty (..))
|
|
|
|
import Data.Maybe as X
|
|
|
|
import Data.Monoid as X (First (..), Last (..), Monoid (..))
|
|
|
|
import Data.Project as X
|
|
|
|
import Data.Proxy as X
|
|
|
|
import Data.Semigroup as X (Semigroup (..))
|
|
|
|
import Data.Semilattice.Lower as X
|
|
|
|
import Data.String
|
|
|
|
import Data.Sum as Sum
|
|
|
|
import Data.Term as X
|
|
|
|
import Data.Traversable as X (for)
|
|
|
|
import Debug.Trace as X (traceM, traceShowM)
|
|
|
|
import Parsing.Parser as X
|
|
|
|
import Semantic.Api hiding (Blob, BlobPair, File)
|
|
|
|
import Semantic.Config (Config (..), optionsLogLevel)
|
|
|
|
import Semantic.Graph (analysisParsers, runHeap, runScopeGraph)
|
|
|
|
import Semantic.Task as X
|
|
|
|
import Semantic.Telemetry (LogQueue, StatQueue)
|
|
|
|
import Semantic.Util as X
|
|
|
|
import Source.Range as X hiding (end, point, start)
|
|
|
|
import Source.Source as X (Source)
|
|
|
|
import Source.Span as X hiding (HasSpan (..), end, point, start)
|
|
|
|
import System.Exit (die)
|
2019-10-22 23:00:35 +03:00
|
|
|
import qualified System.Path as Path
|
2020-01-24 23:41:49 +03:00
|
|
|
import Test.Hspec as X (Spec, SpecWith, around, context, describe, it, parallel, pendingWith, runIO, xit)
|
|
|
|
import Test.Hspec.Expectations as X
|
|
|
|
import Test.Hspec.LeanCheck as X
|
|
|
|
import Test.LeanCheck as X
|
|
|
|
import Unsafe.Coerce (unsafeCoerce)
|
2018-03-13 20:59:20 +03:00
|
|
|
|
2019-06-15 07:53:02 +03:00
|
|
|
runBuilder :: Builder -> ByteString
|
2018-05-14 17:27:45 +03:00
|
|
|
runBuilder = toStrict . toLazyByteString
|
2018-05-14 17:31:40 +03:00
|
|
|
|
2017-04-19 23:25:46 +03:00
|
|
|
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
2019-10-18 17:45:59 +03:00
|
|
|
diffFilePaths :: TaskSession -> Path.RelFile -> Path.RelFile -> IO ByteString
|
|
|
|
diffFilePaths session p1 p2 = do
|
|
|
|
blobs <- readFilePathPair p1 p2
|
2019-10-18 17:29:43 +03:00
|
|
|
builder <- runTask session (runParse (configTreeSitterParseTimeout (config session)) (parseDiffBuilder DiffSExpression [ blobs ]))
|
|
|
|
either (die . displayException) (pure . runBuilder) builder
|
2017-04-19 23:25:46 +03:00
|
|
|
|
2019-09-20 18:52:39 +03:00
|
|
|
-- | Returns an s-expression parse tree for the specified path.
|
|
|
|
parseFilePath :: TaskSession -> Path.RelFile -> IO (Either SomeException ByteString)
|
2019-06-05 21:28:28 +03:00
|
|
|
parseFilePath session path = do
|
2020-01-24 23:41:49 +03:00
|
|
|
blob <- readBlobFromFile (File.fromPath path)
|
2019-10-03 00:32:09 +03:00
|
|
|
res <- runTask session . runParse (configTreeSitterParseTimeout (config session)) . runReader defaultLanguageModes $ parseTermBuilder TermSExpression (toList blob)
|
2019-06-05 21:28:28 +03:00
|
|
|
pure (runBuilder <$> res)
|
2017-04-21 23:56:19 +03:00
|
|
|
|
2019-11-09 06:43:09 +03:00
|
|
|
runParseWithConfig :: Has (Reader Config) sig m => ParseC m a -> m a
|
2019-10-01 00:59:23 +03:00
|
|
|
runParseWithConfig task = asks configTreeSitterParseTimeout >>= \ timeout -> runParse timeout task
|
|
|
|
|
2017-12-11 19:27:13 +03:00
|
|
|
-- | Read two files to a BlobPair.
|
2019-10-18 17:45:59 +03:00
|
|
|
readFilePathPair :: Path.RelFile -> Path.RelFile -> IO BlobPair
|
2020-01-24 23:41:49 +03:00
|
|
|
readFilePathPair p1 p2 = readFilePair (File.fromPath p1) (File.fromPath p2)
|
2017-05-11 16:28:52 +03:00
|
|
|
|
2019-02-16 01:55:15 +03:00
|
|
|
-- Run a Task and call `die` if it returns an Exception.
|
2019-10-01 00:59:23 +03:00
|
|
|
runTaskOrDie :: ParseC TaskC a -> IO a
|
|
|
|
runTaskOrDie task = runTaskWithOptions defaultOptions { optionsLogLevel = Nothing } (runParseWithConfig task) >>= either (die . displayException) pure
|
2019-02-02 02:04:23 +03:00
|
|
|
|
2018-10-24 17:01:49 +03:00
|
|
|
type TestEvaluatingC term
|
2019-03-06 18:12:10 +03:00
|
|
|
= ResumableC (BaseError (AddressError Precise (Val term)))
|
2019-10-23 16:39:54 +03:00
|
|
|
( ResumableC (BaseError (ValueError term Precise))
|
2019-03-06 18:12:10 +03:00
|
|
|
( ResumableC (BaseError ResolutionError)
|
|
|
|
( ResumableC (BaseError (EvalError term Precise (Val term)))
|
|
|
|
( ResumableC (BaseError (HeapError Precise))
|
|
|
|
( ResumableC (BaseError (ScopeError Precise))
|
|
|
|
( ResumableC (BaseError (UnspecializedError Precise (Val term)))
|
|
|
|
( ResumableC (BaseError (LoadError Precise (Val term)))
|
|
|
|
( StateC (Heap Precise Precise (Val term))
|
|
|
|
( StateC (ScopeGraph Precise)
|
|
|
|
( FreshC
|
2019-11-09 06:43:09 +03:00
|
|
|
( Trace.Ignoring.TraceC
|
2019-03-06 18:12:10 +03:00
|
|
|
( LiftC IO))))))))))))
|
2018-09-21 21:42:57 +03:00
|
|
|
type TestEvaluatingErrors term
|
2018-11-07 22:09:18 +03:00
|
|
|
= '[ BaseError (AddressError Precise (Val term))
|
2019-10-23 16:39:54 +03:00
|
|
|
, BaseError (ValueError term Precise)
|
2018-09-21 21:42:57 +03:00
|
|
|
, BaseError ResolutionError
|
2018-12-12 00:51:21 +03:00
|
|
|
, BaseError (EvalError term Precise (Val term))
|
2018-11-07 22:09:18 +03:00
|
|
|
, BaseError (HeapError Precise)
|
|
|
|
, BaseError (ScopeError Precise)
|
2018-12-10 20:40:03 +03:00
|
|
|
, BaseError (UnspecializedError Precise (Val term))
|
2018-11-07 22:09:18 +03:00
|
|
|
, BaseError (LoadError Precise (Val term))
|
2018-09-21 21:42:57 +03:00
|
|
|
]
|
2019-10-23 17:27:38 +03:00
|
|
|
type TestEvaluatingState term a
|
2019-10-23 17:16:46 +03:00
|
|
|
= ( ScopeGraph Precise
|
2019-10-23 17:27:38 +03:00
|
|
|
, ( Heap Precise Precise (Val term)
|
2019-10-23 17:16:46 +03:00
|
|
|
, Either (SomeError (Sum.Sum (TestEvaluatingErrors term))) a
|
|
|
|
)
|
|
|
|
)
|
2019-10-23 17:27:38 +03:00
|
|
|
type TestEvaluatingResult term = ModuleTable (Module (ModuleResult Precise (Val term)))
|
2018-12-05 20:12:13 +03:00
|
|
|
testEvaluating :: Evaluator term Precise (Val term) (TestEvaluatingC term) a
|
2019-10-23 17:27:38 +03:00
|
|
|
-> IO (TestEvaluatingState term a)
|
2018-05-07 00:30:07 +03:00
|
|
|
testEvaluating
|
2018-06-21 21:52:08 +03:00
|
|
|
= runM
|
2019-11-09 06:43:09 +03:00
|
|
|
. Trace.Ignoring.runTrace
|
|
|
|
. fmap snd
|
|
|
|
. runFresh 0
|
2018-10-24 17:05:22 +03:00
|
|
|
. runEvaluator
|
2018-11-29 02:47:10 +03:00
|
|
|
. runScopeGraph
|
|
|
|
. runHeap
|
2018-06-06 16:45:40 +03:00
|
|
|
. fmap reassociate
|
2018-10-24 16:59:57 +03:00
|
|
|
. runLoadError
|
|
|
|
. runUnspecialized
|
2018-11-07 22:09:18 +03:00
|
|
|
. runScopeError
|
|
|
|
. runHeapError
|
2018-10-24 16:59:57 +03:00
|
|
|
. runEvalError
|
|
|
|
. runResolutionError
|
2018-11-07 22:09:18 +03:00
|
|
|
. runValueError
|
2018-10-24 16:59:57 +03:00
|
|
|
. runAddressError
|
2018-06-13 23:35:17 +03:00
|
|
|
|
2018-09-26 00:38:05 +03:00
|
|
|
type Val term = Value term Precise
|
2018-05-07 00:36:33 +03:00
|
|
|
|
2019-10-23 17:34:10 +03:00
|
|
|
evaluateProject :: (HasPrelude lang, SLanguage lang) => TaskSession -> Proxy lang -> [FilePath] -> IO (TestEvaluatingState term (TestEvaluatingResult term))
|
2019-10-23 19:17:10 +03:00
|
|
|
evaluateProject session proxy = case parserForLanguage analysisParsers lang of
|
2019-10-23 17:02:33 +03:00
|
|
|
Just (SomeParser parser) -> unsafeCoerce . testEvaluating <=< evaluateProject' session proxy parser
|
2019-10-22 23:16:47 +03:00
|
|
|
_ -> error $ "analysis not supported for " <> show lang
|
|
|
|
where lang = reflect proxy
|
|
|
|
|
2018-06-07 05:23:16 +03:00
|
|
|
|
2018-12-04 19:24:01 +03:00
|
|
|
members :: EdgeLabel
|
|
|
|
-> Heap Precise Precise (Value term Precise)
|
|
|
|
-> ScopeGraph Precise
|
|
|
|
-> Value term Precise
|
|
|
|
-> Maybe [Name]
|
2019-01-16 00:54:00 +03:00
|
|
|
members edgeLabel heap scopeGraph (Data.Abstract.Value.Concrete.Object frame) = frameNames [ edgeLabel ] heap scopeGraph frame
|
2018-12-04 19:24:01 +03:00
|
|
|
members edgeLabel heap scopeGraph (Class _ _ frame) = frameNames [ edgeLabel ] heap scopeGraph frame
|
|
|
|
members _ _ _ _ = Nothing
|
2018-11-26 21:06:01 +03:00
|
|
|
|
2018-12-04 19:24:01 +03:00
|
|
|
frameNames :: [ EdgeLabel ]
|
|
|
|
-> Heap Precise Precise (Value term Precise)
|
2018-11-26 21:06:01 +03:00
|
|
|
-> ScopeGraph Precise
|
|
|
|
-> Precise
|
|
|
|
-> Maybe [ Name ]
|
2018-12-04 19:24:01 +03:00
|
|
|
frameNames edge heap scopeGraph frame = do
|
2018-11-26 21:06:01 +03:00
|
|
|
scopeAddress <- Heap.scopeLookup frame heap
|
|
|
|
scope <- ScopeGraph.lookupScope scopeAddress scopeGraph
|
2018-12-05 20:44:52 +03:00
|
|
|
pure (unDeclaration <$> toList (ScopeGraph.declarationNames edge scope scopeGraph))
|
2018-11-08 02:27:56 +03:00
|
|
|
|
2018-12-04 19:24:01 +03:00
|
|
|
lookupMembers :: Name -> EdgeLabel -> (Precise, Precise) -> Heap Precise Precise (Value term Precise) -> ScopeGraph Precise -> Maybe [ Name ]
|
|
|
|
lookupMembers name edgeLabel scopeAndFrame heap scopeGraph =
|
|
|
|
(lookupDeclaration name scopeAndFrame heap scopeGraph >>= members edgeLabel heap scopeGraph . Prelude.head)
|
2018-11-08 02:27:56 +03:00
|
|
|
|
2018-11-29 01:27:42 +03:00
|
|
|
lookupDeclaration :: Name -> (Precise, Precise) -> Heap Precise Precise (Value term Precise) -> ScopeGraph Precise -> Maybe [ Value term Precise ]
|
2018-11-29 02:47:10 +03:00
|
|
|
lookupDeclaration name (currentScope, currentFrame) heap scopeGraph = do
|
|
|
|
path <- ScopeGraph.lookupScopePath name currentScope scopeGraph
|
|
|
|
frameAddress <- Heap.lookupFrameAddress path currentFrame heap
|
2019-01-17 05:20:33 +03:00
|
|
|
toList <$> Heap.getSlotValue (Slot frameAddress (Heap.pathPosition path)) heap
|