Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Common.hs @ 93f1e606

History | View | Annotate | Download (7 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 the 'Ganeti.Common' module.
5 51000365 Iustin Pop
6 51000365 Iustin Pop
-}
7 51000365 Iustin Pop
8 51000365 Iustin Pop
{-
9 51000365 Iustin Pop
10 9fb621af Yiannis Tsiouris
Copyright (C) 2009, 2010, 2011, 2012, 2013 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.Common
30 51000365 Iustin Pop
  ( testCommon
31 51000365 Iustin Pop
  , checkOpt
32 51000365 Iustin Pop
  , passFailOpt
33 51000365 Iustin Pop
  , checkEarlyExit
34 51000365 Iustin Pop
  ) where
35 51000365 Iustin Pop
36 51000365 Iustin Pop
import Test.QuickCheck hiding (Result)
37 51000365 Iustin Pop
import Test.HUnit
38 51000365 Iustin Pop
39 51000365 Iustin Pop
import qualified System.Console.GetOpt as GetOpt
40 51000365 Iustin Pop
import System.Exit
41 51000365 Iustin Pop
42 51000365 Iustin Pop
import Test.Ganeti.TestHelper
43 51000365 Iustin Pop
import Test.Ganeti.TestCommon
44 51000365 Iustin Pop
45 51000365 Iustin Pop
import Ganeti.BasicTypes
46 51000365 Iustin Pop
import Ganeti.Common
47 9fb621af Yiannis Tsiouris
import Ganeti.HTools.Program.Main (personalities)
48 9fb621af Yiannis Tsiouris
49 9fb621af Yiannis Tsiouris
{-# ANN module "HLint: ignore Use camelCase" #-}
50 51000365 Iustin Pop
51 51000365 Iustin Pop
-- | Helper to check for correct parsing of an option.
52 51000365 Iustin Pop
checkOpt :: (StandardOptions b) =>
53 51000365 Iustin Pop
            (a -> Maybe String) -- ^ Converts the value into a cmdline form
54 51000365 Iustin Pop
         -> b                   -- ^ The default options
55 51000365 Iustin Pop
         -> (String -> c)       -- ^ Fail test function
56 51000365 Iustin Pop
         -> (String -> d -> d -> c) -- ^ Check for equality function
57 51000365 Iustin Pop
         -> (a -> d)            -- ^ Transforms the value to a compare val
58 51000365 Iustin Pop
         -> (a, GenericOptType b, b -> d) -- ^ Triple of value, the
59 51000365 Iustin Pop
                                          -- option, function to
60 51000365 Iustin Pop
                                          -- extract the set value
61 51000365 Iustin Pop
                                          -- from the options
62 51000365 Iustin Pop
         -> c
63 51000365 Iustin Pop
checkOpt repr defaults failfn eqcheck valfn
64 ce207617 Iustin Pop
         (val, opt@(GetOpt.Option _ longs _ _, _), fn) =
65 51000365 Iustin Pop
  case longs of
66 51000365 Iustin Pop
    [] -> failfn "no long options?"
67 51000365 Iustin Pop
    cmdarg:_ ->
68 51000365 Iustin Pop
      case parseOptsInner defaults
69 51000365 Iustin Pop
             ["--" ++ cmdarg ++ maybe "" ("=" ++) (repr val)]
70 22278fa7 Iustin Pop
             "prog" [opt] [] of
71 51000365 Iustin Pop
        Left e -> failfn $ "Failed to parse option '" ++ cmdarg ++ ": " ++
72 51000365 Iustin Pop
                  show e
73 51000365 Iustin Pop
        Right (options, _) -> eqcheck ("Wrong value in option " ++
74 51000365 Iustin Pop
                                       cmdarg ++ "?") (valfn val) (fn options)
75 51000365 Iustin Pop
76 51000365 Iustin Pop
-- | Helper to check for correct and incorrect parsing of an option.
77 51000365 Iustin Pop
passFailOpt :: (StandardOptions b) =>
78 51000365 Iustin Pop
               b                 -- ^ The default options
79 51000365 Iustin Pop
            -> (String -> c)     -- ^ Fail test function
80 51000365 Iustin Pop
            -> c                 -- ^ Pass function
81 51000365 Iustin Pop
            -> (GenericOptType b, String, String)
82 51000365 Iustin Pop
            -- ^ The list of enabled options, fail value and pass value
83 51000365 Iustin Pop
            -> c
84 51000365 Iustin Pop
passFailOpt defaults failfn passfn
85 ce207617 Iustin Pop
              (opt@(GetOpt.Option _ longs _ _, _), bad, good) =
86 72747d91 Iustin Pop
  let first_opt = case longs of
87 72747d91 Iustin Pop
                    [] -> error "no long options?"
88 72747d91 Iustin Pop
                    x:_ -> x
89 72747d91 Iustin Pop
      prefix = "--" ++ first_opt ++ "="
90 51000365 Iustin Pop
      good_cmd = prefix ++ good
91 51000365 Iustin Pop
      bad_cmd = prefix ++ bad in
92 22278fa7 Iustin Pop
  case (parseOptsInner defaults [bad_cmd]  "prog" [opt] [],
93 22278fa7 Iustin Pop
        parseOptsInner defaults [good_cmd] "prog" [opt] []) of
94 51000365 Iustin Pop
    (Left _,  Right _) -> passfn
95 51000365 Iustin Pop
    (Right _, Right _) -> failfn $ "Command line '" ++ bad_cmd ++
96 51000365 Iustin Pop
                          "' succeeded when it shouldn't"
97 51000365 Iustin Pop
    (Left  _, Left  _) -> failfn $ "Command line '" ++ good_cmd ++
98 51000365 Iustin Pop
                          "' failed when it shouldn't"
99 51000365 Iustin Pop
    (Right _, Left  _) ->
100 51000365 Iustin Pop
      failfn $ "Command line '" ++ bad_cmd ++
101 51000365 Iustin Pop
               "' succeeded when it shouldn't, while command line '" ++
102 51000365 Iustin Pop
               good_cmd ++ "' failed when it shouldn't"
103 51000365 Iustin Pop
104 51000365 Iustin Pop
-- | Helper to test that a given option is accepted OK with quick exit.
105 51000365 Iustin Pop
checkEarlyExit :: (StandardOptions a) =>
106 22278fa7 Iustin Pop
                  a -> String -> [GenericOptType a] -> [ArgCompletion]
107 22278fa7 Iustin Pop
               -> Assertion
108 22278fa7 Iustin Pop
checkEarlyExit defaults name options arguments =
109 51000365 Iustin Pop
  mapM_ (\param ->
110 22278fa7 Iustin Pop
           case parseOptsInner defaults [param] name options arguments of
111 51000365 Iustin Pop
             Left (code, _) ->
112 51000365 Iustin Pop
               assertEqual ("Program " ++ name ++
113 51000365 Iustin Pop
                            " returns invalid code " ++ show code ++
114 51000365 Iustin Pop
                            " for option " ++ param) ExitSuccess code
115 51000365 Iustin Pop
             _ -> assertFailure $ "Program " ++ name ++
116 51000365 Iustin Pop
                  " doesn't consider option " ++
117 51000365 Iustin Pop
                  param ++ " as early exit one"
118 51000365 Iustin Pop
        ) ["-h", "--help", "-V", "--version"]
119 51000365 Iustin Pop
120 51000365 Iustin Pop
-- | Test parseYesNo.
121 51000365 Iustin Pop
prop_parse_yes_no :: Bool -> Bool -> String -> Property
122 51000365 Iustin Pop
prop_parse_yes_no def testval val =
123 51000365 Iustin Pop
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
124 51000365 Iustin Pop
  if testval
125 51000365 Iustin Pop
    then parseYesNo def Nothing ==? Ok def
126 51000365 Iustin Pop
    else let result = parseYesNo def (Just actual_val)
127 51000365 Iustin Pop
         in if actual_val `elem` ["yes", "no"]
128 51000365 Iustin Pop
              then result ==? Ok (actual_val == "yes")
129 51000365 Iustin Pop
              else property $ isBad result
130 51000365 Iustin Pop
131 9fb621af Yiannis Tsiouris
-- | Check that formatCmdUsage works similar to Python _FormatUsage.
132 9fb621af Yiannis Tsiouris
case_formatCommands :: Assertion
133 9fb621af Yiannis Tsiouris
case_formatCommands =
134 9fb621af Yiannis Tsiouris
  assertEqual "proper wrap for HTools Main"
135 9fb621af Yiannis Tsiouris
    resCmdTest (formatCommands personalities)
136 9fb621af Yiannis Tsiouris
  where resCmdTest :: [String]
137 9fb621af Yiannis Tsiouris
        resCmdTest =
138 80ae381e Klaus Aehlig
          [ " hail     - Ganeti IAllocator plugin that implements the instance\
139 9fb621af Yiannis Tsiouris
            \ placement and"
140 80ae381e Klaus Aehlig
          , "            movement using the same algorithm as hbal(1)"
141 80ae381e Klaus Aehlig
          , " harep    - auto-repair tool that detects certain kind of problems\
142 80ae381e Klaus Aehlig
            \ with"
143 80ae381e Klaus Aehlig
          , "            instances and applies the allowed set of solutions"
144 80ae381e Klaus Aehlig
          , " hbal     - cluster balancer that looks at the current state of\
145 9fb621af Yiannis Tsiouris
            \ the cluster and"
146 80ae381e Klaus Aehlig
          , "            computes a series of steps designed to bring the\
147 9fb621af Yiannis Tsiouris
            \ cluster into a"
148 80ae381e Klaus Aehlig
          , "            better state"
149 80ae381e Klaus Aehlig
          , " hcheck   - cluster checker; prints information about cluster's\
150 80ae381e Klaus Aehlig
            \ health and"
151 80ae381e Klaus Aehlig
          , "            checks whether a rebalance done using hbal would help"
152 80ae381e Klaus Aehlig
          , " hinfo    - cluster information printer; it prints information\
153 9fb621af Yiannis Tsiouris
            \ about the current"
154 80ae381e Klaus Aehlig
          , "            cluster state and its residing nodes/instances"
155 80ae381e Klaus Aehlig
          , " hroller  - cluster rolling maintenance helper; it helps\
156 9fb621af Yiannis Tsiouris
            \ scheduling node reboots"
157 80ae381e Klaus Aehlig
          , "            in a manner that doesn't conflict with the instances'\
158 9fb621af Yiannis Tsiouris
            \ topology"
159 80ae381e Klaus Aehlig
          , " hscan    - tool for scanning clusters via RAPI and saving their\
160 9fb621af Yiannis Tsiouris
            \ data in the"
161 80ae381e Klaus Aehlig
          , "            input format used by hbal(1) and hspace(1)"
162 80ae381e Klaus Aehlig
          , " hspace   - computes how many additional instances can be fit on a\
163 80ae381e Klaus Aehlig
            \ cluster,"
164 80ae381e Klaus Aehlig
          , "            while maintaining N+1 status."
165 80ae381e Klaus Aehlig
          , " hsqueeze - cluster dynamic power management;  it powers up and\
166 80ae381e Klaus Aehlig
            \ down nodes to"
167 80ae381e Klaus Aehlig
          , "            keep the amount of free online resources in a given\
168 80ae381e Klaus Aehlig
            \ range"
169 9fb621af Yiannis Tsiouris
          ]
170 51000365 Iustin Pop
171 51000365 Iustin Pop
testSuite "Common"
172 51000365 Iustin Pop
          [ 'prop_parse_yes_no
173 9fb621af Yiannis Tsiouris
          , 'case_formatCommands
174 51000365 Iustin Pop
          ]