aboutsummaryrefslogtreecommitdiff
path: root/tests/Test.hs
blob: 03dc97969739185df47fbccc3ec6e84b9ae1cc0d (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
{-# LANGUAGE OverloadedStrings #-}

module Main
  ( main
  ) where

import Prelude hiding (lookup)

import qualified Data.HashMap.Strict as M
import Data.Maybe (fromJust)

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 Helper (forceGetConfig, getConfig, eitherToMaybe)

main :: IO ()
main = defaultMain tests

tests :: [Test]
tests =
  [ testCase "binding" bindingAssertion
  , testCase "name" nameAssertion
  , testCase "value" valueAssertion
  , testCase "skip" skipAssertion
  , testCase "import" importAssertion
  ]

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                           "
    , "d = True                          "
    ]
  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)
  assertEqual "boolean" (Just True) (lookup "d" config :: Maybe Bool)
  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)

importAssertion :: Assertion
importAssertion = do
  config <- fromJust . eitherToMaybe <$> readConfig "tests/resources/a.conf"
  assertEqual "a" (Just "foo") (lookup "a" config :: Maybe String)
  assertEqual "b" (Just 15) (lookup "b" config :: Maybe Int)
  assertEqual "c" (Just "re baz") (lookup "c" config :: Maybe String)
  assertEqual "d" (Just "zap") (lookup "d" config :: Maybe String)
  assertEqual "e" (Just "re nam") (lookup "e" config :: Maybe String)
  assertEqual "f" (Just 8.5) (lookup "f" config :: Maybe Double)

  missingConfig <- getConfig "import \"required.conf\""
  assertEqual "missing config" Nothing missingConfig

  missingOptionalConfig <- forceGetConfig $ T.unlines
    [ "importMaybe \"required.conf\""
    , "x = 4"
    ]
  assertEqual "missing optional config" (Just 4) (lookup "x" missingOptionalConfig :: Maybe Int)