Skip to content

Commit

Permalink
Issue #26: Add a rule test for faulty reload parsing (#105)
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević authored Nov 26, 2019
1 parent bbbcba9 commit e403ff0
Show file tree
Hide file tree
Showing 4 changed files with 105 additions and 30 deletions.
2 changes: 1 addition & 1 deletion lib/Fencer/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ validatePotentialDomains res = case partitionEithers res of
dupDomain
else Right domains
-- check if there are any duplicate rules
traverse_ (dupRuleCheck . (\dom -> (domainDefinitionId dom, dom))) domains
traverse_ (\dom -> dupRuleCheck (domainDefinitionId dom, dom)) domains

pure domains
where
Expand Down
73 changes: 69 additions & 4 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,14 +13,15 @@ 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 (testCase)
import Test.Tasty.HUnit (assertBool, assertFailure, testCase)

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


tests :: TestTree
Expand All @@ -33,8 +34,9 @@ tests = testGroup "Rule tests"
, test_rulesLoadRules_dontIgnoreDotFiles
, test_rulesLoadRulesException
, test_rulesLoadRulesMinimal
, test_rulesYAMLSeparator
, test_rulesLoadRulesReadPermissions
, test_rulesYAMLSeparator
, test_rulesReloadRules
, test_rulesLoadRulesDuplicateDomain
, test_rulesLoadRulesDuplicateRule
]
Expand Down Expand Up @@ -227,3 +229,66 @@ test_rulesLoadRulesReadPermissions =
file2 = simpleRuleFile
("domain2" </> "config" </> "config.yml")
domainDescriptorKeyText

-- | test that faulty rules in reloading with 'loadRulesFromDirectory'
-- are rejected and the valid ones that were previously loaded are
-- kept instead.
--
-- This matches the behavior of @lyft/ratelimit@.
test_rulesReloadRules :: TestTree
test_rulesReloadRules =
testCase "Rules fail to reload for an invalid domain" $
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
rules <- writeAndLoadRules
(#ignoreDotFiles False)
(#root tempDir)
(#files files)
failures <- writeAndLoadRules
(#ignoreDotFiles False)
(#root tempDir)
(#files filesFailure)
case (rules, failures) of
(Left errs, _) ->
assertFailure
("Expected domains, got failures: " ++
prettyPrintErrors (NE.toList errs))
(Right _, Right newDefinitions) ->
assertFailure
("Expected failures, got domains: " ++ show newDefinitions)
(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 =
[ simpleRuleFile ("domain1" </> "config.yml") domainDescriptorKeyValueText
, simpleRuleFile ("domain2" </> "config.yml") domainDescriptorKeyText ]
filesFailure :: [RuleFile]
filesFailure =
[ simpleRuleFile ("domain1" </> "config.yml") domainDescriptorKeyValueText
, simpleRuleFile "faultyDomain.yaml" faultyDomain ]

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

result :: Either (NonEmpty LoadRulesError) [DomainDefinition]
result = Right [domainDescriptorKeyValue, domainDescriptorKey]
12 changes: 8 additions & 4 deletions test/Fencer/Rules/Test/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Fencer.Rules.Test.Helpers
( writeContentsToFile
, writeAndLoadRules
, expectLoadRules
, trimPath
)
where

Expand Down Expand Up @@ -95,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
48 changes: 27 additions & 21 deletions test/Fencer/Server/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ test_serverResponseReadPermissions =
response <- Proto.rateLimitServiceShouldRateLimit service $
Grpc.ClientNormalRequest request 1 mempty
expectSuccess
(expectedResponse, Grpc.StatusOk)
(genericOKResponse, Grpc.StatusOk)
response
where
files :: [RuleFile]
Expand All @@ -194,20 +194,6 @@ test_serverResponseReadPermissions =
, Proto.rateLimitRequestHitsAddend = 0
}

expectedResponse :: Proto.RateLimitResponse
expectedResponse = Proto.RateLimitResponse
{ rateLimitResponseOverallCode =
Enumerated $ Right Proto.RateLimitResponse_CodeOK
, rateLimitResponseStatuses = Vector.singleton
Proto.RateLimitResponse_DescriptorStatus
{ rateLimitResponse_DescriptorStatusCode =
Enumerated $ Right Proto.RateLimitResponse_CodeOK
, rateLimitResponse_DescriptorStatusCurrentLimit = Nothing
, rateLimitResponse_DescriptorStatusLimitRemaining = 0
}
, rateLimitResponseHeaders = Vector.empty
}

-- | A parameterized test that checks if a request with a non-empty
-- descriptor list results in a response with an unknown status code
-- in presence of a configuration with a duplicate domain/rule.
Expand Down Expand Up @@ -283,12 +269,6 @@ test_serverResponseDuplicateRule =
-- Helpers
----------------------------------------------------------------------------

domainDefinitionWithoutRules :: DomainDefinition
domainDefinitionWithoutRules = DomainDefinition
{ domainDefinitionId = DomainId "domain"
, domainDefinitionDescriptors = []
}

-- | Assert that a gRPC request is successful and has a specific result and
-- status code.
expectSuccess
Expand Down Expand Up @@ -424,3 +404,29 @@ withService server act =
Grpc.withGRPCClient (clientConfig (serverPort server)) $ \grpcClient -> do
service <- Proto.rateLimitServiceClient grpcClient
act service

----------------------------------------------------------------------------
-- Various useful values
----------------------------------------------------------------------------

domainDefinitionWithoutRules :: DomainDefinition
domainDefinitionWithoutRules = DomainDefinition
{ domainDefinitionId = DomainId "domain"
, domainDefinitionDescriptors = []
}

-- | A generic response useful for testing situations where the server
-- replies with a generic OK response.
genericOKResponse :: Proto.RateLimitResponse
genericOKResponse = Proto.RateLimitResponse
{ rateLimitResponseOverallCode =
Enumerated $ Right Proto.RateLimitResponse_CodeOK
, rateLimitResponseStatuses = Vector.singleton
Proto.RateLimitResponse_DescriptorStatus
{ rateLimitResponse_DescriptorStatusCode =
Enumerated $ Right Proto.RateLimitResponse_CodeOK
, rateLimitResponse_DescriptorStatusCurrentLimit = Nothing
, rateLimitResponse_DescriptorStatusLimitRemaining = 0
}
, rateLimitResponseHeaders = Vector.empty
}

0 comments on commit e403ff0

Please sign in to comment.