{-# LANGUAGE Safe #-}
module Test.Common (
checkDefinesFail,
checkDefinesSuccess,
checkEquals,
checkTypeFail,
checkTypeSuccess,
containsAtLeast,
containsAtMost,
containsExactly,
containsNoDuplicates,
forceParse,
loadFile,
parseFilterMap,
parseTheTest,
readMulti,
readSingle,
readSingleWith,
runAllTests,
showParams,
) where
import Control.Monad (when)
import Data.Either
import Data.List
import System.Exit
import System.FilePath
import System.IO
import Text.Parsec
import qualified Data.Map as Map
import qualified Data.Set as Set
import Base.CompileError
import Base.CompileInfo
import Parser.Common
import Parser.TypeInstance ()
import Types.TypeInstance
runAllTests :: [IO (CompileInfo ())] -> IO ()
runAllTests :: [IO (CompileInfo ())] -> IO ()
runAllTests [IO (CompileInfo ())]
ts = do
[CompileInfo ()]
results <- [IO (CompileInfo ())] -> IO [CompileInfo ()]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [IO (CompileInfo ())]
ts
let ([(Int, CompileMessage)]
es,[()]
ps) = [Either (Int, CompileMessage) ()]
-> ([(Int, CompileMessage)], [()])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ([Either (Int, CompileMessage) ()]
-> ([(Int, CompileMessage)], [()]))
-> [Either (Int, CompileMessage) ()]
-> ([(Int, CompileMessage)], [()])
forall a b. (a -> b) -> a -> b
$ (Int -> CompileInfo () -> Either (Int, CompileMessage) ())
-> [Int] -> [CompileInfo ()] -> [Either (Int, CompileMessage) ()]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> CompileInfo () -> Either (Int, CompileMessage) ()
forall a b. a -> CompileInfo b -> Either (a, CompileMessage) b
numberError ([Int
1..] :: [Int]) [CompileInfo ()]
results
((Int, CompileMessage) -> IO ())
-> [(Int, CompileMessage)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
n,CompileMessage
e) -> Handle -> String -> IO ()
hPutStr Handle
stderr (String
"Test " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompileMessage -> String
forall a. Show a => a -> String
show CompileMessage
e String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n")) [(Int, CompileMessage)]
es
Handle -> String -> IO ()
hPutStr Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show ([()] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [()]
ps) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" tests passed + " String -> String -> String
forall a. [a] -> [a] -> [a]
++
Int -> String
forall a. Show a => a -> String
show ([(Int, CompileMessage)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Int, CompileMessage)]
es) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" tests failed\n"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [(Int, CompileMessage)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, CompileMessage)]
es) IO ()
forall a. IO a
exitFailure
numberError :: a -> CompileInfo b -> Either (a,CompileMessage) b
numberError :: a -> CompileInfo b -> Either (a, CompileMessage) b
numberError a
n CompileInfo b
c
| CompileInfo b -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo b
c = (a, CompileMessage) -> Either (a, CompileMessage) b
forall a b. a -> Either a b
Left (a
n,CompileInfo b -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo b
c)
| Bool
otherwise = b -> Either (a, CompileMessage) b
forall a b. b -> Either a b
Right (CompileInfo b -> b
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo b
c)
forceParse :: ParseFromSource a => String -> a
forceParse :: String -> a
forceParse String
s = CompileInfo a -> a
forall a. CompileInfo a -> a
getCompileSuccess (CompileInfo a -> a) -> CompileInfo a -> a
forall a b. (a -> b) -> a -> b
$ ParserE (CompileInfoT Identity) a
-> String -> String -> CompileInfo a
forall (m :: * -> *) a.
CompileErrorM m =>
ParserE m a -> String -> String -> m a
runParserE ParserE (CompileInfoT Identity) a
forall a (m :: * -> *).
(ParseFromSource a, CompileErrorM m) =>
ParserE m a
sourceParser String
"(string)" String
s
readSingle :: ParseFromSource a => String -> String -> CompileInfo a
readSingle :: String -> String -> CompileInfo a
readSingle = ParserE (CompileInfoT Identity) a
-> String -> String -> CompileInfo a
forall a.
ParserE (CompileInfoT Identity) a
-> String -> String -> CompileInfo a
readSingleWith ParserE (CompileInfoT Identity) a
forall a (m :: * -> *).
(ParseFromSource a, CompileErrorM m) =>
ParserE m a
sourceParser
readSingleWith :: ParserE CompileInfo a -> String -> String -> CompileInfo a
readSingleWith :: ParserE (CompileInfoT Identity) a
-> String -> String -> CompileInfo a
readSingleWith ParserE (CompileInfoT Identity) a
p = ParserE (CompileInfoT Identity) a
-> String -> String -> CompileInfo a
forall (m :: * -> *) a.
CompileErrorM m =>
ParserE m a -> String -> String -> m a
runParserE (ParsecT String () (CompileInfoT Identity) ()
-> ParsecT String () (CompileInfoT Identity) ()
-> ParserE (CompileInfoT Identity) a
-> ParserE (CompileInfoT Identity) a
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between ParsecT String () (CompileInfoT Identity) ()
forall (m :: * -> *). Monad m => ParserE m ()
nullParse ParsecT String () (CompileInfoT Identity) ()
forall (m :: * -> *). Monad m => ParserE m ()
endOfDoc ParserE (CompileInfoT Identity) a
p)
readMulti :: ParseFromSource a => String -> String -> CompileInfo [a]
readMulti :: String -> String -> CompileInfo [a]
readMulti String
f String
s = ParserE (CompileInfoT Identity) [a]
-> String -> String -> CompileInfo [a]
forall (m :: * -> *) a.
CompileErrorM m =>
ParserE m a -> String -> String -> m a
runParserE (ParsecT String () (CompileInfoT Identity) ()
-> ParsecT String () (CompileInfoT Identity) ()
-> ParserE (CompileInfoT Identity) [a]
-> ParserE (CompileInfoT Identity) [a]
forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between ParsecT String () (CompileInfoT Identity) ()
forall (m :: * -> *). Monad m => ParserE m ()
optionalSpace ParsecT String () (CompileInfoT Identity) ()
forall (m :: * -> *). Monad m => ParserE m ()
endOfDoc (ParsecT String () (CompileInfoT Identity) a
-> ParsecT String () (CompileInfoT Identity) ()
-> ParserE (CompileInfoT Identity) [a]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
sepBy ParsecT String () (CompileInfoT Identity) a
forall a (m :: * -> *).
(ParseFromSource a, CompileErrorM m) =>
ParserE m a
sourceParser ParsecT String () (CompileInfoT Identity) ()
forall (m :: * -> *). Monad m => ParserE m ()
optionalSpace)) String
f String
s
parseFilterMap :: [(String,[String])] -> CompileInfo ParamFilters
parseFilterMap :: [(String, [String])] -> CompileInfo ParamFilters
parseFilterMap [(String, [String])]
pa = do
[(ParamName, [TypeFilter])]
pa2 <- ((String, [String])
-> CompileInfoT Identity (ParamName, [TypeFilter]))
-> [(String, [String])]
-> CompileInfoT Identity [(ParamName, [TypeFilter])]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (String, [String])
-> CompileInfoT Identity (ParamName, [TypeFilter])
forall b.
ParseFromSource b =>
(String, [String]) -> CompileInfoT Identity (ParamName, [b])
parseFilters [(String, [String])]
pa
ParamFilters -> CompileInfo ParamFilters
forall (m :: * -> *) a. Monad m => a -> m a
return (ParamFilters -> CompileInfo ParamFilters)
-> ParamFilters -> CompileInfo ParamFilters
forall a b. (a -> b) -> a -> b
$ [(ParamName, [TypeFilter])] -> ParamFilters
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ParamName, [TypeFilter])]
pa2
where
parseFilters :: (String, [String]) -> CompileInfoT Identity (ParamName, [b])
parseFilters (String
n,[String]
fs) = do
[b]
fs2 <- (String -> CompileInfoT Identity b)
-> [String] -> CompileInfoT Identity [b]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (String -> String -> CompileInfoT Identity b
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)") [String]
fs
(ParamName, [b]) -> CompileInfoT Identity (ParamName, [b])
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ParamName
ParamName String
n,[b]
fs2)
parseTheTest :: ParseFromSource a => [(String,[String])] -> [String] -> CompileInfo ([a],ParamFilters)
parseTheTest :: [(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String]
xs = do
[a]
ts <- (String -> CompileInfoT Identity a)
-> [String] -> CompileInfoT Identity [a]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (String -> String -> CompileInfoT Identity a
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)") [String]
xs
ParamFilters
pa2 <- [(String, [String])] -> CompileInfo ParamFilters
parseFilterMap [(String, [String])]
pa
([a], ParamFilters) -> CompileInfo ([a], ParamFilters)
forall (m :: * -> *) a. Monad m => a -> m a
return ([a]
ts,ParamFilters
pa2)
showParams :: [(String,[String])] -> String
showParams :: [(String, [String])] -> String
showParams [(String, [String])]
pa = String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ([[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String]) -> [[String]] -> [String]
forall a b. (a -> b) -> a -> b
$ ((String, [String]) -> [String])
-> [(String, [String])] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map (String, [String]) -> [String]
expand [(String, [String])]
pa) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]" where
expand :: (String, [String]) -> [String]
expand (String
n,[String]
ps) = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
p -> String
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
p) [String]
ps
checkTypeSuccess :: TypeResolver r => r -> [(String,[String])] -> String -> CompileInfo ()
checkTypeSuccess :: r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess r
r [(String, [String])]
pa String
x = do
([GeneralInstance
t],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([GeneralInstance], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x]
CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> m a
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ r -> ParamFilters -> GeneralInstance -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> GeneralInstance -> m ()
validateGeneralInstance r
r ParamFilters
pa2 GeneralInstance
t
where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: m a -> m a
check m a
x2 = m a
x2 m a -> String -> m a
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":"
checkTypeFail :: TypeResolver r => r -> [(String,[String])] -> String -> CompileInfo ()
checkTypeFail :: r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail r
r [(String, [String])]
pa String
x = do
([GeneralInstance
t],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([GeneralInstance], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x]
CompileInfo () -> CompileInfo ()
forall a. CompileInfo a -> CompileInfo ()
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ r -> ParamFilters -> GeneralInstance -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> GeneralInstance -> m ()
validateGeneralInstance r
r ParamFilters
pa2 GeneralInstance
t
where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: CompileInfo a -> CompileInfo ()
check :: CompileInfo a -> CompileInfo ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
checkDefinesSuccess :: TypeResolver r => r -> [(String,[String])] -> String -> CompileInfo ()
checkDefinesSuccess :: r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesSuccess r
r [(String, [String])]
pa String
x = do
([DefinesInstance
t],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([DefinesInstance], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x]
CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> m a
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ r -> ParamFilters -> DefinesInstance -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> DefinesInstance -> m ()
validateDefinesInstance r
r ParamFilters
pa2 DefinesInstance
t
where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: m a -> m a
check m a
x2 = m a
x2 m a -> String -> m a
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":"
checkDefinesFail :: TypeResolver r => r -> [(String,[String])] -> String -> CompileInfo ()
checkDefinesFail :: r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesFail r
r [(String, [String])]
pa String
x = do
([DefinesInstance
t],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([DefinesInstance], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x]
CompileInfo () -> CompileInfo ()
forall a. CompileInfo a -> CompileInfo ()
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ r -> ParamFilters -> DefinesInstance -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> DefinesInstance -> m ()
validateDefinesInstance r
r ParamFilters
pa2 DefinesInstance
t
where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: CompileInfo a -> CompileInfo ()
check :: CompileInfo a -> CompileInfo ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
containsExactly :: (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly :: [a] -> [a] -> CompileInfo ()
containsExactly [a]
actual [a]
expected = do
[a] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> CompileInfo ()
containsNoDuplicates [a]
actual
[a] -> [a] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsAtLeast [a]
actual [a]
expected
[a] -> [a] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsAtMost [a]
actual [a]
expected
containsNoDuplicates :: (Ord a, Show a) => [a] -> CompileInfo ()
containsNoDuplicates :: [a] -> CompileInfo ()
containsNoDuplicates [a]
expected =
(([a] -> CompileInfo ()) -> [[a]] -> CompileInfo ()
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m ()
mapErrorsM_ [a] -> CompileInfo ()
forall (m :: * -> *) a. (CompileErrorM m, Show a) => [a] -> m ()
checkSingle ([[a]] -> CompileInfo ()) -> [[a]] -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
group ([a] -> [[a]]) -> [a] -> [[a]]
forall a b. (a -> b) -> a -> b
$ [a] -> [a]
forall a. Ord a => [a] -> [a]
sort [a]
expected) CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! [a] -> String
forall a. Show a => a -> String
show [a]
expected
where
checkSingle :: [a] -> m ()
checkSingle xa :: [a]
xa@(a
x:a
_:[a]
_) =
String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" occurs " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xa) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" times"
checkSingle [a]
_ = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
containsAtLeast :: (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsAtLeast :: [a] -> [a] -> CompileInfo ()
containsAtLeast [a]
actual [a]
expected =
((a -> CompileInfo ()) -> [a] -> CompileInfo ()
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m ()
mapErrorsM_ (Set a -> a -> CompileInfo ()
forall a (m :: * -> *).
(Ord a, CompileErrorM m, Show a) =>
Set a -> a -> m ()
checkInActual (Set a -> a -> CompileInfo ()) -> Set a -> a -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList [a]
actual) [a]
expected) CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!!
[a] -> String
forall a. Show a => a -> String
show [a]
actual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
expected String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (expected)"
where
checkInActual :: Set a -> a -> m ()
checkInActual Set a
va a
v =
if a
v a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
va
then () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
v String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" was expected but not present"
containsAtMost :: (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsAtMost :: [a] -> [a] -> CompileInfo ()
containsAtMost [a]
actual [a]
expected =
((a -> CompileInfo ()) -> [a] -> CompileInfo ()
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m ()
mapErrorsM_ (Set a -> a -> CompileInfo ()
forall a (m :: * -> *).
(Ord a, CompileErrorM m, Show a) =>
Set a -> a -> m ()
checkInExpected (Set a -> a -> CompileInfo ()) -> Set a -> a -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList [a]
expected) [a]
actual) CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!!
[a] -> String
forall a. Show a => a -> String
show [a]
actual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
expected String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (expected)"
where
checkInExpected :: Set a -> a -> m ()
checkInExpected Set a
va a
v =
if a
v a -> Set a -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
va
then () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
v String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" is unexpected"
checkEquals :: (Eq a, Show a) => a -> a -> CompileInfo ()
checkEquals :: a -> a -> CompileInfo ()
checkEquals a
actual a
expected
| a
actual a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
expected = () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
"Expected " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
expected String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" but got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
actual
loadFile :: String -> IO String
loadFile :: String -> IO String
loadFile String
f = String -> IO String
readFile (String
"src" String -> String -> String
</> String
"Test" String -> String -> String
</> String
f)