Skip to content

Commit

Permalink
fix(eo-phi-normalizer): allow optional "when" and "tests" in the rule…
Browse files Browse the repository at this point in the history
…s file
  • Loading branch information
deemp committed Nov 28, 2024
1 parent f417b6f commit dc71f63
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 7 deletions.
6 changes: 3 additions & 3 deletions eo-phi-normalizer/src/Language/EO/Phi/Rules/Yaml.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,8 +101,8 @@ data Rule = Rule
, pattern :: Object
, result :: Object
, fresh :: Maybe [FreshMetaId]
, when :: [Condition]
, tests :: [RuleTest]
, when :: Maybe [Condition]
, tests :: Maybe [RuleTest]
}
deriving (Generic, FromJSON, Show)

Expand Down Expand Up @@ -183,7 +183,7 @@ convertRule Rule{..} ctx obj = do
let pattern' = applySubst contextSubsts pattern
result' = applySubst contextSubsts result
subst <- matchObject pattern' obj
guard $ all (\cond -> checkCond ctx cond (contextSubsts <> subst)) when
guard $ all (\cond -> checkCond ctx cond (contextSubsts <> subst)) (fromMaybe [] when)
let substFresh = mkFreshSubst ctx result' fresh
result'' = applySubst (contextSubsts <> subst <> substFresh) result'
-- TODO #152:30m what context should we pass to evaluate meta funcs?
Expand Down
6 changes: 3 additions & 3 deletions eo-phi-normalizer/src/Language/EO/Phi/ToLaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ instance ToLatex RuleAttribute where
instance ToLatex Condition where
toLatex (IsNF nf) = inMathMode $ toLatex nf <> "\\in\\mathcal{N}"
toLatex (IsNFInsideFormation nf_inside_formation) =
(inMathMode $ toLatex nf_inside_formation) <> " is nf inside formation"
inMathMode (toLatex nf_inside_formation) <> " is nf inside formation"
toLatex (PresentAttrs (AttrsInBindings attrs bindings)) =
inMathMode $ fold (intersperse ", " (map toLatex attrs)) <> " \\in " <> foldMap toLatex bindings
toLatex (AbsentAttrs (AttrsInBindings attrs bindings)) =
Expand Down Expand Up @@ -147,7 +147,7 @@ instance ToLatex Rule where
<> inMathMode (toLatex result)
<> (if not (null when) || isNonEmptyContext context then "\\\\\\text {if }" else mempty)
<> maybe mempty (\c -> "&" <> toLatex c <> "\\\\") context
<> fold (intersperse ",\\\\" (map (("&" <>) . toLatex) when))
<> fold (intersperse ",\\\\" (maybe [] (map (("&" <>) . toLatex)) when))

instance ToLatex [Rule] where
toLatex rules =
Expand All @@ -166,7 +166,7 @@ ruleToLatexCompact (Rule name _ context _ pattern result _ when _) =
<> inMathMode (toLatex result)
<> (if not (null when) || isNonEmptyContext context then "\\quad\\text {if }" else "")
<> maybe mempty (\c -> toLatex c <> ", ") context
<> fold (intersperse ", " (map toLatex when))
<> fold (intersperse ", " (maybe [] (map toLatex) when))

rulesToLatexCompact :: [Rule] -> LaTeX
rulesToLatexCompact rules =
Expand Down
4 changes: 3 additions & 1 deletion eo-phi-normalizer/src/Language/EO/Test/YamlSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
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)
Expand All @@ -40,7 +41,8 @@ spec testPaths = describe "User-defined rules unit tests" do
describe ruleset.title do
forM_ ruleset.rules $ \rule -> do
describe rule.name do
forM_ rule.tests $ \ruleTest -> do
let tests' = fromMaybe [] rule.tests
forM_ tests' $ \ruleTest -> do
it ruleTest.name $
let rule' = convertRuleNamed rule
resultOneStep = applyOneRule (defaultContext [rule'] ruleTest.input) ruleTest.input
Expand Down

0 comments on commit dc71f63

Please sign in to comment.