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
|
2017-12-10 19:46:17 +03:00
|
|
|
, readFilePair
|
2018-05-07 00:30:07 +03:00
|
|
|
, testEvaluating
|
2018-05-10 16:58:38 +03:00
|
|
|
, deNamespace
|
2018-05-10 16:55:11 +03:00
|
|
|
, derefQName
|
2018-03-13 21:18:05 +03:00
|
|
|
, verbatim
|
2018-05-28 16:35:42 +03:00
|
|
|
, TermEvaluator(..)
|
2018-06-13 23:35:17 +03:00
|
|
|
, TestEff(..)
|
2018-03-13 21:18:05 +03:00
|
|
|
, Verbatim(..)
|
2018-04-27 17:11:54 +03:00
|
|
|
) where
|
2017-04-19 19:12:19 +03:00
|
|
|
|
2018-04-25 19:38:28 +03:00
|
|
|
import Analysis.Abstract.Evaluating
|
2018-05-02 22:54:11 +03:00
|
|
|
import Analysis.Abstract.Evaluating as X (EvaluatingState(..))
|
2018-05-15 19:58:05 +03:00
|
|
|
import Control.Abstract
|
2018-05-10 16:58:38 +03:00
|
|
|
import Control.Arrow ((&&&))
|
2018-05-11 01:27:10 +03:00
|
|
|
import Control.Monad.Effect.Trace as X (runIgnoringTrace, runReturningTrace)
|
2018-05-10 16:55:11 +03:00
|
|
|
import Control.Monad ((>=>))
|
2018-03-13 20:26:09 +03:00
|
|
|
import Data.Abstract.Address as X
|
2018-05-10 16:55:11 +03:00
|
|
|
import Data.Abstract.Environment as Env
|
2018-04-25 19:46:01 +03:00
|
|
|
import Data.Abstract.Evaluatable
|
2018-05-18 20:06:49 +03:00
|
|
|
import Data.Abstract.FreeVariables as X
|
2018-03-15 03:42:59 +03:00
|
|
|
import Data.Abstract.Heap as X
|
2018-03-31 02:53:23 +03:00
|
|
|
import Data.Abstract.ModuleTable as X hiding (lookup)
|
2018-05-18 20:06:35 +03:00
|
|
|
import Data.Abstract.Name as X
|
2018-05-28 15:54:33 +03:00
|
|
|
import Data.Abstract.Value (Value(..), ValueError, runValueError)
|
2018-05-07 23:56:40 +03:00
|
|
|
import Data.Bifunctor (first)
|
2018-03-13 20:59:20 +03:00
|
|
|
import Data.Blob as X
|
2018-05-14 17:18:52 +03:00
|
|
|
import Data.ByteString.Builder (toLazyByteString)
|
|
|
|
import Data.ByteString.Lazy (toStrict)
|
2018-05-16 18:38:00 +03:00
|
|
|
import Data.Project as X
|
2018-06-18 18:11:22 +03:00
|
|
|
import Data.Proxy as X
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.Functor.Listable as X
|
|
|
|
import Data.Language as X
|
2018-05-10 16:55:11 +03:00
|
|
|
import Data.List.NonEmpty as X (NonEmpty(..))
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.Range as X
|
2018-03-13 20:59:20 +03:00
|
|
|
import Data.Record as X
|
2018-06-15 18:41:38 +03:00
|
|
|
import Data.Semilattice.Lower as X
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.Source as X
|
2018-03-13 20:59:20 +03:00
|
|
|
import Data.Span as X
|
2018-06-07 05:01:48 +03:00
|
|
|
import Data.Sum
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.Term as X
|
2018-03-13 20:26:09 +03:00
|
|
|
import Parsing.Parser as X
|
2018-05-14 23:19:59 +03:00
|
|
|
import Rendering.Renderer as X hiding (error)
|
2018-04-05 16:18:20 +03:00
|
|
|
import Semantic.Diff as X
|
|
|
|
import Semantic.Parse as X
|
2018-04-05 16:38:31 +03:00
|
|
|
import Semantic.Task as X hiding (parsePackage)
|
2018-03-13 20:26:09 +03:00
|
|
|
import Semantic.Util as X
|
2018-03-13 20:59:20 +03:00
|
|
|
import System.FilePath as X
|
|
|
|
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.ByteString as X (ByteString)
|
2018-03-13 21:04:58 +03:00
|
|
|
import Data.Functor.Both as X (Both, runBothWith, both)
|
2018-03-13 21:18:05 +03:00
|
|
|
import Data.Maybe as X
|
2018-03-13 20:26:09 +03:00
|
|
|
import Data.Monoid as X (Monoid(..), First(..), Last(..))
|
|
|
|
import Data.Semigroup as X (Semigroup(..))
|
2018-03-23 17:29:01 +03:00
|
|
|
import Control.Monad as X
|
2018-03-13 02:13:21 +03:00
|
|
|
|
2018-03-13 21:10:50 +03:00
|
|
|
import Test.Hspec as X (Spec, SpecWith, context, describe, it, xit, parallel, pendingWith, around, runIO)
|
2018-03-13 20:26:09 +03:00
|
|
|
import Test.Hspec.Expectations.Pretty as X
|
2018-03-13 20:59:20 +03:00
|
|
|
import Test.Hspec.LeanCheck as X
|
|
|
|
import Test.LeanCheck as X
|
|
|
|
|
2018-03-13 20:32:25 +03:00
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified Semantic.IO as IO
|
2018-03-23 20:11:29 +03:00
|
|
|
|
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.
|
2018-03-13 21:18:05 +03:00
|
|
|
diffFilePaths :: Both FilePath -> IO ByteString
|
2018-05-15 01:39:41 +03:00
|
|
|
diffFilePaths paths = readFilePair paths >>= fmap runBuilder . runTask . runDiff SExpressionDiffRenderer . pure
|
2017-04-19 23:25:46 +03:00
|
|
|
|
|
|
|
-- | Returns an s-expression parse tree for the specified FilePath.
|
2018-03-13 21:18:05 +03:00
|
|
|
parseFilePath :: FilePath -> IO ByteString
|
2018-05-15 01:39:41 +03:00
|
|
|
parseFilePath path = (fromJust <$> IO.readFile (file path)) >>= fmap runBuilder . runTask . runParse SExpressionTermRenderer . pure
|
2017-04-21 23:56:19 +03:00
|
|
|
|
2017-12-11 19:27:13 +03:00
|
|
|
-- | Read two files to a BlobPair.
|
|
|
|
readFilePair :: Both FilePath -> IO BlobPair
|
2018-04-21 17:22:09 +03:00
|
|
|
readFilePair paths = let paths' = fmap file paths in
|
2017-12-11 19:27:13 +03:00
|
|
|
runBothWith IO.readFilePair paths'
|
2017-05-11 16:28:52 +03:00
|
|
|
|
2018-06-07 05:01:48 +03:00
|
|
|
testEvaluating :: TermEvaluator term Precise
|
2018-06-13 23:35:17 +03:00
|
|
|
Val
|
|
|
|
'[ Resumable (ValueError Precise TestEff)
|
|
|
|
, Resumable (AddressError Precise Val)
|
2018-06-07 05:01:48 +03:00
|
|
|
, Resumable EvalError, Resumable (EnvironmentError Precise)
|
|
|
|
, Resumable ResolutionError
|
2018-06-13 23:35:17 +03:00
|
|
|
, Resumable (Unspecialized Val)
|
|
|
|
, Resumable (LoadError Precise Val)
|
2018-06-07 05:01:48 +03:00
|
|
|
, Fresh
|
2018-06-13 23:35:17 +03:00
|
|
|
, State (Heap Precise Latest Val)
|
2018-06-22 20:52:21 +03:00
|
|
|
, State (ModuleTable (Maybe (Environment Precise, Precise)))
|
2018-06-07 05:01:48 +03:00
|
|
|
, Trace
|
|
|
|
]
|
2018-06-22 20:52:21 +03:00
|
|
|
[(Environment Precise, Precise)]
|
|
|
|
-> ( [String]
|
|
|
|
, ( EvaluatingState Precise Val
|
|
|
|
, Either
|
2018-06-07 05:01:48 +03:00
|
|
|
(SomeExc
|
|
|
|
(Data.Sum.Sum
|
2018-06-13 23:35:17 +03:00
|
|
|
'[ ValueError Precise TestEff
|
|
|
|
, AddressError Precise Val
|
2018-06-07 05:01:48 +03:00
|
|
|
, EvalError
|
|
|
|
, EnvironmentError Precise
|
|
|
|
, ResolutionError
|
2018-06-13 23:35:17 +03:00
|
|
|
, Unspecialized Val
|
|
|
|
, LoadError Precise Val
|
2018-06-07 05:01:48 +03:00
|
|
|
]))
|
2018-06-22 20:52:21 +03:00
|
|
|
[(Environment Precise, Value Precise TestEff)]))
|
2018-05-07 00:30:07 +03:00
|
|
|
testEvaluating
|
2018-05-07 00:38:04 +03:00
|
|
|
= run
|
2018-05-11 01:27:10 +03:00
|
|
|
. runReturningTrace
|
2018-05-07 00:38:04 +03:00
|
|
|
. evaluating
|
2018-06-06 16:45:40 +03:00
|
|
|
. fmap reassociate
|
2018-05-07 00:30:07 +03:00
|
|
|
. runLoadError
|
|
|
|
. runUnspecialized
|
|
|
|
. runResolutionError
|
2018-05-07 22:56:47 +03:00
|
|
|
. runEnvironmentError
|
2018-05-07 00:30:07 +03:00
|
|
|
. runEvalError
|
|
|
|
. runAddressError
|
2018-05-28 16:55:01 +03:00
|
|
|
. runValueError
|
2018-06-13 23:26:25 +03:00
|
|
|
. (>>= traverse deref1)
|
2018-06-13 23:35:17 +03:00
|
|
|
. runTermEvaluator @_ @_ @Val
|
|
|
|
|
|
|
|
type Val = Value Precise TestEff
|
|
|
|
newtype TestEff a = TestEff
|
2018-06-26 19:09:21 +03:00
|
|
|
{ runTestEff :: Eff '[ Exc (LoopControl Precise)
|
2018-06-26 19:00:25 +03:00
|
|
|
, Exc (Return Precise)
|
2018-06-13 23:35:17 +03:00
|
|
|
, Env Precise
|
|
|
|
, Allocator Precise Val
|
|
|
|
, Reader ModuleInfo
|
|
|
|
, Modules Precise Val
|
|
|
|
, Reader Span
|
|
|
|
, Reader PackageInfo
|
|
|
|
, Resumable (ValueError Precise TestEff)
|
|
|
|
, Resumable (AddressError Precise Val)
|
|
|
|
, Resumable EvalError
|
|
|
|
, Resumable (EnvironmentError Precise)
|
|
|
|
, Resumable ResolutionError
|
|
|
|
, Resumable (Unspecialized Val)
|
|
|
|
, Resumable (LoadError Precise Val)
|
|
|
|
, Fresh
|
|
|
|
, State (Heap Precise Latest Val)
|
2018-06-22 20:52:21 +03:00
|
|
|
, State (ModuleTable (Maybe (Environment Precise, Precise)))
|
2018-06-13 23:35:17 +03:00
|
|
|
, Trace
|
|
|
|
] a
|
|
|
|
}
|
2018-05-07 00:36:33 +03:00
|
|
|
|
2018-06-22 20:52:21 +03:00
|
|
|
deref1 (env, ptr) = runAllocator $ do
|
2018-06-07 05:23:16 +03:00
|
|
|
val <- deref ptr
|
2018-06-22 20:52:21 +03:00
|
|
|
pure (env, val)
|
2018-06-07 05:23:16 +03:00
|
|
|
|
2018-05-28 16:35:42 +03:00
|
|
|
deNamespace :: Value Precise term -> Maybe (Name, [Name])
|
2018-05-28 15:54:33 +03:00
|
|
|
deNamespace (Namespace name scope) = Just (name, Env.names scope)
|
|
|
|
deNamespace _ = Nothing
|
|
|
|
|
2018-05-28 16:35:42 +03:00
|
|
|
namespaceScope :: Value Precise term -> Maybe (Environment Precise)
|
2018-05-28 15:54:33 +03:00
|
|
|
namespaceScope (Namespace _ scope) = Just scope
|
|
|
|
namespaceScope _ = Nothing
|
2018-05-10 16:58:38 +03:00
|
|
|
|
2018-05-28 16:35:42 +03:00
|
|
|
derefQName :: Heap Precise (Cell Precise) (Value Precise term) -> NonEmpty Name -> Environment Precise -> Maybe (Value Precise term)
|
2018-05-10 16:55:11 +03:00
|
|
|
derefQName heap = go
|
2018-05-16 00:43:57 +03:00
|
|
|
where go (n1 :| ns) env = Env.lookup n1 env >>= flip heapLookup heap >>= getLast . unLatest >>= case ns of
|
2018-05-10 16:55:11 +03:00
|
|
|
[] -> Just
|
2018-05-28 15:54:33 +03:00
|
|
|
(n2 : ns) -> namespaceScope >=> go (n2 :| ns)
|
2018-05-10 16:55:11 +03:00
|
|
|
|
2018-03-13 21:18:05 +03:00
|
|
|
newtype Verbatim = Verbatim ByteString
|
2018-02-07 23:20:27 +03:00
|
|
|
deriving (Eq)
|
|
|
|
|
|
|
|
instance Show Verbatim where
|
|
|
|
show (Verbatim x) = show x
|
|
|
|
|
2018-03-13 21:18:05 +03:00
|
|
|
verbatim :: ByteString -> Verbatim
|
2018-02-07 23:20:27 +03:00
|
|
|
verbatim = Verbatim . stripWhitespace
|
|
|
|
where
|
2018-03-13 21:18:05 +03:00
|
|
|
stripWhitespace :: ByteString -> ByteString
|
2018-02-07 23:20:27 +03:00
|
|
|
stripWhitespace = B.foldl' go B.empty
|
|
|
|
where go acc x | x `B.elem` " \t\n" = acc
|
|
|
|
| otherwise = B.snoc acc x
|