module Cli.TestRunner (
runSingleTest,
) where
import Control.Arrow (second)
import Control.Monad (when)
import Control.Monad.IO.Class
import Data.List (intercalate,isSuffixOf,nub,sort)
import System.Directory
import System.IO
import System.Posix.Temp (mkdtemp)
import System.FilePath
import Text.Regex.TDFA
import qualified Data.Map as Map
import Base.CompilerError
import Base.TrackedErrors
import Cli.Programs
import CompilerCxx.CxxFiles
import CompilerCxx.LanguageModule
import CompilerCxx.Naming
import Module.CompileMetadata
import Module.Paths
import Module.ProcessMetadata
import Parser.SourceFile
import Parser.TextParser (SourceContext)
import Types.IntegrationTest
import Types.Procedure
import Types.TypeCategory
runSingleTest :: CompilerBackend b => b -> FilePath ->
LanguageModule SourceContext -> [FilePath] -> [CompileMetadata] ->
(String,String) -> TrackedErrorsIO ((Int,Int),TrackedErrors ())
runSingleTest :: forall b.
CompilerBackend b =>
b
-> FilePath
-> LanguageModule SourceContext
-> [FilePath]
-> [CompileMetadata]
-> (FilePath, FilePath)
-> TrackedErrorsIO ((Int, Int), TrackedErrors ())
runSingleTest b
b FilePath
cl LanguageModule SourceContext
cm [FilePath]
paths [CompileMetadata]
deps (FilePath
f,FilePath
s) = do
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"\nExecuting tests from " forall a. [a] -> [a] -> [a]
++ FilePath
f
((Int, Int), TrackedErrors ())
allResults <- forall {m :: * -> *} {a}.
(MonadIO m, CollectErrorsM m) =>
TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
-> m ((Int, Int), TrackedErrors ())
checkAndRun (forall (m :: * -> *).
ErrorContextM m =>
(FilePath, FilePath)
-> m ([PragmaSource SourceContext],
[IntegrationTest SourceContext])
parseTestSource (FilePath
f,FilePath
s))
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ((FilePath
"\nIn test file " forall a. [a] -> [a] -> [a]
++ FilePath
f) forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a -> m a
??>) ((Int, Int), TrackedErrors ())
allResults where
checkAndRun :: TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
-> m ((Int, Int), TrackedErrors ())
checkAndRun TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
ts
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
ts = do
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Failed to parse tests in " forall a. [a] -> [a] -> [a]
++ FilePath
f
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int
0,Int
1),TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
ts forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
| Bool
otherwise = do
let (a
_,[IntegrationTest SourceContext]
ts') = forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity (a, [IntegrationTest SourceContext])
ts
[((Int, Int), TrackedErrors ())]
allResults <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM forall {m :: * -> *}.
(ErrorContextM m, MonadIO m) =>
IntegrationTest SourceContext -> m ((Int, Int), TrackedErrors ())
runSingle [IntegrationTest SourceContext]
ts'
let passed :: Int
passed = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [((Int, Int), TrackedErrors ())]
allResults
let failed :: Int
failed = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [((Int, Int), TrackedErrors ())]
allResults
let result :: TrackedErrors ()
result = forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [((Int, Int), TrackedErrors ())]
allResults
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int
passed,Int
failed),TrackedErrors ()
result)
runSingle :: IntegrationTest SourceContext -> m ((Int, Int), TrackedErrors ())
runSingle IntegrationTest SourceContext
t = do
let name :: FilePath
name = FilePath
"\"" forall a. [a] -> [a] -> [a]
++ forall c. IntegrationTestHeader c -> FilePath
ithTestName (forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t) forall a. [a] -> [a] -> [a]
++ FilePath
"\" (from " forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
")"
let context :: FilePath
context = forall a. Show a => [a] -> FilePath
formatFullContextBrace (forall c. IntegrationTestHeader c -> [c]
ithContext forall a b. (a -> b) -> a -> b
$ forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t)
let scope :: FilePath
scope = FilePath
"\nIn testcase \"" forall a. [a] -> [a] -> [a]
++ forall c. IntegrationTestHeader c -> FilePath
ithTestName (forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t) forall a. [a] -> [a] -> [a]
++ FilePath
"\"" forall a. [a] -> [a] -> [a]
++ FilePath
context
forall {m :: * -> *} {c}.
ErrorContextM m =>
IntegrationTestHeader c -> m ()
warnUnused (forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t) forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
scope
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"\n*** Executing testcase " forall a. [a] -> [a] -> [a]
++ FilePath
name forall a. [a] -> [a] -> [a]
++ FilePath
" ***"
TrackedErrors [TrackedErrors ()]
result <- forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}.
(MonadIO m, Num a, Ord a, Show a) =>
ExpectedResult SourceContext
-> [FilePath]
-> Maybe a
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT m [TrackedErrors ()]
run (forall c. IntegrationTestHeader c -> ExpectedResult c
ithResult forall a b. (a -> b) -> a -> b
$ forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t)
(forall c. IntegrationTestHeader c -> [FilePath]
ithArgs forall a b. (a -> b) -> a -> b
$ forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t)
(forall c. IntegrationTestHeader c -> Maybe Integer
ithTimeout forall a b. (a -> b) -> a -> b
$ forall c. IntegrationTest c -> IntegrationTestHeader c
itHeader IntegrationTest SourceContext
t)
(forall c. IntegrationTest c -> [AnyCategory c]
itCategory IntegrationTest SourceContext
t) (forall c. IntegrationTest c -> [DefinedCategory c]
itDefinition IntegrationTest SourceContext
t) (forall c. IntegrationTest c -> [TestProcedure c]
itTests IntegrationTest SourceContext
t)
if forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors [TrackedErrors ()]
result
then forall (m :: * -> *) a. Monad m => a -> m a
return ((Int
0,Int
1),FilePath
scope forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a -> m a
??> (TrackedErrors [TrackedErrors ()]
result forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()))
else do
let allResults :: [TrackedErrors ()]
allResults = forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrors [TrackedErrors ()]
result
let passed :: Int
passed = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError) [TrackedErrors ()]
allResults
let failed :: Int
failed = forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError [TrackedErrors ()]
allResults
let combined :: TrackedErrors ()
combined = FilePath
scope forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a -> m a
??> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ [TrackedErrors ()]
allResults
if Int
failed forall a. Ord a => a -> a -> Bool
> Int
0
then forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"*** Some tests in testcase " forall a. [a] -> [a] -> [a]
++ FilePath
name forall a. [a] -> [a] -> [a]
++ FilePath
" failed ***"
else forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"*** All tests in testcase " forall a. [a] -> [a] -> [a]
++ FilePath
name forall a. [a] -> [a] -> [a]
++ FilePath
" passed ***"
forall (m :: * -> *) a. Monad m => a -> m a
return ((Int
passed,Int
failed),TrackedErrors ()
combined)
warnUnused :: IntegrationTestHeader c -> m ()
warnUnused (IntegrationTestHeader [c]
_ FilePath
_ [FilePath]
args Maybe Integer
timeout ExpectedResult c
ex) = m ()
check where
check :: m ()
check =
case ExpectedResult c
ex of
(ExpectCompilerError [c]
_ [OutputPattern]
_ [OutputPattern]
_) -> do
forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
warnArgs FilePath
"error"
forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
warnTimeout FilePath
"error"
(ExpectCompiles [c]
_ [OutputPattern]
_ [OutputPattern]
_) -> do
forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
warnArgs FilePath
"compiles"
forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
warnTimeout FilePath
"compiles"
ExpectedResult c
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
warnArgs :: FilePath -> m ()
warnArgs FilePath
ex2 =
case [FilePath]
args of
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
[FilePath]
_ -> forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
compilerWarningM forall a b. (a -> b) -> a -> b
$ FilePath
"Explicit args are ignored in " forall a. [a] -> [a] -> [a]
++ FilePath
ex2 forall a. [a] -> [a] -> [a]
++ FilePath
" tests: " forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", " (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> FilePath
show [FilePath]
args)
warnTimeout :: FilePath -> m ()
warnTimeout FilePath
ex2 =
case Maybe Integer
timeout of
Maybe Integer
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Integer
t -> forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
compilerWarningM forall a b. (a -> b) -> a -> b
$ FilePath
"Explicit timeouts are ignored in " forall a. [a] -> [a] -> [a]
++ FilePath
ex2 forall a. [a] -> [a] -> [a]
++ FilePath
" tests: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Integer
t
run :: ExpectedResult SourceContext
-> [FilePath]
-> Maybe a
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT m [TrackedErrors ()]
run (ExpectCompilerError [SourceContext]
_ [OutputPattern]
rs [OutputPattern]
es) [FilePath]
_ Maybe a
_ [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result <- forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *}.
Monad m =>
Maybe ([SourceContext], TypeInstance)
-> [FilePath]
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT
m ([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
compileAll forall a. Maybe a
Nothing [] [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
if Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
then forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM FilePath
"Expected compilation failure"
else forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ do
let warnings :: FilePath
warnings = forall a. Show a => a -> FilePath
show forall a b. (a -> b) -> a -> b
$ forall a. TrackedErrors a -> CompilerMessage
getCompilerWarnings TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
let errors :: FilePath
errors = forall a. Show a => a -> FilePath
show forall a b. (a -> b) -> a -> b
$ forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
[OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> TrackedErrors ()
checkContent [OutputPattern]
rs [OutputPattern]
es (FilePath -> [FilePath]
lines FilePath
warnings forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath]
lines FilePath
errors) [] []
run (ExpectCompiles [SourceContext]
_ [OutputPattern]
rs [OutputPattern]
es) [FilePath]
_ Maybe a
_ [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result <- forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *}.
Monad m =>
Maybe ([SourceContext], TypeInstance)
-> [FilePath]
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT
m ([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
compileAll forall a. Maybe a
Nothing [] [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
if forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
then forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m a
fromTrackedErrors TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return []
else forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ do
let warnings :: FilePath
warnings = forall a. Show a => a -> FilePath
show forall a b. (a -> b) -> a -> b
$ forall a. TrackedErrors a -> CompilerMessage
getCompilerWarnings TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
[OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> TrackedErrors ()
checkContent [OutputPattern]
rs [OutputPattern]
es (FilePath -> [FilePath]
lines FilePath
warnings) [] []
run (ExpectRuntimeError [SourceContext]
_ Maybe ([SourceContext], TypeInstance)
t [OutputPattern]
rs [OutputPattern]
es) [FilePath]
args Maybe a
timeout [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Int
length [TestProcedure SourceContext]
ts forall a. Eq a => a -> a -> Bool
/= Int
1) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM FilePath
"Exactly one unittest is required when failure is expected"
forall {m :: * -> *} {a}.
(CollectErrorsM m, Show a, Ord a) =>
[TestProcedure a] -> m ()
uniqueTestNames [TestProcedure SourceContext]
ts
forall {m :: * -> *} {a}.
(MonadIO m, CollectErrorsM m, Num a, Ord a, Show a) =>
Bool
-> Maybe ([SourceContext], TypeInstance)
-> [OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> Maybe a
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> m [TrackedErrors ()]
execute Bool
False Maybe ([SourceContext], TypeInstance)
t [OutputPattern]
rs [OutputPattern]
es [FilePath]
args Maybe a
timeout [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
run (ExpectRuntimeSuccess [SourceContext]
_ Maybe ([SourceContext], TypeInstance)
t [OutputPattern]
rs [OutputPattern]
es) [FilePath]
args Maybe a
timeout [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TestProcedure SourceContext]
ts) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM FilePath
"At least one unittest is required when success is expected"
forall {m :: * -> *} {a}.
(CollectErrorsM m, Show a, Ord a) =>
[TestProcedure a] -> m ()
uniqueTestNames [TestProcedure SourceContext]
ts
forall {m :: * -> *} {a}.
(MonadIO m, CollectErrorsM m, Num a, Ord a, Show a) =>
Bool
-> Maybe ([SourceContext], TypeInstance)
-> [OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> Maybe a
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> m [TrackedErrors ()]
execute Bool
True Maybe ([SourceContext], TypeInstance)
t [OutputPattern]
rs [OutputPattern]
es [FilePath]
args Maybe a
timeout [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
checkContent :: [OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> TrackedErrors ()
checkContent [OutputPattern]
rs [OutputPattern]
es [FilePath]
comp [FilePath]
err [FilePath]
out = do
let cr :: TrackedErrors ()
cr = [OutputPattern]
-> [FilePath] -> [FilePath] -> [FilePath] -> TrackedErrors ()
checkRequired [OutputPattern]
rs [FilePath]
comp [FilePath]
err [FilePath]
out
let ce :: TrackedErrors ()
ce = [OutputPattern]
-> [FilePath] -> [FilePath] -> [FilePath] -> TrackedErrors ()
checkExcluded [OutputPattern]
es [FilePath]
comp [FilePath]
err [FilePath]
out
let compError :: TrackedErrors ()
compError = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
comp
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else (forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM [FilePath]
comp) forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"\nOutput from compiler:"
let errError :: TrackedErrors ()
errError = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
err
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else (forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM [FilePath]
err) forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"\nOutput to stderr from test:"
let outError :: TrackedErrors ()
outError = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FilePath]
out
then forall (m :: * -> *) a. Monad m => a -> m a
return ()
else (forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM [FilePath]
out) forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"\nOutput to stdout from test:"
if forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors ()
cr Bool -> Bool -> Bool
|| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors ()
ce
then forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ [TrackedErrors ()
cr,TrackedErrors ()
ce,TrackedErrors ()
compError,TrackedErrors ()
errError,TrackedErrors ()
outError]
else forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ [TrackedErrors ()
cr,TrackedErrors ()
ce]
uniqueTestNames :: [TestProcedure a] -> m ()
uniqueTestNames [TestProcedure a]
ts = do
let ts' :: Map FunctionName [TestProcedure a]
ts' = forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith forall a. [a] -> [a] -> [a]
(++) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\TestProcedure a
t -> (forall c. TestProcedure c -> FunctionName
tpName TestProcedure a
t,[TestProcedure a
t])) [TestProcedure a]
ts
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall {m :: * -> *} {a} {a}.
(CollectErrorsM m, Show a, Show a, Ord a) =>
(a, [TestProcedure a]) -> m ()
testClash forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList Map FunctionName [TestProcedure a]
ts'
testClash :: (a, [TestProcedure a]) -> m ()
testClash (a
_,[TestProcedure a
_]) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
testClash (a
n,[TestProcedure a]
ts) = FilePath
"unittest " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
n forall a. [a] -> [a] -> [a]
++ FilePath
" is defined multiple times" forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a -> m a
!!>
(forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
"Defined at " forall a. [a] -> [a] -> [a]
++) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => [a] -> FilePath
formatFullContext) forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> [a]
sort forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall c. TestProcedure c -> [c]
tpContext [TestProcedure a]
ts)
execute :: Bool
-> Maybe ([SourceContext], TypeInstance)
-> [OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> Maybe a
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> m [TrackedErrors ()]
execute Bool
s2 Maybe ([SourceContext], TypeInstance)
t [OutputPattern]
rs [OutputPattern]
es [FilePath]
args Maybe a
timeout [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result <- forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *}.
Monad m =>
Maybe ([SourceContext], TypeInstance)
-> [FilePath]
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT
m ([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
compileAll Maybe ([SourceContext], TypeInstance)
t [FilePath]
args [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
if forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
then forall (m :: * -> *) a. Monad m => a -> m a
return [TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()]
else do
let ([CxxOutput]
xx,CxxOutput
main,[(FunctionName, [SourceContext])]
fs) = forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result
(FilePath
dir,FilePath
binaryName) <- forall {m :: * -> *} {a}.
(MonadIO m, CollectErrorsM m, Num a, Ord a, Show a) =>
CxxOutput -> Maybe a -> [CxxOutput] -> m (FilePath, FilePath)
createBinary CxxOutput
main Maybe a
timeout [CxxOutput]
xx
[TrackedErrors ()]
results <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a} {a} {a}.
(Show a, Show a) =>
FilePath
-> [OutputPattern]
-> [OutputPattern]
-> TrackedErrors a
-> Bool
-> (a, [a])
-> TrackedErrorsT IO ()
executeTest FilePath
binaryName [OutputPattern]
rs [OutputPattern]
es TrackedErrors
([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
result Bool
s2) [(FunctionName, [SourceContext])]
fs
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError [TrackedErrors ()]
results) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
removeDirectoryRecursive FilePath
dir
forall (m :: * -> *) a. Monad m => a -> m a
return [TrackedErrors ()]
results
executeTest :: FilePath
-> [OutputPattern]
-> [OutputPattern]
-> TrackedErrors a
-> Bool
-> (a, [a])
-> TrackedErrorsT IO ()
executeTest FilePath
binary [OutputPattern]
rs [OutputPattern]
es TrackedErrors a
res Bool
s2 (a
f2,[a]
c) = forall {t :: (* -> *) -> * -> *} {a}.
(ErrorContextT t, ErrorContextM (t IO)) =>
t IO a -> t IO a
printOutcome forall a b. (a -> b) -> a -> b
$ FilePath
context forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a -> m a
??> do
let command :: TestCommand
command = FilePath -> FilePath -> [FilePath] -> TestCommand
TestCommand FilePath
binary (FilePath -> FilePath
takeDirectory FilePath
binary) [forall a. Show a => a -> FilePath
show a
f2,FilePath
cl]
forall (m :: * -> *) a. ErrorContextM m => m a -> m a
resetBackgroundM forall a b. (a -> b) -> a -> b
$ do
forall {m :: * -> *}. ErrorContextM m => FilePath -> m ()
compilerBackgroundM forall a b. (a -> b) -> a -> b
$ FilePath
"See output files for testcase in " forall a. [a] -> [a] -> [a]
++ (FilePath -> FilePath
takeDirectory FilePath
binary)
(TestCommandResult Bool
s2' [FilePath]
out [FilePath]
err) <- forall b (m :: * -> *).
(CompilerBackend b, MonadIO m, CollectErrorsM m) =>
b -> TestCommand -> m TestCommandResult
runTestCommand b
b TestCommand
command
case (Bool
s2,Bool
s2') of
(Bool
True,Bool
False) -> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ forall a b. (a -> b) -> a -> b
$ (forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m ()
asCompilerError TrackedErrors a
res)forall a. a -> [a] -> [a]
:(forall a b. (a -> b) -> [a] -> [b]
map forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ [FilePath]
err forall a. [a] -> [a] -> [a]
++ [FilePath]
out)
(Bool
False,Bool
True) -> forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ [forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM FilePath
"Expected runtime failure",
forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m ()
asCompilerError TrackedErrors a
res forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"\nOutput from compiler:"]
(Bool, Bool)
_ -> forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m a
fromTrackedErrors forall a b. (a -> b) -> a -> b
$ [OutputPattern]
-> [OutputPattern]
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> TrackedErrors ()
checkContent [OutputPattern]
rs [OutputPattern]
es (FilePath -> [FilePath]
lines forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show forall a b. (a -> b) -> a -> b
$ forall a. TrackedErrors a -> CompilerMessage
getCompilerWarnings TrackedErrors a
res) [FilePath]
err [FilePath]
out
where
context :: FilePath
context = FilePath
"\nIn unittest " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
f2 forall a. [a] -> [a] -> [a]
++ forall a. Show a => [a] -> FilePath
formatFullContextBrace [a]
c
printOutcome :: t IO a -> t IO a
printOutcome t IO a
outcome =
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(ErrorContextT t, Monad m, ErrorContextM (t m)) =>
t m a -> m () -> m () -> t m a
ifElseSuccessT t IO a
outcome
(Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"--- unittest " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
f2 forall a. [a] -> [a] -> [a]
++ FilePath
" passed ---")
(Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"--- unittest " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
f2 forall a. [a] -> [a] -> [a]
++ FilePath
" failed ---")
compileAll :: Maybe ([SourceContext], TypeInstance)
-> [FilePath]
-> [AnyCategory SourceContext]
-> [DefinedCategory SourceContext]
-> [TestProcedure SourceContext]
-> TrackedErrorsT
m ([CxxOutput], CxxOutput, [(FunctionName, [SourceContext])])
compileAll Maybe ([SourceContext], TypeInstance)
t [FilePath]
args [AnyCategory SourceContext]
cs [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts = do
let ns1 :: Namespace
ns1 = FilePath -> Namespace
StaticNamespace forall a b. (a -> b) -> a -> b
$ forall a. Hashable a => a -> FilePath
privateNamespace FilePath
s
let cs' :: [AnyCategory SourceContext]
cs' = forall a b. (a -> b) -> [a] -> [b]
map (forall c. Namespace -> AnyCategory c -> AnyCategory c
setCategoryNamespace Namespace
ns1) [AnyCategory SourceContext]
cs
forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m a
fromTrackedErrors forall a b. (a -> b) -> a -> b
$ forall c (m :: * -> *).
(Ord c, Show c, CollectErrorsM m) =>
LanguageModule c
-> Namespace
-> [FilePath]
-> Maybe ([c], TypeInstance)
-> [AnyCategory c]
-> [DefinedCategory c]
-> [TestProcedure c]
-> m ([CxxOutput], CxxOutput, [(FunctionName, [c])])
compileTestsModule LanguageModule SourceContext
cm Namespace
ns1 [FilePath]
args Maybe ([SourceContext], TypeInstance)
t [AnyCategory SourceContext]
cs' [DefinedCategory SourceContext]
ds [TestProcedure SourceContext]
ts
checkRequired :: [OutputPattern]
-> [FilePath] -> [FilePath] -> [FilePath] -> TrackedErrors ()
checkRequired [OutputPattern]
rs [FilePath]
comp [FilePath]
err [FilePath]
out = forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (Bool
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> OutputPattern
-> TrackedErrors ()
checkSubsetForRegex Bool
True [FilePath]
comp [FilePath]
err [FilePath]
out) [OutputPattern]
rs
checkExcluded :: [OutputPattern]
-> [FilePath] -> [FilePath] -> [FilePath] -> TrackedErrors ()
checkExcluded [OutputPattern]
es [FilePath]
comp [FilePath]
err [FilePath]
out = forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (Bool
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> OutputPattern
-> TrackedErrors ()
checkSubsetForRegex Bool
False [FilePath]
comp [FilePath]
err [FilePath]
out) [OutputPattern]
es
checkSubsetForRegex :: Bool
-> [FilePath]
-> [FilePath]
-> [FilePath]
-> OutputPattern
-> TrackedErrors ()
checkSubsetForRegex Bool
expected [FilePath]
comp [FilePath]
err [FilePath]
out (OutputPattern OutputScope
OutputAny FilePath
r) =
Bool -> [FilePath] -> FilePath -> FilePath -> TrackedErrors ()
checkForRegex Bool
expected ([FilePath]
comp forall a. [a] -> [a] -> [a]
++ [FilePath]
err forall a. [a] -> [a] -> [a]
++ [FilePath]
out) FilePath
r FilePath
"compiler output or test output"
checkSubsetForRegex Bool
expected [FilePath]
comp [FilePath]
_ [FilePath]
_ (OutputPattern OutputScope
OutputCompiler FilePath
r) =
Bool -> [FilePath] -> FilePath -> FilePath -> TrackedErrors ()
checkForRegex Bool
expected [FilePath]
comp FilePath
r FilePath
"compiler output"
checkSubsetForRegex Bool
expected [FilePath]
_ [FilePath]
err [FilePath]
_ (OutputPattern OutputScope
OutputStderr FilePath
r) =
Bool -> [FilePath] -> FilePath -> FilePath -> TrackedErrors ()
checkForRegex Bool
expected [FilePath]
err FilePath
r FilePath
"test stderr"
checkSubsetForRegex Bool
expected [FilePath]
_ [FilePath]
_ [FilePath]
out (OutputPattern OutputScope
OutputStdout FilePath
r) =
Bool -> [FilePath] -> FilePath -> FilePath -> TrackedErrors ()
checkForRegex Bool
expected [FilePath]
out FilePath
r FilePath
"test stdout"
checkForRegex :: Bool -> [String] -> String -> String -> TrackedErrors ()
checkForRegex :: Bool -> [FilePath] -> FilePath -> FilePath -> TrackedErrors ()
checkForRegex Bool
expected [FilePath]
ms FilePath
r FilePath
n = do
let found :: Bool
found = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ FilePath
r) [FilePath]
ms
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
found Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
expected) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Pattern \"" forall a. [a] -> [a] -> [a]
++ FilePath
r forall a. [a] -> [a] -> [a]
++ FilePath
"\" present in " forall a. [a] -> [a] -> [a]
++ FilePath
n
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
found Bool -> Bool -> Bool
&& Bool
expected) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Pattern \"" forall a. [a] -> [a] -> [a]
++ FilePath
r forall a. [a] -> [a] -> [a]
++ FilePath
"\" missing from " forall a. [a] -> [a] -> [a]
++ FilePath
n
createBinary :: CxxOutput -> Maybe a -> [CxxOutput] -> m (FilePath, FilePath)
createBinary (CxxOutput Maybe CategoryName
_ FilePath
f2 Namespace
_ Set Namespace
_ Set CategoryName
_ Set FilePath
_ [FilePath]
content) Maybe a
timeout [CxxOutput]
xx = do
FilePath
dir <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
mkdtemp FilePath
"/tmp/ztest_"
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Writing temporary files to " forall a. [a] -> [a] -> [a]
++ FilePath
dir
[([FilePath], CxxOutput)]
sources <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> CxxOutput -> m ([FilePath], CxxOutput)
writeSingleFile FilePath
dir) [CxxOutput]
xx
let main :: FilePath
main = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
f2
let binary :: FilePath
binary = FilePath
dir FilePath -> FilePath -> FilePath
</> FilePath
"testcase"
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
writeFile FilePath
main forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. [a] -> [a] -> [a]
++ FilePath
"\n") [FilePath]
content
let flags :: [FilePath]
flags = [CompileMetadata] -> [FilePath]
getLinkFlagsForDeps [CompileMetadata]
deps
let paths' :: [FilePath]
paths' = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map FilePath -> FilePath
fixPath (FilePath
dirforall a. a -> [a] -> [a]
:[FilePath]
paths)
let libraries :: [FilePath]
libraries = [CompileMetadata] -> [FilePath]
getLibrariesForDeps [CompileMetadata]
deps
[(FilePath, Maybe FilePath)]
macro <- forall {a} {m :: * -> *}.
(Num a, Ord a, ErrorContextM m, Show a) =>
Maybe a -> m [(FilePath, Maybe FilePath)]
timeoutMacro Maybe a
timeout
let command :: CxxCommand
command = FilePath
-> [FilePath]
-> [(FilePath, Maybe FilePath)]
-> FilePath
-> [FilePath]
-> [FilePath]
-> CxxCommand
CompileToBinary FilePath
main (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [([FilePath], CxxOutput)]
sources) forall a. [a] -> [a] -> [a]
++ [FilePath]
libraries) [(FilePath, Maybe FilePath)]
macro FilePath
binary [FilePath]
paths' [FilePath]
flags
FilePath
file <- forall b (m :: * -> *).
(CompilerBackend b, MonadIO m, CollectErrorsM m) =>
b -> CxxCommand -> m FilePath
syncCxxCommand b
b CxxCommand
command
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
dir,FilePath
file)
timeoutMacro :: Maybe a -> m [(FilePath, Maybe FilePath)]
timeoutMacro (Just a
0) = forall (m :: * -> *) a. Monad m => a -> m a
return []
timeoutMacro Maybe a
Nothing = forall (m :: * -> *) a. Monad m => a -> m a
return [(FilePath
testTimeoutMacro,forall a. a -> Maybe a
Just FilePath
"30")]
timeoutMacro (Just a
t)
| a
t forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
|| a
t forall a. Ord a => a -> a -> Bool
> a
65535 = forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Invalid testcase timeout " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show a
t forall a. [a] -> [a] -> [a]
++ FilePath
" => use timeout 0 for unlimited time"
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return [(FilePath
testTimeoutMacro,forall a. a -> Maybe a
Just (forall a. Show a => a -> FilePath
show a
t))]
writeSingleFile :: FilePath -> CxxOutput -> m ([FilePath], CxxOutput)
writeSingleFile FilePath
d ca :: CxxOutput
ca@(CxxOutput Maybe CategoryName
_ FilePath
f2 Namespace
_ Set Namespace
_ Set CategoryName
_ Set FilePath
_ [FilePath]
content) = do
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
writeFile (FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
f2) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. [a] -> [a] -> [a]
++ FilePath
"\n") [FilePath]
content
if forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".cpp" FilePath
f2
then forall (m :: * -> *) a. Monad m => a -> m a
return ([FilePath
d FilePath -> FilePath -> FilePath
</> FilePath
f2],CxxOutput
ca)
else forall (m :: * -> *) a. Monad m => a -> m a
return ([],CxxOutput
ca)