aboutsummaryrefslogtreecommitdiff
path: root/tests
diff options
context:
space:
mode:
authorJoris2016-03-13 21:26:03 +0100
committerJoris2016-03-13 21:26:03 +0100
commit47623ec732ec19c765c0a1ebffd9b234f81e0d01 (patch)
treea52969d730e64d1303e62efa8c36b03a7be7f1a5 /tests
Initial commit
Diffstat (limited to 'tests')
-rw-r--r--tests/Helper.hs34
-rw-r--r--tests/Test.hs104
2 files changed, 138 insertions, 0 deletions
diff --git a/tests/Helper.hs b/tests/Helper.hs
new file mode 100644
index 0000000..5979ae2
--- /dev/null
+++ b/tests/Helper.hs
@@ -0,0 +1,34 @@
+module Helper
+ ( forceGetConfig
+ , getConfig
+ ) where
+
+
+import System.IO (hClose)
+import System.IO.Temp (withSystemTempFile)
+import System.Directory (removeFile)
+
+import Data.Text (Text)
+import qualified Data.Text.IO as T
+import Data.Maybe (fromJust)
+
+import Data.ConfigManager
+import Data.ConfigManager.Config
+
+forceGetConfig :: Text -> IO Config
+forceGetConfig = (fmap fromJust) . getConfig
+
+getConfig :: Text -> IO (Maybe Config)
+getConfig input =
+ withSystemTempFile "config-manager-test" (\filePath handle -> do
+ hClose handle
+ T.writeFile filePath input
+ config <- readConfig filePath
+ removeFile filePath
+ putStrLn . show $ config
+ return $ eitherToMaybe config
+ )
+
+eitherToMaybe :: Either a b -> Maybe b
+eitherToMaybe (Left _) = Nothing
+eitherToMaybe (Right x) = Just x
diff --git a/tests/Test.hs b/tests/Test.hs
new file mode 100644
index 0000000..51ced1f
--- /dev/null
+++ b/tests/Test.hs
@@ -0,0 +1,104 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Main
+ ( main
+ ) where
+
+import Prelude hiding (lookup)
+
+import qualified Data.HashMap.Strict as M
+
+import Test.Framework
+import Test.Framework.Providers.HUnit
+import Test.HUnit hiding (Test)
+
+import Data.ConfigManager
+import Data.ConfigManager.Config
+import qualified Data.Text as T
+
+import Helper (forceGetConfig, getConfig)
+
+main :: IO ()
+main = defaultMain tests
+
+tests :: [Test]
+tests =
+ [ testCase "binding" bindingAssertion
+ , testCase "name" nameAssertion
+ , testCase "value" valueAssertion
+ , testCase "skip" skipAssertion
+ ]
+
+bindingAssertion :: Assertion
+bindingAssertion = do
+ empty <- forceGetConfig ""
+ assertEqual "empty" (M.fromList []) (hashMap empty)
+
+ oneBinding <- forceGetConfig "x = \"foo\""
+ assertEqual "one binding present" (Just "foo") (lookup "x" oneBinding :: Maybe String)
+ assertEqual "one binding missing" Nothing (lookup "y" oneBinding :: Maybe String)
+ 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" (Just "baz") (lookup "z" multipleBindings :: Maybe String)
+
+ overlappingBindings <- forceGetConfig $ T.unlines
+ [ "x = \"foo\""
+ , "y = \"bar\""
+ , "x = \"baz\""
+ ]
+ assertEqual "overlapping bindings count" 2 (M.size . hashMap $ overlappingBindings)
+ assertEqual "overlapping bindings redefinition" (Just "baz") (lookup "x" overlappingBindings :: Maybe String)
+
+nameAssertion :: Assertion
+nameAssertion = do
+ validNames <- forceGetConfig $ T.unlines
+ [ "validIdent = \"foo\" "
+ , "valid_ident = \"foo\""
+ , "valid-ident = \"foo\""
+ ]
+ assertEqual "validIdent" (Just "foo") (lookup "validIdent" validNames :: Maybe String)
+ assertEqual "valid_ident" (Just "foo") (lookup "valid_ident" validNames :: Maybe String)
+ assertEqual "valid-ident" (Just "foo") (lookup "valid-ident" validNames :: Maybe String)
+
+ 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 "
+ , " "
+ ]
+ assertEqual "string" (Just "lorem ipsum sir dolor emet") (lookup "a" config :: Maybe String)
+ assertEqual "integer" (Just 4) (lookup "b" config :: Maybe Int)
+ assertEqual "double 1" (Just 4.0) (lookup "b" config :: Maybe Double)
+ assertEqual "double 2" (Just 5.0) (lookup "c" config :: Maybe Double)
+ assertEqual "integer fail" Nothing (lookup "c" config :: Maybe Int)
+ 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" (Just "foo") (lookup "x" config :: Maybe String)
+ assertEqual "bindings y" (Just "bar") (lookup "y" config :: Maybe String)