Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / CLI.hs @ 879d9290

History | View | Annotate | Download (4.3 kB)

1 e1ee7d5a Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 e1ee7d5a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 e09c1fa0 Iustin Pop
module Test.Ganeti.HTools.CLI (testHTools_CLI) where
30 e1ee7d5a Iustin Pop
31 51000365 Iustin Pop
import Test.HUnit
32 e1ee7d5a Iustin Pop
import Test.QuickCheck
33 e1ee7d5a Iustin Pop
34 e1ee7d5a Iustin Pop
import Control.Monad
35 e1ee7d5a Iustin Pop
import Data.List
36 e1ee7d5a Iustin Pop
import Text.Printf (printf)
37 e1ee7d5a Iustin Pop
38 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
39 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
40 51000365 Iustin Pop
import Test.Ganeti.Common
41 e1ee7d5a Iustin Pop
42 01e52493 Iustin Pop
import Ganeti.BasicTypes
43 51000365 Iustin Pop
import Ganeti.HTools.CLI as CLI
44 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Program as Program
45 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
46 e1ee7d5a Iustin Pop
47 5b11f8db Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
48 5b11f8db Iustin Pop
49 e1ee7d5a Iustin Pop
-- | Test correct parsing.
50 20bc5360 Iustin Pop
prop_parseISpec :: String -> Int -> Int -> Int -> Property
51 20bc5360 Iustin Pop
prop_parseISpec descr dsk mem cpu =
52 e1ee7d5a Iustin Pop
  let str = printf "%d,%d,%d" dsk mem cpu::String
53 01e52493 Iustin Pop
  in parseISpecString descr str ==? Ok (Types.RSpec cpu mem dsk)
54 e1ee7d5a Iustin Pop
55 e1ee7d5a Iustin Pop
-- | Test parsing failure due to wrong section count.
56 20bc5360 Iustin Pop
prop_parseISpecFail :: String -> Property
57 20bc5360 Iustin Pop
prop_parseISpecFail descr =
58 5b11f8db Iustin Pop
  forAll (choose (0,100) `suchThat` (/= 3)) $ \nelems ->
59 e1ee7d5a Iustin Pop
  forAll (replicateM nelems arbitrary) $ \values ->
60 e1ee7d5a Iustin Pop
  let str = intercalate "," $ map show (values::[Int])
61 51000365 Iustin Pop
  in case parseISpecString descr str of
62 01e52493 Iustin Pop
       Ok v -> failTest $ "Expected failure, got " ++ show v
63 2e0bb81d Iustin Pop
       _ -> passTest
64 e1ee7d5a Iustin Pop
65 e1ee7d5a Iustin Pop
-- | Test a few string arguments.
66 51000365 Iustin Pop
prop_string_arg :: String -> Property
67 51000365 Iustin Pop
prop_string_arg argument =
68 51000365 Iustin Pop
  let args = [ (oDataFile,      optDataFile)
69 51000365 Iustin Pop
             , (oDynuFile,      optDynuFile)
70 51000365 Iustin Pop
             , (oSaveCluster,   optSaveCluster)
71 51000365 Iustin Pop
             , (oPrintCommands, optShowCmds)
72 51000365 Iustin Pop
             , (oLuxiSocket,    optLuxi)
73 51000365 Iustin Pop
             , (oIAllocSrc,     optIAllocSrc)
74 51000365 Iustin Pop
             ]
75 51000365 Iustin Pop
  in conjoin $ map (\(o, opt) ->
76 51000365 Iustin Pop
                      checkOpt Just defaultOptions
77 51000365 Iustin Pop
                      failTest (const (==?)) Just (argument, o, opt)) args
78 51000365 Iustin Pop
79 51000365 Iustin Pop
-- | Test a few positive arguments.
80 51000365 Iustin Pop
prop_numeric_arg :: Positive Double -> Property
81 51000365 Iustin Pop
prop_numeric_arg (Positive argument) =
82 51000365 Iustin Pop
  let args = [ (oMaxCpu,     optMcpu)
83 51000365 Iustin Pop
             , (oMinDisk,    Just . optMdsk)
84 51000365 Iustin Pop
             , (oMinGain,    Just . optMinGain)
85 51000365 Iustin Pop
             , (oMinGainLim, Just . optMinGainLim)
86 51000365 Iustin Pop
             , (oMinScore,   Just . optMinScore)
87 e1ee7d5a Iustin Pop
             ]
88 51000365 Iustin Pop
  in conjoin $
89 51000365 Iustin Pop
     map (\(x, y) -> checkOpt (Just . show) defaultOptions
90 51000365 Iustin Pop
                     failTest (const (==?)) Just (argument, x, y)) args
91 51000365 Iustin Pop
92 51000365 Iustin Pop
-- | Test a few boolean arguments.
93 51000365 Iustin Pop
case_bool_arg :: Assertion
94 51000365 Iustin Pop
case_bool_arg =
95 51000365 Iustin Pop
  mapM_ (checkOpt (const Nothing) defaultOptions assertFailure
96 51000365 Iustin Pop
                  assertEqual id)
97 51000365 Iustin Pop
        [ (False, oDiskMoves,    optDiskMoves)
98 51000365 Iustin Pop
        , (False, oInstMoves,    optInstMoves)
99 51000365 Iustin Pop
        , (True,  oEvacMode,     optEvacMode)
100 51000365 Iustin Pop
        , (True,  oExecJobs,     optExecJobs)
101 51000365 Iustin Pop
        , (True,  oNoHeaders,    optNoHeaders)
102 51000365 Iustin Pop
        , (True,  oNoSimulation, optNoSimulation)
103 51000365 Iustin Pop
        ]
104 51000365 Iustin Pop
105 51000365 Iustin Pop
-- | Tests a few invalid arguments.
106 51000365 Iustin Pop
case_wrong_arg :: Assertion
107 5b11f8db Iustin Pop
case_wrong_arg =
108 51000365 Iustin Pop
  mapM_ (passFailOpt defaultOptions assertFailure (return ()))
109 51000365 Iustin Pop
        [ (oSpindleUse,   "-1", "1")
110 51000365 Iustin Pop
        , (oSpindleUse,   "a",  "1")
111 51000365 Iustin Pop
        , (oMaxCpu,       "-1", "1")
112 51000365 Iustin Pop
        , (oMinDisk,      "a",  "1")
113 51000365 Iustin Pop
        , (oMinGainLim,   "a",  "1")
114 51000365 Iustin Pop
        , (oMaxSolLength, "x",  "10")
115 51000365 Iustin Pop
        , (oStdSpec,      "no-such-spec", "1,1,1")
116 51000365 Iustin Pop
        , (oTieredSpec,   "no-such-spec", "1,1,1")
117 51000365 Iustin Pop
        ]
118 51000365 Iustin Pop
119 51000365 Iustin Pop
-- | Test that all binaries support some common options.
120 51000365 Iustin Pop
case_stdopts :: Assertion
121 51000365 Iustin Pop
case_stdopts =
122 22278fa7 Iustin Pop
  mapM_ (\(name, (_, o, a)) -> checkEarlyExit defaultOptions name
123 22278fa7 Iustin Pop
                               (o ++ genericOpts) a) Program.personalities
124 e1ee7d5a Iustin Pop
125 e09c1fa0 Iustin Pop
testSuite "HTools/CLI"
126 20bc5360 Iustin Pop
          [ 'prop_parseISpec
127 20bc5360 Iustin Pop
          , 'prop_parseISpecFail
128 51000365 Iustin Pop
          , 'prop_string_arg
129 51000365 Iustin Pop
          , 'prop_numeric_arg
130 51000365 Iustin Pop
          , 'case_bool_arg
131 51000365 Iustin Pop
          , 'case_wrong_arg
132 51000365 Iustin Pop
          , 'case_stdopts
133 e1ee7d5a Iustin Pop
          ]