module Test.SourceFile (tests) where
import System.FilePath
import Base.CompilerError
import Base.TrackedErrors
import Parser.Pragma (parsePragmas)
import Parser.SourceFile
import Test.Common
tests :: [IO (TrackedErrors ())]
tests :: [IO (TrackedErrors ())]
tests = [
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$ModuleOnly$" (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) TextParser (PragmaSource SourceContext)
pragmaModuleOnly)
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[PragmaVisibility [SourceContext]
_ CodeVisibility
ModuleOnly] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$TestsOnly$" (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) TextParser (PragmaSource SourceContext)
pragmaTestsOnly)
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[PragmaVisibility [SourceContext]
_ CodeVisibility
TestsOnly] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"/*only comments*/" (forall a. [TextParser a] -> TextParser [a]
parsePragmas [TextParser (PragmaSource SourceContext)
pragmaModuleOnly,TextParser (PragmaSource SourceContext)
pragmaTestsOnly])
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$ModuleOnly$ // comment" (forall a. [TextParser a] -> TextParser [a]
parsePragmas [TextParser (PragmaSource SourceContext)
pragmaTestsOnly,TextParser (PragmaSource SourceContext)
pragmaModuleOnly])
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[PragmaVisibility [SourceContext]
_ CodeVisibility
ModuleOnly] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$TestsOnly$ /*comment*/" (forall a. [TextParser a] -> TextParser [a]
parsePragmas [TextParser (PragmaSource SourceContext)
pragmaModuleOnly,TextParser (PragmaSource SourceContext)
pragmaTestsOnly])
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[PragmaVisibility [SourceContext]
_ CodeVisibility
TestsOnly] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> TextParser a -> (a -> Bool) -> IO (TrackedErrors ())
checkParseMatch String
"$TestsOnly$\n$TestsOnly$\n$ModuleOnly$" (forall a. [TextParser a] -> TextParser [a]
parsePragmas [TextParser (PragmaSource SourceContext)
pragmaModuleOnly,TextParser (PragmaSource SourceContext)
pragmaTestsOnly])
(\[PragmaSource SourceContext]
e -> case [PragmaSource SourceContext]
e of
[PragmaVisibility [SourceContext]
_ CodeVisibility
TestsOnly,
PragmaVisibility [SourceContext]
_ CodeVisibility
TestsOnly,
PragmaVisibility [SourceContext]
_ CodeVisibility
ModuleOnly] -> Bool
True
[PragmaSource SourceContext]
_ -> Bool
False),
forall a.
Show a =>
String -> String -> TextParser a -> IO (TrackedErrors ())
checkParseError String
"$ModuleOnly[ extra ]$" String
"does not allow arguments" TextParser (PragmaSource SourceContext)
pragmaModuleOnly,
forall a.
Show a =>
String -> String -> TextParser a -> IO (TrackedErrors ())
checkParseError String
"$TestsOnly[ extra ]$" String
"does not allow arguments" TextParser (PragmaSource SourceContext)
pragmaTestsOnly,
forall a.
String
-> ((String, String) -> TrackedErrors a) -> IO (TrackedErrors ())
checkParseSuccess (String
"testfiles" String -> String -> String
</> String
"public.0rp") forall (m :: * -> *).
ErrorContextM m =>
(String, String)
-> m ([PragmaSource SourceContext], [AnyCategory SourceContext])
parsePublicSource,
forall a.
String
-> ((String, String) -> TrackedErrors a) -> IO (TrackedErrors ())
checkParseSuccess (String
"testfiles" String -> String -> String
</> String
"internal.0rx") forall (m :: * -> *).
ErrorContextM m =>
(String, String)
-> m ([PragmaSource SourceContext], [AnyCategory SourceContext],
[DefinedCategory SourceContext])
parseInternalSource,
forall a.
String
-> ((String, String) -> TrackedErrors a) -> IO (TrackedErrors ())
checkParseSuccess (String
"testfiles" String -> String -> String
</> String
"test.0rt") forall (m :: * -> *).
ErrorContextM m =>
(String, String)
-> m ([PragmaSource SourceContext],
[IntegrationTest SourceContext])
parseTestSource
]
checkParseSuccess :: String -> ((FilePath,String) -> TrackedErrors a) -> IO (TrackedErrors ())
checkParseSuccess :: forall a.
String
-> ((String, String) -> TrackedErrors a) -> IO (TrackedErrors ())
checkParseSuccess String
f (String, String) -> TrackedErrors a
p = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors a
parsed = (String, String) -> TrackedErrors a
p (String
f,String
contents)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}.
ErrorContextM m =>
TrackedErrorsT Identity a -> m ()
check TrackedErrors a
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Parse " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
":\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return ()