2023-03-29 16:51:04 +03:00
|
|
|
module Formatter.Positive where
|
|
|
|
|
|
|
|
import Base
|
|
|
|
import Juvix.Formatter
|
|
|
|
import Scope.Positive qualified
|
|
|
|
import Scope.Positive qualified as Scope
|
|
|
|
|
2023-04-13 12:27:39 +03:00
|
|
|
runScopeEffIO :: Member (Embed IO) r => Sem (ScopeEff ': r) a -> Sem r a
|
|
|
|
runScopeEffIO = interpret $ \case
|
2023-03-29 16:51:04 +03:00
|
|
|
ScopeFile p -> do
|
2023-04-13 12:27:39 +03:00
|
|
|
entry <- embed (defaultEntryPointCwdIO p)
|
2023-03-30 14:39:27 +03:00
|
|
|
embed (snd <$> runIO' entry upToScoping)
|
2023-03-29 16:51:04 +03:00
|
|
|
|
|
|
|
makeFormatTest' :: Scope.PosTest -> TestDescr
|
|
|
|
makeFormatTest' Scope.PosTest {..} =
|
|
|
|
let tRoot = Scope.Positive.root <//> _relDir
|
|
|
|
file' = tRoot <//> _file
|
|
|
|
in TestDescr
|
|
|
|
{ _testName = _name,
|
|
|
|
_testRoot = tRoot,
|
|
|
|
_testAssertion = Single $ do
|
2023-04-13 12:27:39 +03:00
|
|
|
d <- runM $ runError $ runOutputList @FormattedFileInfo $ runScopeEffIO $ runFilesIO $ format file'
|
2023-03-29 16:51:04 +03:00
|
|
|
case d of
|
|
|
|
Right (_, FormatResultOK) -> return ()
|
|
|
|
Right (_, FormatResultFail) -> assertFailure ("File: " <> show file' <> " is not formatted")
|
|
|
|
Left {} -> assertFailure ("Error: ")
|
|
|
|
}
|
|
|
|
|
|
|
|
filterOutTests :: [String] -> [Scope.PosTest] -> [Scope.PosTest]
|
|
|
|
filterOutTests out = filter (\Scope.PosTest {..} -> _name `notElem` out)
|
|
|
|
|
|
|
|
-- Ignore tests that use the stdlib
|
|
|
|
ignoredTests :: [String]
|
|
|
|
ignoredTests = ["Import embedded standard library", "Basic dependencies"]
|
|
|
|
|
|
|
|
allTests :: TestTree
|
|
|
|
allTests =
|
|
|
|
testGroup
|
|
|
|
"Formatter positive tests"
|
|
|
|
(map (mkTest . makeFormatTest') (filterOutTests ignoredTests Scope.Positive.tests))
|