Skip to content

Commit

Permalink
Issue #26: use a more precise type for a list of errors
Browse files Browse the repository at this point in the history
  • Loading branch information
Marko Dimjašević committed Nov 25, 2019
1 parent 9cb3563 commit dbd6538
Show file tree
Hide file tree
Showing 4 changed files with 40 additions and 35 deletions.
46 changes: 23 additions & 23 deletions lib/Fencer/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ where
import BasePrelude

import Control.Concurrent.STM (atomically)
import qualified Data.List.NonEmpty as NE
import System.FilePath ((</>))
import qualified System.Logger as Logger
import System.Logger (Logger)
Expand Down Expand Up @@ -77,27 +78,26 @@ reloadRules logger settings appState = do
Logger.msg ("Loading rules from " ++ configDir)

-- Read and parse the rules
ruleDefinitionsVal :: Either [LoadRulesError] [DomainDefinition] <-
loadRulesFromDirectory
(#rootDirectory $ settingsRoot settings)
(#subDirectory $ settingsSubdirectory settings </> "config")
(#ignoreDotFiles (settingsIgnoreDotFiles settings))
case ruleDefinitionsVal of
Left fs ->
Logger.err logger $
Logger.msg ("error loading new configuration from runtime: " ++
prettyPrintErrors fs)
Right ruleDefinitions -> do
Logger.info logger $
Logger.msg ("Parsed rules for domains: " ++
show (map (unDomainId . domainDefinitionId) ruleDefinitions))
loadRulesFromDirectory
(#rootDirectory $ settingsRoot settings)
(#subDirectory $ settingsSubdirectory settings </> "config")
(#ignoreDotFiles (settingsIgnoreDotFiles settings))
>>= \case
Left fs ->
Logger.err logger $
Logger.msg ("error loading new configuration from runtime: " ++
prettyPrintErrors (NE.toList fs))
Right ruleDefinitions -> do
Logger.info logger $
Logger.msg ("Parsed rules for domains: " ++
show (map (unDomainId . domainDefinitionId) ruleDefinitions))

-- Recreate 'appStateRules'
--
-- There is no need to remove old rate limiting rules
atomically $
-- See the documentation of 'setRules' for details on what
-- happens with counters during rule reloading.
setRules appState (map domainToRuleTree ruleDefinitions)
Logger.info logger $
Logger.msg (Logger.val "Applied new rules")
-- Recreate 'appStateRules'
--
-- There is no need to remove old rate limiting rules
atomically $
-- See the documentation of 'setRules' for details on what
-- happens with counters during rule reloading.
setRules appState (map domainToRuleTree ruleDefinitions)
Logger.info logger $
Logger.msg (Logger.val "Applied new rules")
9 changes: 5 additions & 4 deletions lib/Fencer/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,9 @@ import BasePrelude
import Control.Applicative (liftA2)
import Control.Monad.Extra (partitionM, concatMapM, ifM)
import Data.Either (partitionEithers)
import Data.Maybe (catMaybes)
import qualified Data.HashMap.Strict as HM
import Data.List.NonEmpty (NonEmpty)
import Data.Maybe (catMaybes)
import qualified Data.List.NonEmpty as NE
import Named ((:!), arg)
import System.Directory (listDirectory, doesFileExist, doesDirectoryExist, getPermissions, pathIsSymbolicLink, readable)
Expand Down Expand Up @@ -60,7 +61,7 @@ loadRulesFromDirectory
:: "rootDirectory" :! FilePath
-> "subDirectory" :! FilePath
-> "ignoreDotFiles" :! Bool
-> IO (Either [LoadRulesError] [DomainDefinition])
-> IO (Either (NonEmpty LoadRulesError) [DomainDefinition])
loadRulesFromDirectory
(arg #rootDirectory -> rootDirectory)
(arg #subDirectory -> subDirectory)
Expand Down Expand Up @@ -123,9 +124,9 @@ loadRulesFromDirectory
-- of @lyft/ratelimit@.
validatePotentialDomains
:: [Either LoadRulesError (Maybe DomainDefinition)]
-> Either [LoadRulesError] [DomainDefinition]
-> Either (NonEmpty LoadRulesError) [DomainDefinition]
validatePotentialDomains res = case partitionEithers res of
(errs@(_:_), _ ) -> Left errs
(errs@(_:_), _ ) -> Left $ NE.fromList errs
([] , mRules) -> do
-- check if there are any duplicate domains
let
Expand Down
6 changes: 4 additions & 2 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Fencer.Rules.Test

import BasePrelude

import qualified Data.List.NonEmpty as NE
import qualified Data.Yaml as Yaml
import qualified System.Directory as Dir
import System.FilePath ((</>))
Expand Down Expand Up @@ -138,7 +139,7 @@ test_rulesLoadRulesException =
, simpleRuleFile "faultyDomain.yaml" faultyDomain
]
)
(#result $ Left
(#result $ Left $ NE.fromList
[LoadRulesParseError "faultyDomain.yaml" $
Yaml.AesonException
"Error in $.descriptors[1]: key \"key\" not present"])
Expand Down Expand Up @@ -183,7 +184,8 @@ test_rulesLoadRulesDuplicateDomain =
, simpleRuleFile "two.yaml" domainDescriptorKeyValueText
]
)
(#result $ Left [LoadRulesDuplicateDomain $ DomainId "domain1"])
(#result $
Left $ NE.fromList [LoadRulesDuplicateDomain $ DomainId "domain1"])

-- | test that 'loadRulesFromDirectory' loads a configuration file in
-- presence of another configuration file without read permissions.
Expand Down
14 changes: 8 additions & 6 deletions test/Fencer/Rules/Test/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@ where

import BasePrelude

import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NE
import qualified Data.Text.IO as TIO
import Named ((:!), arg)
import qualified System.Directory as Dir
Expand Down Expand Up @@ -46,7 +48,7 @@ writeAndLoadRules
:: "ignoreDotFiles" :! Bool
-> "root" :! FilePath
-> "files" :! [RuleFile]
-> IO (Either [LoadRulesError] [DomainDefinition])
-> IO (Either (NonEmpty LoadRulesError) [DomainDefinition])
writeAndLoadRules
(arg #ignoreDotFiles -> ignoreDotFiles)
(arg #root -> root)
Expand All @@ -66,7 +68,7 @@ writeAndLoadRules
expectLoadRules
:: "ignoreDotFiles" :! Bool
-> "files" :! [RuleFile]
-> "result" :! Either [LoadRulesError] [DomainDefinition]
-> "result" :! Either (NonEmpty LoadRulesError) [DomainDefinition]
-> Assertion
expectLoadRules
(arg #ignoreDotFiles -> ignoreDotFiles)
Expand All @@ -84,11 +86,11 @@ expectLoadRules
assertFailure "Expected failures, got domain definitions!"
Left expectedErrs ->
assertBool ("Exceptions differ! Expected: " ++
(prettyPrintErrors expectedErrs) ++ "\nGot: " ++
(prettyPrintErrors errs))
(prettyPrintErrors $ NE.toList expectedErrs) ++ "\nGot: " ++
(prettyPrintErrors $ NE.toList errs))
(((==) `on` (fmap showError))
(sortBy (compare `on` showError) (trimPath <$> expectedErrs))
(sortBy (compare `on` showError) (trimPath <$> errs)))
(NE.sortBy (compare `on` showError) (trimPath <$> expectedErrs))
(NE.sortBy (compare `on` showError) (trimPath <$> errs)))
Right definitions -> assertBool "unexpected definitions"
(((==) `on` show)
(sortOn domainDefinitionId <$> result)
Expand Down

0 comments on commit dbd6538

Please sign in to comment.