Skip to content

Commit

Permalink
Issue #26: implement @effectfully's feedback on error expectations
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević committed Nov 26, 2019
1 parent 7c5da30 commit 32b4f38
Show file tree
Hide file tree
Showing 3 changed files with 35 additions and 31 deletions.
1 change: 0 additions & 1 deletion fencer.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,6 @@ test-suite test-fencer
, base-prelude
, bytestring
, directory
, either
, filepath
, grpc-haskell
, named
Expand Down
44 changes: 26 additions & 18 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,18 +9,17 @@ module Fencer.Rules.Test

import BasePrelude

import Data.Either.Combinators (mapLeft)
import qualified Data.List.NonEmpty as NE
import qualified Data.Yaml as Yaml
import qualified System.Directory as Dir
import System.FilePath ((</>))
import qualified System.IO.Temp as Temp
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (assertBool, assertEqual, assertFailure, testCase)
import Test.Tasty.HUnit (assertBool, assertFailure, testCase)

import Fencer.Rules
import Fencer.Rules.Test.Examples
import Fencer.Rules.Test.Helpers (expectLoadRules, writeAndLoadRules, toErrorList)
import Fencer.Rules.Test.Helpers (expectLoadRules, writeAndLoadRules, trimPath)
import Fencer.Rules.Test.Types
import Fencer.Types (DomainDefinition, domainDefinitionId, DomainId(..), RuleKey(..))

Expand Down Expand Up @@ -256,15 +255,24 @@ test_rulesReloadRules =
(Right _, Right newDefinitions) ->
assertFailure
("Expected failures, got domains: " ++ show newDefinitions)
(Right definitions, f@(Left _)) -> do
assertEqual
"unexpected failure"
(length . toErrorList $ mapLeft NE.toList f)
(length . toErrorList $ expectedFailure)
assertBool "unexpected definitions"
(((==) `on` show)
(sortOn domainDefinitionId <$> result)
(Right $ sortOn domainDefinitionId definitions))
(Right definitions, Left errs) -> do
let
sortedResult = sortOn domainDefinitionId <$> result
sortedDefs = sortOn domainDefinitionId definitions
assertBool
("Unexpected definitions! Expected: " ++ (show sortedResult) ++
"\nGot: " ++ show sortedDefs) $
((==) `on` show) sortedResult (Right sortedDefs)

assertBool
("Unexpected failure! Expected: " ++
(prettyPrintErrors . NE.toList $ expectedFailure) ++
"\nGot: " ++
(prettyPrintErrors . NE.toList $ errs)
) $
((==) `on` (fmap showError . NE.toList))
expectedFailure
(trimPath <$> errs)
where
files :: [RuleFile]
files =
Expand All @@ -275,12 +283,12 @@ test_rulesReloadRules =
[ simpleRuleFile ("domain1" </> "config.yml") domainDescriptorKeyValueText
, simpleRuleFile "faultyDomain.yaml" faultyDomain ]

expectedFailure :: Either [LoadRulesError] [DomainDefinition]
expectedFailure :: NonEmpty LoadRulesError
expectedFailure =
Left [LoadRulesParseError
"faultyDomain.yaml" $
Yaml.AesonException
"Error in $.descriptors[1]: key \"key\" not present"]
NE.fromList [LoadRulesParseError
"faultyDomain.yaml" $
Yaml.AesonException
"Error in $.descriptors[1]: key \"key\" not present"]

result :: Either [LoadRulesError] [DomainDefinition]
result :: Either (NonEmpty LoadRulesError) [DomainDefinition]
result = Right [domainDescriptorKeyValue, domainDescriptorKey]
21 changes: 9 additions & 12 deletions test/Fencer/Rules/Test/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,10 @@

-- | Module with helper functions used in rules and other testing.
module Fencer.Rules.Test.Helpers
( toErrorList
, writeContentsToFile
( writeContentsToFile
, writeAndLoadRules
, expectLoadRules
, trimPath
)
where

Expand All @@ -26,12 +26,6 @@ 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.
writeContentsToFile
Expand Down Expand Up @@ -102,7 +96,10 @@ expectLoadRules
(((==) `on` show)
(sortOn domainDefinitionId <$> result)
(Right $ sortOn domainDefinitionId definitions))
where
trimPath :: LoadRulesError -> LoadRulesError
trimPath (LoadRulesParseError p ex) = LoadRulesParseError (takeFileName p) ex
trimPath e = e

-- | Trim a path in a 'LoadRulesParseError' such that only the file
-- name is retained. This is useful in testing where a test file has
-- an unpredictable path in a temporary directory.
trimPath :: LoadRulesError -> LoadRulesError
trimPath (LoadRulesParseError p ex) = LoadRulesParseError (takeFileName p) ex
trimPath e = e

0 comments on commit 32b4f38

Please sign in to comment.