Skip to content

Commit

Permalink
Issue #26: adjust the test_serverResponseDuplicateDomainOrRule function
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević committed Nov 21, 2019
2 parents a13c351 + 680032c commit eb9aaf0
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 20 deletions.
12 changes: 6 additions & 6 deletions lib/Fencer/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module Fencer.Rules
( LoadRulesError(..)
, prettyPrintErrors
, loadRulesFromDirectory
, validatePotentialDomains
, definitionsToRuleTree
, domainToRuleTree
, applyRules
Expand Down Expand Up @@ -74,7 +75,7 @@ loadRulesFromDirectory
let filteredFiles = if ignoreDotFiles
then filter (not . isDotFile) files
else files
finalChecks <$> mapM loadFile filteredFiles
validatePotentialDomains <$> mapM loadFile filteredFiles
where
loadFile :: FilePath -> IO (Either LoadRulesError (Maybe DomainDefinition))
loadFile file = catch
Expand Down Expand Up @@ -122,13 +123,12 @@ loadRulesFromDirectory
dirs <- filterM isDirectory other
(files ++) <$> concatMapM listAllFiles dirs

-- | For a list of rule loading results, perform final checks to make
-- sure the behavior matches that of @lyft/ratelimit@. This function
-- is called from the 'loadRulesFromDirectory' function.
finalChecks
-- | Perform validation checks to make sure the behavior matches that
-- of @lyft/ratelimit@.
validatePotentialDomains
:: [Either LoadRulesError (Maybe DomainDefinition)]
-> Either [LoadRulesError] [DomainDefinition]
finalChecks res = case partitionEithers res of
validatePotentialDomains res = case partitionEithers res of
(errs@(_:_), _ ) -> Left errs
([] , mDomains) -> do
-- check if there are any duplicate domains
Expand Down
5 changes: 3 additions & 2 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module Fencer.Rules.Test
( tests
, writeAndLoadRules
-- example values
, domain1
, domain1Text
, domain2Text
, duplicateRuleDomain
Expand All @@ -22,7 +23,7 @@ import qualified Data.Yaml as Yaml
import Named ((:!), arg)
import NeatInterpolation (text)
import qualified System.IO.Temp as Temp
import System.FilePath (splitFileName, (</>))
import System.FilePath (takeDirectory, (</>))
import qualified System.Directory as Dir
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (assertBool, assertEqual, Assertion, testCase)
Expand Down Expand Up @@ -61,7 +62,7 @@ writeFile
(arg #modifyPerms -> modifyPerms) = do

let
(dir, _) = splitFileName path
dir = takeDirectory path
fullPath = root </> path
Dir.createDirectoryIfMissing True (root </> dir)
TIO.writeFile fullPath content
Expand Down
28 changes: 16 additions & 12 deletions test/Fencer/Server/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -200,20 +200,25 @@ test_serverResponseReadPermissions =
-- This behavior matches @lyft/ratelimit@.
test_serverResponseDuplicateDomainOrRule
:: "label" :! String
-> "files" :! [(FilePath, Text, Dir.Permissions -> Dir.Permissions)]
-> "definitionsOrFiles" :! Either [DomainDefinition] [(FilePath, Text, Dir.Permissions -> Dir.Permissions)]
-> TestTree
test_serverResponseDuplicateDomainOrRule
(arg #label -> label)
(arg #files -> files) =
(arg #definitionsOrFiles -> definitionsOrFiles) =
withResource createServer destroyServer $ \serverIO ->
testCase ("In presence of duplicate " ++ label ++ " all requests error") $
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
server <- serverIO
RTest.writeAndLoadRules
(#ignoreDotFiles False)
(#root tempDir)
(#files files)
>>= \case
df :: Either [LoadRulesError] [DomainDefinition] <-
case definitionsOrFiles of
Left domains ->
pure (validatePotentialDomains $ Right . Just <$> domains)
Right files ->
RTest.writeAndLoadRules
(#ignoreDotFiles False)
(#root tempDir)
(#files files)
case df of
Left _ ->
withService server $ \service -> do
response <- Proto.rateLimitServiceShouldRateLimit service $
Expand Down Expand Up @@ -244,10 +249,7 @@ test_serverResponseDuplicateDomain :: TestTree
test_serverResponseDuplicateDomain =
test_serverResponseDuplicateDomainOrRule
(#label "domains")
(#files
[ ("domain1" </> "config.yml", RTest.domain1Text, id)
, ("domain2" </> "config.yml", RTest.domain1Text, id) ]
)
(#definitionsOrFiles (Left $ replicate 2 RTest.domain1))

-- | Test that a request with a non-empty descriptor list results in a
-- response with an unknown status code in presence of a configuration
Expand All @@ -258,7 +260,9 @@ test_serverResponseDuplicateRule :: TestTree
test_serverResponseDuplicateRule =
test_serverResponseDuplicateDomainOrRule
(#label "rules")
(#files [("another.yaml", RTest.duplicateRuleDomain, id)])
(#definitionsOrFiles
(Right [("another.yaml", RTest.duplicateRuleDomain, id)])
)

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

0 comments on commit eb9aaf0

Please sign in to comment.