Skip to content

Commit

Permalink
Merge branch 'mdimjasevic/26-ignore-dot-files' of github.com:juspay/f…
Browse files Browse the repository at this point in the history
…encer into mdimjasevic/26-runtime-ignoredotfiles-env-var
  • Loading branch information
Marko Dimjašević committed Oct 28, 2019
2 parents 0ce515e + 066f499 commit 3de7d4b
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 36 deletions.
1 change: 1 addition & 0 deletions fencer.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@ test-suite test-fencer
, directory
, filepath
, grpc-haskell
, named
, neat-interpolation
, proto3-wire
, proto3-suite
Expand Down
88 changes: 52 additions & 36 deletions test/Fencer/Rules/Test.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLabels #-}
Expand All @@ -10,12 +11,13 @@ import BasePrelude
import Data.List (sortOn)
import Data.Text (Text)
import qualified Data.Text.IO as TIO
import Named ((:!), arg)
import NeatInterpolation (text)
import qualified System.IO.Temp as Temp
import System.FilePath ((</>))
import System.FilePath (splitFileName, (</>))
import System.Directory (createDirectoryIfMissing)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit (assertEqual, testCase)
import Test.Tasty.HUnit (assertEqual, Assertion, testCase)

import Fencer.Rules
import Fencer.Settings (getSettingsFromEnvironment, settingsIgnoreDotFiles)
Expand All @@ -31,35 +33,53 @@ tests = testGroup "Rule tests"
, test_rulesLoadRulesRUNTIME_IGNOREDOTFILES
]

-- | A helper function for loading rules and making sure they are as
-- expected.
loadRules :: String -> Bool -> IO ()
loadRules dirTemplate ignoreDotFiles =
Temp.withSystemTempDirectory dirTemplate $ \tempDir -> do
TIO.writeFile (tempDir </> "config1.yml") domain1Text
TIO.writeFile (tempDir </> "config2.yaml") domain2Text
definitions <-
loadRulesFromDirectory
(#directory tempDir)
(#ignoreDotFiles ignoreDotFiles)
-- | Create given directory structure and check that 'loadRulesFromDirectory'
-- produces expected result.
expectLoadRules
:: "ignoreDotFiles" :! Bool
-> "files" :! [(FilePath, Text)]
-> "result" :! [DomainDefinition]
-> Assertion
expectLoadRules
(arg #ignoreDotFiles -> ignoreDotFiles)
(arg #files -> files)
(arg #result -> result) =
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
forM_ files $ \(path, txt) -> do
let (dir, file) = splitFileName path
createDirectoryIfMissing True (tempDir </> dir)
TIO.writeFile (tempDir </> dir </> file) txt
definitions <- loadRulesFromDirectory
(#directory tempDir)
(#ignoreDotFiles ignoreDotFiles)
assertEqual "unexpected definitions"
(sortOn domainDefinitionId [domain1, domain2])
(sortOn domainDefinitionId result)
(sortOn domainDefinitionId definitions)


-- | test that 'loadRulesFromDirectory' loads rules from YAML files.
test_rulesLoadRulesYaml :: TestTree
test_rulesLoadRulesYaml =
testCase "Rules are loaded from YAML files" $
loadRules "fencer-config" True
expectLoadRules
(#ignoreDotFiles True)
(#files
[ ("config1.yml", domain1Text)
, ("config2.yaml", domain2Text) ]
)
(#result [domain1, domain2])

-- | test that 'loadRulesFromDirectory' loads rules from a
-- dot-directory when dot-files should be ignored.
test_rulesLoadRulesDotDirectory :: TestTree
test_rulesLoadRulesDotDirectory =
testCase "Rules are loaded from a dot-directory" $
loadRules ".fencer-config" True

expectLoadRules
(#ignoreDotFiles True)
(#files
[ (".domain1/config1.yml", domain1Text)
, (".domain2/config2.yaml", domain2Text) ]
)
(#result [domain1, domain2])

-- | test that 'loadRulesFromDirectory' respects the
-- RUNTIME_IGNOREDOTFILES environment variable.
Expand Down Expand Up @@ -87,31 +107,27 @@ test_rulesLoadRulesRUNTIME_IGNOREDOTFILES =
test_rulesLoadRulesNonYaml :: TestTree
test_rulesLoadRulesNonYaml =
testCase "Rules are loaded from non-YAML files" $
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
TIO.writeFile (tempDir </> "config1.bin") domain1Text
TIO.writeFile (tempDir </> "config2") domain2Text
definitions <-
loadRulesFromDirectory (#directory tempDir) (#ignoreDotFiles True)
assertEqual "unexpected definitions"
(sortOn domainDefinitionId [domain1, domain2])
(sortOn domainDefinitionId definitions)
expectLoadRules
(#ignoreDotFiles True)
(#files
[ ("config1.bin", domain1Text)
, ("config2", domain2Text) ]
)
(#result [domain1, domain2])

-- | Test that 'loadRulesFromDirectory' loads rules recursively.
--
-- This matches the behavior of @lyft/ratelimit@.
test_rulesLoadRulesRecursively :: TestTree
test_rulesLoadRulesRecursively =
testCase "Rules are loaded recursively" $
Temp.withSystemTempDirectory "fencer-config" $ \tempDir -> do
createDirectoryIfMissing True (tempDir </> "domain1")
TIO.writeFile (tempDir </> "domain1/config.yml") domain1Text
createDirectoryIfMissing True (tempDir </> "domain2/config")
TIO.writeFile (tempDir </> "domain2/config/config.yml") domain2Text
definitions <-
loadRulesFromDirectory (#directory tempDir) (#ignoreDotFiles True)
assertEqual "unexpected definitions"
(sortOn domainDefinitionId [domain1, domain2])
(sortOn domainDefinitionId definitions)
expectLoadRules
(#ignoreDotFiles True)
(#files
[ ("domain1/config.yml", domain1Text)
, ("domain2/config/config.yml", domain2Text) ]
)
(#result [domain1, domain2])

----------------------------------------------------------------------------
-- Sample definitions
Expand Down

0 comments on commit 3de7d4b

Please sign in to comment.