{-# LANGUAGE OverloadedStrings #-} module Main ( main ) where import Prelude hiding (lookup) import qualified Data.HashMap.Strict as M import Data.Maybe (fromJust) import Data.Either (isLeft) import Data.Text (Text) import Test.Framework import Test.Framework.Providers.HUnit import Test.HUnit hiding (Test) import Data.ConfigManager import Data.ConfigManager.Types (Config(..)) import qualified Data.Text as T import Data.Time.Clock (DiffTime) import qualified Data.Time.Clock as Time import Helper (forceGetConfig, getConfig, eitherToMaybe) main :: IO () main = defaultMain tests tests :: [Test] tests = [ testCase "binding" bindingAssertion , testCase "lookupDefault" lookupDefaultAssertion , testCase "name" nameAssertion , testCase "value" valueAssertion , testCase "skip" skipAssertion , testCase "import" importAssertion , testCase "duration" durationAssertion ] bindingAssertion :: Assertion bindingAssertion = do empty <- forceGetConfig "" assertEqual "empty" (M.fromList []) (hashMap empty) oneBinding <- forceGetConfig "x = \"foo\"" assertEqual "one binding present" (Right "foo") (lookup "x" oneBinding) assertBool "one binding missing" (isLeft (lookup "y" oneBinding :: Either Text Int)) assertEqual "one binding count" 1 (M.size . hashMap $ oneBinding) multipleBindings <- forceGetConfig $ T.unlines [ "x = \"foo\"" , "y = \"bar\"" , "z = \"baz\"" ] assertEqual "multiple bindings count" 3 (M.size . hashMap $ multipleBindings) assertEqual "multiple bindings last" (Right "baz") (lookup "z" multipleBindings) overlappingBindings <- forceGetConfig $ T.unlines [ "x = \"foo\"" , "y = \"bar\"" , "x = \"baz\"" ] assertEqual "overlapping bindings count" 2 (M.size . hashMap $ overlappingBindings) assertEqual "overlapping bindings redefinition" (Right "baz") (lookup "x" overlappingBindings) lookupDefaultAssertion :: Assertion lookupDefaultAssertion = do config <- forceGetConfig "x = 5" assertEqual "x" 5 (lookupDefault 10 "x" config :: Int) assertEqual "y" 10 (lookupDefault 10 "y" config :: Int) nameAssertion :: Assertion nameAssertion = do validNames <- forceGetConfig $ T.unlines [ "validIdent = \"foo\" " , "valid_ident = \"foo\"" , "valid-ident = \"foo\"" ] assertEqual "validIdent" (Right "foo") (lookup "validIdent" validNames) assertEqual "valid_ident" (Right "foo") (lookup "valid_ident" validNames) assertEqual "valid-ident" (Right "foo") (lookup "valid-ident" validNames) invalid1 <- getConfig "-invalid_ident = \"foo\"" assertEqual "-invalid" Nothing invalid1 invalid2 <- getConfig "_invalid = \"foo\"" assertEqual "_invalid" Nothing invalid2 valueAssertion :: Assertion valueAssertion = do config <- forceGetConfig $ T.unlines [ "a = \"lorem ipsum sir dolor emet\"" , "b = 4 " , "c = 5.0 " , "d = True " ] assertEqual "string" (Right "lorem ipsum sir dolor emet") (lookup "a" config) assertEqual "integer" (Right 4) (lookup "b" config) assertEqual "double 1" (Right 4.0) (lookup "b" config) assertEqual "double 2" (Right 5.0) (lookup "c" config) assertBool "integer fail" (isLeft $ (lookup "c" config :: Either Text Int)) assertEqual "boolean" (Right True) (lookup "d" config) return () skipAssertion :: Assertion skipAssertion = do config <- forceGetConfig $ T.unlines [ " " , " # Comment " , " x = \"foo\" " , " " , " #### " , " " , " y = \"bar\" # Other comment" , " " ] assertEqual "bindings count" 2 (M.size . hashMap $ config) assertEqual "bindings x" (Right "foo") (lookup "x" config) assertEqual "bindings y" (Right "bar") (lookup "y" config) importAssertion :: Assertion importAssertion = do config <- fromJust . eitherToMaybe <$> readConfig "tests/resources/a.conf" assertEqual "a" (Right "foo") (lookup "a" config) assertEqual "b" (Right 15) (lookup "b" config) assertEqual "c" (Right "re baz") (lookup "c" config) assertEqual "d" (Right "zap") (lookup "d" config) assertEqual "e" (Right "re nam") (lookup "e" config) assertEqual "f" (Right 8.5) (lookup "f" config) missingConfig <- getConfig "import \"required.conf\"" assertEqual "missing config" Nothing missingConfig missingOptionalConfig <- forceGetConfig $ T.unlines [ "importMaybe \"required.conf\"" , "x = 4" ] assertEqual "missing optional config" (Right 4) (lookup "x" missingOptionalConfig) durationAssertion :: Assertion durationAssertion = do config <- forceGetConfig $ T.unlines [ "a = 1 second" , "b = 5 seconds" , "c = 1 minute" , "d = 10 minutes" , "e = 1 hour" , "f = 7 hours" , "g = 1 day" , "h = 2 days" , "i = 1 week" , "j = 9 weeks" , "" , "k = 1 minutes" , "l = 20 weeks" ] let second = 1 let minute = 60 * second let hour = 60 * minute let day = 24 * hour let week = 7 * day assertEqual "a" (Right (Time.secondsToDiffTime $ 1 * second)) (lookup "a" config) assertEqual "b" (Right (Time.secondsToDiffTime $ 5 * second)) (lookup "b" config) assertEqual "c" (Right (Time.secondsToDiffTime $ 1 * minute)) (lookup "c" config) assertEqual "d" (Right (Time.secondsToDiffTime $ 10 * minute)) (lookup "d" config) assertEqual "e" (Right (Time.secondsToDiffTime $ 1 * hour)) (lookup "e" config) assertEqual "f" (Right (Time.secondsToDiffTime $ 7 * hour)) (lookup "f" config) assertEqual "g" (Right (Time.secondsToDiffTime $ 1 * day)) (lookup "g" config) assertEqual "h" (Right (Time.secondsToDiffTime $ 2 * day)) (lookup "h" config) assertEqual "i" (Right (Time.secondsToDiffTime $ 1 * week)) (lookup "i" config) assertEqual "j" (Right (Time.secondsToDiffTime $ 9 * week)) (lookup "j" config) assertBool "k" (isLeft (lookup "k" config :: Either Text DiffTime)) assertBool "l" (isLeft (lookup "l" config :: Either Text DiffTime))