Skip to content

Commit

Permalink
Issue #26: precise matching on error results in rule tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević committed Nov 25, 2019
1 parent 71bdcfe commit 3517482
Show file tree
Hide file tree
Showing 3 changed files with 29 additions and 26 deletions.
12 changes: 7 additions & 5 deletions lib/Fencer/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
module Fencer.Rules
( LoadRulesError(..)
, prettyPrintErrors
, showError
, loadRulesFromDirectory
, definitionsToRuleTree
, domainToRuleTree
Expand All @@ -32,14 +33,15 @@ data LoadRulesError
| LoadRulesIOError IOException
deriving stock (Show)

-- | Pretty-print a 'LoadRulesError'.
showError :: LoadRulesError -> String
showError (LoadRulesParseError file yamlEx) =
show file ++ ", " ++ (Yaml.prettyPrintParseException yamlEx)
showError (LoadRulesIOError ex) = "IO error: " ++ displayException ex

-- | Pretty-print a list of 'LoadRulesError's.
prettyPrintErrors :: [LoadRulesError] -> String
prettyPrintErrors = intercalate ", " . fmap showError
where
showError (LoadRulesParseError file yamlEx) =
show file ++ ", " ++ (Yaml.prettyPrintParseException yamlEx)
showError (LoadRulesIOError ex) =
"IO error: " ++ displayException ex

-- | Read rate limiting rules from a directory, recursively. Files are
-- assumed to be YAML, but do not have to have a @.yml@ extension. If
Expand Down
4 changes: 3 additions & 1 deletion test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,9 @@ test_rulesLoadRulesException =
]
)
(#result $ Left
[LoadRulesParseError "faultyDomain.yaml" $ Yaml.AesonException ""])
[LoadRulesParseError "faultyDomain.yaml" $
Yaml.AesonException
"Error in $.descriptors[1]: key \"key\" not present"])

-- | test that 'loadRulesFromDirectory' accepts a minimal
-- configuration containing only the domain id.
Expand Down
39 changes: 19 additions & 20 deletions test/Fencer/Rules/Test/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@

-- | Module with helper functions used in rules and other testing.
module Fencer.Rules.Test.Helpers
( toErrorList
, writeContentsToFile
( writeContentsToFile
, writeAndLoadRules
, expectLoadRules
)
Expand All @@ -15,19 +14,14 @@ import BasePrelude
import qualified Data.Text.IO as TIO
import Named ((:!), arg)
import qualified System.Directory as Dir
import System.FilePath (FilePath, takeDirectory, (</>))
import System.FilePath (FilePath, takeDirectory, takeFileName, (</>))
import qualified System.IO.Temp as Temp
import Test.Tasty.HUnit (assertBool, assertEqual, Assertion)
import Test.Tasty.HUnit (assertBool, assertFailure, Assertion)

import Fencer.Rules (LoadRulesError(..), loadRulesFromDirectory)
import Fencer.Rules (LoadRulesError(..), loadRulesFromDirectory, prettyPrintErrors, showError)
import Fencer.Rules.Test.Types (RuleFile(..))
import Fencer.Types (DomainDefinition(..))

-- | Get a list of values on the Left or an empty list if it is a
-- Right value.
toErrorList :: Either [a] [b] -> [a]
toErrorList (Right _) = []
toErrorList (Left xs) = xs

-- | Write contents to a path in the given root and modify file
-- permissions.
Expand Down Expand Up @@ -84,17 +78,22 @@ expectLoadRules
(#root tempDir)
(#files files)
>>= \case
f@(Left _) ->
-- Paths to temporary files vary and there is not much point
-- in writing down exact expected exception messages so the
-- only assertion made is that the number of exceptions is the
-- same.
assertEqual
"unexpected failure"
(length . toErrorList $ result)
(length . toErrorList $ f)
Left errs -> do
case result of
Right _ ->
assertFailure "Expected failures, got domain definitions!"
Left expectedErrs -> do
assertBool ("Exceptions differ! Expected: " ++
(prettyPrintErrors expectedErrs) ++ "\nGot: " ++
(prettyPrintErrors errs))
(((==) `on` (fmap showError))
(sortBy (compare `on` showError) (trimPath <$> expectedErrs))
(sortBy (compare `on` showError) (trimPath <$> errs)))
Right definitions -> assertBool "unexpected definitions"
(((==) `on` show)
(sortOn domainDefinitionId <$> result)
(Right $ sortOn domainDefinitionId definitions))

where
trimPath :: LoadRulesError -> LoadRulesError
trimPath (LoadRulesParseError p ex) = LoadRulesParseError (takeFileName p) ex
trimPath e = e

0 comments on commit 3517482

Please sign in to comment.