1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00
semantic/test/SpecHelpers.hs

187 lines
6.8 KiB
Haskell
Raw Normal View History

2018-06-29 23:17:27 +03:00
{-# OPTIONS_GHC -fno-warn-orphans #-}
module SpecHelpers
( module X
2018-05-14 17:27:45 +03:00
, runBuilder
, diffFilePaths
, parseFilePath
2017-12-10 19:46:17 +03:00
, readFilePair
, testEvaluating
, deNamespace
, derefQName
, verbatim
, TermEvaluator(..)
, Verbatim(..)
, toList
, Config
, LogQueue
, StatQueue
) where
2018-05-15 19:58:05 +03:00
import Control.Abstract
import Control.Arrow ((&&&))
import Control.Monad.Effect.Trace as X (runIgnoringTrace, runReturningTrace)
import Control.Monad ((>=>))
2018-08-10 20:46:24 +03:00
import Data.Abstract.Address.Precise as X
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
import Data.Abstract.Module 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
import Data.Abstract.Value.Concrete (Value(..), ValueError, runValueError, materializeEnvironment)
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)
import Data.Project as X
2018-06-18 18:11:22 +03:00
import Data.Proxy as X
import Data.Foldable (toList)
import Data.Functor.Listable as X
import Data.Language as X
import Data.List.NonEmpty as X (NonEmpty(..))
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
import Data.Source as X
2018-03-13 20:59:20 +03:00
import Data.Span as X
2018-06-29 23:17:27 +03:00
import Data.String
2018-06-07 05:01:48 +03:00
import Data.Sum
import Data.Term as X
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
import Semantic.Task as X hiding (parsePackage)
import Semantic.Util as X
2018-03-13 20:59:20 +03:00
import System.FilePath as X
import Data.ByteString as X (ByteString)
2018-03-13 21:04:58 +03:00
import Data.Functor.Both as X (Both, runBothWith, both)
import Data.Maybe as X
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 21:10:50 +03:00
import Test.Hspec as X (Spec, SpecWith, context, describe, it, xit, parallel, pendingWith, around, runIO)
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
2018-08-09 22:51:55 +03:00
import qualified Data.Set as Set
2018-03-13 20:32:25 +03:00
import qualified Semantic.IO as IO
import Semantic.Config (Config)
2018-08-15 19:08:15 +03:00
import Semantic.Graph (ConcreteEff)
import Semantic.Telemetry (LogQueue, StatQueue)
import System.Exit (die)
import Control.Exception (displayException)
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
2018-06-29 23:17:27 +03:00
-- | This orphan instance is so we don't have to insert @name@ calls
-- in dozens and dozens of environment specs.
instance IsString Name where
fromString = name . fromString
-- | Returns an s-expression formatted diff for the specified FilePath pair.
diffFilePaths :: TaskConfig -> Both FilePath -> IO ByteString
diffFilePaths (TaskConfig config logger statter) paths = readFilePair paths >>= runTaskWithConfig config logger statter . runDiff SExpressionDiffRenderer . pure >>= either (die . displayException) (pure . runBuilder)
-- | Returns an s-expression parse tree for the specified FilePath.
parseFilePath :: TaskConfig -> FilePath -> IO ByteString
parseFilePath (TaskConfig config logger statter) path = (fromJust <$> IO.readFile (file path)) >>= runTaskWithConfig config logger statter . runParse SExpressionTermRenderer . pure >>= either (die . displayException) (pure . runBuilder)
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-08-15 18:55:45 +03:00
type TestEvaluatingEffects = '[ Resumable (BaseError (ValueError Precise (ConcreteEff Precise '[Trace, Lift IO])))
2018-08-04 02:59:34 +03:00
, Resumable (BaseError (AddressError Precise Val))
, Resumable (BaseError ResolutionError)
, Resumable (BaseError EvalError)
, Resumable (BaseError (EnvironmentError Precise))
2018-08-06 21:50:49 +03:00
, Resumable (BaseError (UnspecializedError Val))
2018-08-07 01:10:59 +03:00
, Resumable (BaseError (LoadError Precise))
, Fresh
2018-08-09 22:40:42 +03:00
, State (Heap Precise Val)
, Trace
, Lift IO
]
2018-08-15 18:55:45 +03:00
type TestEvaluatingErrors = '[ BaseError (ValueError Precise (ConcreteEff Precise '[Trace, Lift IO]))
2018-08-04 02:59:34 +03:00
, BaseError (AddressError Precise Val)
, BaseError ResolutionError
, BaseError EvalError
, BaseError (EnvironmentError Precise)
2018-08-06 21:50:49 +03:00
, BaseError (UnspecializedError Val)
2018-08-07 01:10:59 +03:00
, BaseError (LoadError Precise)
]
2018-07-17 04:42:01 +03:00
testEvaluating :: Evaluator Precise Val TestEvaluatingEffects (ModuleTable (NonEmpty (Module (ModuleResult Precise))))
-> IO
( [String]
2018-08-09 22:40:42 +03:00
, ( Heap Precise Val
, Either (SomeExc (Data.Sum.Sum TestEvaluatingErrors))
2018-07-17 04:42:01 +03:00
(ModuleTable (NonEmpty (Module (ModuleResult Precise))))
)
)
testEvaluating
= runM
. runReturningTrace
2018-06-21 20:19:24 +03:00
. runState lowerBound
2018-06-20 19:17:46 +03:00
. runFresh 0
2018-06-06 16:45:40 +03:00
. fmap reassociate
. runLoadError
. runUnspecialized
. runEnvironmentError
. runEvalError
. runResolutionError
. runAddressError
2018-08-15 18:55:45 +03:00
. runValueError @_ @Precise @(ConcreteEff Precise _)
2018-08-15 18:55:45 +03:00
type Val = Value Precise (ConcreteEff Precise '[Trace, Lift IO])
2018-05-07 00:36:33 +03:00
2018-08-09 22:51:55 +03:00
deNamespace :: Heap Precise (Value Precise term)
-> Value Precise term
-> Maybe (Name, [Name])
deNamespace heap ns@(Namespace name _ _) = (,) name . Env.allNames <$> namespaceScope heap ns
deNamespace _ _ = Nothing
2018-05-28 15:54:33 +03:00
2018-08-09 22:51:55 +03:00
namespaceScope :: Heap Precise (Value Precise term)
-> Value Precise term
-> Maybe (Environment Precise)
namespaceScope heap ns@(Namespace _ _ _)
= either (const Nothing) snd
. run
. runFresh 0
. runAddressError
. runState heap
2018-08-04 02:59:34 +03:00
. runReader (lowerBound @Span)
2018-08-07 20:48:01 +03:00
. runReader (ModuleInfo "SpecHelper.hs")
. runDeref
$ materializeEnvironment ns
namespaceScope _ _ = Nothing
2018-08-09 22:40:42 +03:00
derefQName :: Heap Precise (Value Precise term) -> NonEmpty Name -> Bindings Precise -> Maybe (Value Precise term)
derefQName heap names binds = go names (Env.newEnv binds)
2018-08-09 22:30:50 +03:00
where go (n1 :| ns) env = Env.lookupEnv' n1 env >>= flip heapLookup heap >>= fmap fst . Set.minView >>= case ns of
[] -> Just
(n2 : ns) -> namespaceScope heap >=> go (n2 :| ns)
newtype Verbatim = Verbatim ByteString
2018-02-07 23:20:27 +03:00
deriving (Eq)
instance Show Verbatim where
show (Verbatim x) = show x
verbatim :: ByteString -> Verbatim
2018-02-07 23:20:27 +03:00
verbatim = Verbatim . stripWhitespace
where
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