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