{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Language.EO.Test.YamlSpec where
import Control.Monad (forM_)
import Data.Maybe (fromMaybe)
import Language.EO.Phi.Dataize.Context (defaultContext)
import Language.EO.Phi.Rules.Common (applyOneRule)
import Language.EO.Phi.Rules.Yaml (Rule (..), RuleSet (..), RuleTest (..), RuleTestOption (..), convertRuleNamed)
import Language.EO.Test.Yaml
import Test.Hspec
spec :: [FilePath] -> Spec
spec :: [String] -> Spec
spec [String]
testPaths = String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"User-defined rules unit tests" do
[String] -> (String -> Spec) -> Spec
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
testPaths ((String -> Spec) -> Spec) -> (String -> Spec) -> Spec
forall a b. (a -> b) -> a -> b
$ \String
path -> do
RuleSet
ruleset <- IO RuleSet -> SpecM () RuleSet
forall r a. IO r -> SpecM a r
runIO (IO RuleSet -> SpecM () RuleSet) -> IO RuleSet -> SpecM () RuleSet
forall a b. (a -> b) -> a -> b
$ String -> IO RuleSet
fileTests String
path
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe RuleSet
ruleset.title do
[Rule] -> (Rule -> Spec) -> Spec
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ RuleSet
ruleset.rules ((Rule -> Spec) -> Spec) -> (Rule -> Spec) -> Spec
forall a b. (a -> b) -> a -> b
$ \Rule
rule -> do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe Rule
rule.name do
let tests' :: [RuleTest]
tests' = [RuleTest] -> Maybe [RuleTest] -> [RuleTest]
forall a. a -> Maybe a -> a
fromMaybe [] Rule
rule.tests
[RuleTest] -> (RuleTest -> Spec) -> Spec
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [RuleTest]
tests' ((RuleTest -> Spec) -> Spec) -> (RuleTest -> Spec) -> Spec
forall a b. (a -> b) -> a -> b
$ \RuleTest
ruleTest -> do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it RuleTest
ruleTest.name (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
let rule' :: NamedRule
rule' = Rule -> NamedRule
convertRuleNamed Rule
rule
resultOneStep :: [(String, Object)]
resultOneStep = Context -> Object -> [(String, Object)]
applyOneRule ([NamedRule] -> Object -> Context
defaultContext [NamedRule
rule'] RuleTest
ruleTest.input) RuleTest
ruleTest.input
normalizationResult :: [(String, Object)]
normalizationResult = [(String, Object)]
-> ([RuleTestOption] -> [(String, Object)])
-> Maybe [RuleTestOption]
-> [(String, Object)]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [(String, Object)]
resultOneStep (\[RuleTestOption]
lst -> if Bool -> RuleTestOption
TakeOne Bool
True RuleTestOption -> [RuleTestOption] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [RuleTestOption]
lst then Int -> [(String, Object)] -> [(String, Object)]
forall a. Int -> [a] -> [a]
take Int
1 [(String, Object)]
resultOneStep else [(String, Object)]
resultOneStep) RuleTest
ruleTest.options
expected :: [Object]
expected = RuleTest
ruleTest.output
in ((String, Object) -> Object) -> [(String, Object)] -> [Object]
forall a b. (a -> b) -> [a] -> [b]
map (String, Object) -> Object
forall a b. (a, b) -> b
snd [(String, Object)]
normalizationResult [Object] -> [Object] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [Object]
expected