Skip to content

Commit

Permalink
Issue #26: Support handling duplicate rules in configuration (#104)
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević authored Nov 26, 2019
1 parent cb8afc7 commit 6068fb8
Show file tree
Hide file tree
Showing 5 changed files with 169 additions and 33 deletions.
56 changes: 46 additions & 10 deletions lib/Fencer/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,12 @@ import qualified Data.Yaml as Yaml

import Fencer.Types


data LoadRulesError
= LoadRulesParseError FilePath Yaml.ParseException
| LoadRulesIOError IOException
| LoadRulesDuplicateDomain DomainId
| LoadRulesDuplicateRule DomainId RuleKey
deriving stock (Show)

-- | Pretty-print a 'LoadRulesError'.
Expand All @@ -44,6 +46,9 @@ showError (LoadRulesParseError file yamlEx) =
showError (LoadRulesIOError ex) = "IO error: " ++ displayException ex
showError (LoadRulesDuplicateDomain d) =
"duplicate domain " ++ (show . unDomainId $ d) ++ " in config file"
showError (LoadRulesDuplicateRule dom key) =
"duplicate descriptor composite key " ++
(show . unDomainId $ dom) ++ "." ++ (show . unRuleKey $ key)

-- | Pretty-print a list of 'LoadRulesError's.
prettyPrintErrors :: [LoadRulesError] -> String
Expand Down Expand Up @@ -127,18 +132,49 @@ validatePotentialDomains
-> Either (NonEmpty LoadRulesError) [DomainDefinition]
validatePotentialDomains res = case partitionEithers res of
(errs@(_:_), _ ) -> Left $ NE.fromList errs
([] , mRules) -> do
([] , mDomains) -> do
-- check if there are any duplicate domains
let
rules = catMaybes mRules
groupedRules :: [NonEmpty DomainDefinition] = NE.groupBy
((==) `on` (unDomainId . domainDefinitionId))
(NE.fromList $ sortOn domainDefinitionId rules)
if (length @[] rules /= length @[] groupedRules)
domains <- do
let
domains = catMaybes mDomains
groupedDomains :: [NonEmpty DomainDefinition] = NE.groupBy
((==) `on` domainDefinitionId)
(NE.fromList $ sortOn domainDefinitionId domains)
if (length @[] domains /= length @[] groupedDomains)
then
let dupDomain = NE.head . head $ filter (\l -> NE.length l > 1) groupedRules
in Left . pure . LoadRulesDuplicateDomain . domainDefinitionId $ dupDomain
else Right rules
let dupDomain =
NE.head . head $ filter (\l -> NE.length l > 1) groupedDomains
in
Left .
pure .
LoadRulesDuplicateDomain .
domainDefinitionId $
dupDomain
else Right domains
-- check if there are any duplicate rules
traverse_ (dupRuleCheck . (\dom -> (domainDefinitionId dom, dom))) domains

pure domains
where
dupRuleCheck
:: HasDescriptors a
=> (DomainId, a)
-> Either (NonEmpty LoadRulesError) ()
dupRuleCheck (_, d) | null @[] (descriptorsOf d) = Right ()
dupRuleCheck (domId, d) = do
let
descs = descriptorsOf d
groupedDescs :: [NonEmpty DescriptorDefinition] = NE.groupBy
((==) `on` descriptorDefinitionKey)
(NE.fromList $ sortOn (unRuleKey . descriptorDefinitionKey) descs)
if (length @[] descs /= length @[] groupedDescs)
then
let dupRule = NE.head . head $ filter (\l -> NE.length l > 1) groupedDescs
in Left . pure $
LoadRulesDuplicateRule
domId
(descriptorDefinitionKey dupRule)
else traverse_ (curry dupRuleCheck domId) $ descriptorsOf d

-- | Convert a list of descriptors to a 'RuleTree'.
definitionsToRuleTree :: [DescriptorDefinition] -> RuleTree
Expand Down
16 changes: 16 additions & 0 deletions lib/Fencer/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Fencer.Types
, RuleValue(..)
, unRuleValue
, RateLimit(..)
, HasDescriptors(..)

-- * Time units
, TimeUnit(..)
Expand Down Expand Up @@ -132,6 +133,15 @@ instance FromJSON RateLimit where
-- Rate limit rule configs
----------------------------------------------------------------------------

-- | A class describing how to access descriptor definitions within a
-- type, if there are any present at all.
--
-- This class is needed for accessing descriptor definitions in a
-- uniform way both when dealing with domain definitions and when
-- dealing with descriptor definitions.
class HasDescriptors a where
descriptorsOf :: a -> [DescriptorDefinition]

-- | Config for a single domain.
--
-- Corresponds to one YAML file.
Expand All @@ -150,6 +160,12 @@ data DescriptorDefinition = DescriptorDefinition
}
deriving stock (Eq, Show)

instance HasDescriptors DomainDefinition where
descriptorsOf = domainDefinitionDescriptors

instance HasDescriptors DescriptorDefinition where
descriptorsOf d = fromMaybe [] $ descriptorDefinitionDescriptors d

instance FromJSON DomainDefinition where
parseJSON = withObject "DomainDefinition" $ \o -> do
domainDefinitionId <- o .: "domain"
Expand Down
24 changes: 22 additions & 2 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ import Fencer.Rules
import Fencer.Rules.Test.Examples
import Fencer.Rules.Test.Helpers (expectLoadRules)
import Fencer.Rules.Test.Types
import Fencer.Types (DomainId(..))
import Fencer.Types (DomainId(..), RuleKey(..))


tests :: TestTree
Expand All @@ -36,6 +36,7 @@ tests = testGroup "Rule tests"
, test_rulesYAMLSeparator
, test_rulesLoadRulesReadPermissions
, test_rulesLoadRulesDuplicateDomain
, test_rulesLoadRulesDuplicateRule
]

-- | test that 'loadRulesFromDirectory' loads rules from YAML files.
Expand Down Expand Up @@ -185,7 +186,26 @@ test_rulesLoadRulesDuplicateDomain =
]
)
(#result $
Left $ NE.fromList [LoadRulesDuplicateDomain $ DomainId "domain1"])
Left $ NE.fromList [LoadRulesDuplicateDomain $ DomainId "domain1"]
)

-- | test that 'loadRulesFromDirectory' rejects a configuration with a
-- duplicate rule.
--
-- This matches the behavior of @lyft/ratelimit@.
test_rulesLoadRulesDuplicateRule :: TestTree
test_rulesLoadRulesDuplicateRule =
testCase "Error on a configuration with a duplicate rule" $
expectLoadRules
(#ignoreDotFiles False)
(#files [simpleRuleFile "another.yaml" duplicateRuleDomain])
(#result $
Left $ NE.fromList
[LoadRulesDuplicateRule
(DomainId "another")
(RuleKey "key1")
]
)

-- | test that 'loadRulesFromDirectory' loads a configuration file in
-- presence of another configuration file without read permissions.
Expand Down
21 changes: 21 additions & 0 deletions test/Fencer/Rules/Test/Examples.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module Fencer.Rules.Test.Examples
, minimalDomainText
, separatorDomain
, separatorDomainText
, duplicateRuleDomain
)
where

Expand Down Expand Up @@ -119,3 +120,23 @@ separatorDomainText = [text|
value: some value
- key: some key 2
|]

-- | The text value of a faulty domain definition that has a key
-- repeated.
duplicateRuleDomain :: Text
duplicateRuleDomain = [text|
domain: another
descriptors:
- key: key1
rate_limit:
unit: minute
requests_per_unit: 20
- key: key2
rate_limit:
unit: minute
requests_per_unit: 30
- key: key1
rate_limit:
unit: hour
requests_per_unit: 10
|]
85 changes: 64 additions & 21 deletions test/Fencer/Server/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import BasePrelude
import Data.ByteString (ByteString)
import qualified Data.Vector as Vector
import GHC.Exts (fromList)
import Named ((:!), arg)
import qualified Network.GRPC.HighLevel.Generated as Grpc
import Proto3.Suite.Types (Enumerated(..))
import qualified System.Directory as Dir
Expand All @@ -31,7 +32,12 @@ import Fencer.Server
import Fencer.Settings (defaultGRPCPort, getLogLevel, newLogger)
import Fencer.Types
import Fencer.Rules
import Fencer.Rules.Test.Examples (domainDescriptorKeyValueText, domainDescriptorKeyText, domainDescriptorKeyValue)
import Fencer.Rules.Test.Examples
( domainDescriptorKeyValueText
, domainDescriptorKeyText
, domainDescriptorKeyValue
, duplicateRuleDomain
)
import Fencer.Rules.Test.Helpers (writeAndLoadRules)
import Fencer.Rules.Test.Types (RuleFile(..), simpleRuleFile)
import qualified Fencer.Proto as Proto
Expand All @@ -49,6 +55,7 @@ tests = testGroup "Server tests"
, test_serverResponseEmptyDescriptorList
, test_serverResponseReadPermissions
, test_serverResponseDuplicateDomain
, test_serverResponseDuplicateRule
]

-- | Test that when Fencer is started without any rules provided to it (i.e.
Expand Down Expand Up @@ -197,30 +204,42 @@ test_serverResponseReadPermissions =
, rateLimitResponseHeaders = Vector.empty
}

-- | Test that 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.
-- | 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.
--
-- This behavior matches @lyft/ratelimit@.
test_serverResponseDuplicateDomain :: TestTree
test_serverResponseDuplicateDomain =
test_serverResponseDuplicateDomainOrRule
:: "label" :! String
-> "definitionsOrFiles" :! Either [DomainDefinition] [RuleFile]
-> TestTree
test_serverResponseDuplicateDomainOrRule
(arg #label -> label)
(arg #definitionsOrFiles -> definitionsOrFiles) =
withResource createServer destroyServer $ \serverIO ->
testCase "In presence of duplicate domains all requests error" $ do
server <- serverIO
pure (validatePotentialDomains $ Right . Just <$> domains) >>= \case
Left _ ->
withService server $ \service -> do
response <- Proto.rateLimitServiceShouldRateLimit service $
Grpc.ClientNormalRequest request 1 mempty
expectError
(unknownError "no rate limit configuration loaded")
response
Right _ -> assertFailure $
"Expected a failure, and got domain definitions instead"
testCase ("In presence of duplicate " ++ label ++ " all requests error") $
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
server <- serverIO
df :: Either (NonEmpty LoadRulesError) [DomainDefinition] <-
case definitionsOrFiles of
Left domains ->
pure (validatePotentialDomains $ Right . Just <$> domains)
Right files ->
writeAndLoadRules
(#ignoreDotFiles False)
(#root tempDir)
(#files files)
case df of
Left _ ->
withService server $ \service -> do
response <- Proto.rateLimitServiceShouldRateLimit service $
Grpc.ClientNormalRequest request 1 mempty
expectError
(unknownError "no rate limit configuration loaded")
response
Right _ -> assertFailure $
"Expected a failure, and got domain definitions instead"
where
domains :: [DomainDefinition]
domains = replicate 2 domainDescriptorKeyValue

request :: Proto.RateLimitRequest
request = Proto.RateLimitRequest
{ Proto.rateLimitRequestDomain = "domain1"
Expand All @@ -232,6 +251,30 @@ test_serverResponseDuplicateDomain =
, Proto.rateLimitRequestHitsAddend = 0
}

-- | Test that 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.
--
-- This behavior matches @lyft/ratelimit@.
test_serverResponseDuplicateDomain :: TestTree
test_serverResponseDuplicateDomain =
test_serverResponseDuplicateDomainOrRule
(#label "domains")
(#definitionsOrFiles (Left $ replicate 2 domainDescriptorKeyValue))

-- | Test that 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 rule.
--
-- This behavior matches @lyft/ratelimit@.
test_serverResponseDuplicateRule :: TestTree
test_serverResponseDuplicateRule =
test_serverResponseDuplicateDomainOrRule
(#label "rules")
(#definitionsOrFiles
(Right [simpleRuleFile "another.yaml" duplicateRuleDomain])
)

----------------------------------------------------------------------------
-- Helpers
----------------------------------------------------------------------------
Expand Down

0 comments on commit 6068fb8

Please sign in to comment.