root / htest / Test / Ganeti / Daemon.hs @ da1dcce1
History | View | Annotate | Download (2.5 kB)
1 |
{-# LANGUAGE TemplateHaskell #-} |
---|---|
2 |
{-# OPTIONS_GHC -fno-warn-orphans #-} |
3 |
|
4 |
{-| Unittests for ganeti-htools. |
5 |
|
6 |
-} |
7 |
|
8 |
{- |
9 |
|
10 |
Copyright (C) 2009, 2010, 2011, 2012 Google Inc. |
11 |
|
12 |
This program is free software; you can redistribute it and/or modify |
13 |
it under the terms of the GNU General Public License as published by |
14 |
the Free Software Foundation; either version 2 of the License, or |
15 |
(at your option) any later version. |
16 |
|
17 |
This program is distributed in the hope that it will be useful, but |
18 |
WITHOUT ANY WARRANTY; without even the implied warranty of |
19 |
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
20 |
General Public License for more details. |
21 |
|
22 |
You should have received a copy of the GNU General Public License |
23 |
along with this program; if not, write to the Free Software |
24 |
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
25 |
02110-1301, USA. |
26 |
|
27 |
-} |
28 |
|
29 |
module Test.Ganeti.Daemon (testDaemon) where |
30 |
|
31 |
import Test.QuickCheck hiding (Result) |
32 |
import Test.HUnit |
33 |
|
34 |
import Test.Ganeti.TestHelper |
35 |
import Test.Ganeti.TestCommon |
36 |
import Test.Ganeti.Common |
37 |
|
38 |
import Ganeti.Common |
39 |
import Ganeti.Daemon as Daemon |
40 |
|
41 |
{-# ANN module "HLint: ignore Use camelCase" #-} |
42 |
|
43 |
-- | Test a few string arguments. |
44 |
prop_string_arg :: String -> Property |
45 |
prop_string_arg argument = |
46 |
let args = [ (argument, oBindAddress, optBindAddress) |
47 |
] |
48 |
in conjoin $ |
49 |
map (checkOpt Just defaultOptions failTest (const (==?)) Just) args |
50 |
|
51 |
-- | Test a few integer arguments (only one for now). |
52 |
prop_numeric_arg :: Int -> Property |
53 |
prop_numeric_arg argument = |
54 |
checkOpt (Just . show) defaultOptions |
55 |
failTest (const (==?)) (Just . fromIntegral) |
56 |
(argument, oPort 0, optPort) |
57 |
|
58 |
-- | Test a few boolean arguments. |
59 |
case_bool_arg :: Assertion |
60 |
case_bool_arg = |
61 |
mapM_ (checkOpt (const Nothing) defaultOptions assertFailure |
62 |
assertEqual id) |
63 |
[ (False, oNoDaemonize, optDaemonize) |
64 |
, (True, oDebug, optDebug) |
65 |
, (True, oNoUserChecks, optNoUserChecks) |
66 |
] |
67 |
|
68 |
-- | Tests a few invalid arguments. |
69 |
case_wrong_arg :: Assertion |
70 |
case_wrong_arg = |
71 |
mapM_ (passFailOpt defaultOptions assertFailure (return ())) |
72 |
[ (oSyslogUsage, "foo", "yes") |
73 |
, (oPort 0, "x", "10") |
74 |
] |
75 |
|
76 |
-- | Test that the option list supports some common options. |
77 |
case_stdopts :: Assertion |
78 |
case_stdopts = |
79 |
checkEarlyExit defaultOptions "prog" [oShowHelp, oShowVer] [] |
80 |
|
81 |
testSuite "Daemon" |
82 |
[ 'prop_string_arg |
83 |
, 'prop_numeric_arg |
84 |
, 'case_bool_arg |
85 |
, 'case_wrong_arg |
86 |
, 'case_stdopts |
87 |
] |