Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / CLI.hs @ 51000365

History | View | Annotate | Download (4.2 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.HTools.CLI (testHTools_CLI) where
30

    
31
import Test.HUnit
32
import Test.QuickCheck
33

    
34
import Control.Monad
35
import Data.List
36
import Text.Printf (printf)
37

    
38
import Test.Ganeti.TestHelper
39
import Test.Ganeti.TestCommon
40
import Test.Ganeti.Common
41

    
42
import Ganeti.HTools.CLI as CLI
43
import qualified Ganeti.HTools.Program as Program
44
import qualified Ganeti.HTools.Types as Types
45

    
46
-- | Test correct parsing.
47
prop_parseISpec :: String -> Int -> Int -> Int -> Property
48
prop_parseISpec descr dsk mem cpu =
49
  let str = printf "%d,%d,%d" dsk mem cpu::String
50
  in parseISpecString descr str ==? Types.Ok (Types.RSpec cpu mem dsk)
51

    
52
-- | Test parsing failure due to wrong section count.
53
prop_parseISpecFail :: String -> Property
54
prop_parseISpecFail descr =
55
  forAll (choose (0,100) `suchThat` ((/=) 3)) $ \nelems ->
56
  forAll (replicateM nelems arbitrary) $ \values ->
57
  let str = intercalate "," $ map show (values::[Int])
58
  in case parseISpecString descr str of
59
       Types.Ok v -> failTest $ "Expected failure, got " ++ show v
60
       _ -> passTest
61

    
62
-- | Test a few string arguments.
63
prop_string_arg :: String -> Property
64
prop_string_arg argument =
65
  let args = [ (oDataFile,      optDataFile)
66
             , (oDynuFile,      optDynuFile)
67
             , (oSaveCluster,   optSaveCluster)
68
             , (oPrintCommands, optShowCmds)
69
             , (oLuxiSocket,    optLuxi)
70
             , (oIAllocSrc,     optIAllocSrc)
71
             ]
72
  in conjoin $ map (\(o, opt) ->
73
                      checkOpt Just defaultOptions
74
                      failTest (const (==?)) Just (argument, o, opt)) args
75

    
76
-- | Test a few positive arguments.
77
prop_numeric_arg :: Positive Double -> Property
78
prop_numeric_arg (Positive argument) =
79
  let args = [ (oMaxCpu,     optMcpu)
80
             , (oMinDisk,    Just . optMdsk)
81
             , (oMinGain,    Just . optMinGain)
82
             , (oMinGainLim, Just . optMinGainLim)
83
             , (oMinScore,   Just . optMinScore)
84
             ]
85
  in conjoin $
86
     map (\(x, y) -> checkOpt (Just . show) defaultOptions
87
                     failTest (const (==?)) Just (argument, x, y)) args
88

    
89
-- | Test a few boolean arguments.
90
case_bool_arg :: Assertion
91
case_bool_arg =
92
  mapM_ (checkOpt (const Nothing) defaultOptions assertFailure
93
                  assertEqual id)
94
        [ (False, oDiskMoves,    optDiskMoves)
95
        , (False, oInstMoves,    optInstMoves)
96
        , (True,  oEvacMode,     optEvacMode)
97
        , (True,  oExecJobs,     optExecJobs)
98
        , (True,  oNoHeaders,    optNoHeaders)
99
        , (True,  oNoSimulation, optNoSimulation)
100
        ]
101

    
102
-- | Tests a few invalid arguments.
103
case_wrong_arg :: Assertion
104
case_wrong_arg = do
105
  mapM_ (passFailOpt defaultOptions assertFailure (return ()))
106
        [ (oSpindleUse,   "-1", "1")
107
        , (oSpindleUse,   "a",  "1")
108
        , (oMaxCpu,       "-1", "1")
109
        , (oMinDisk,      "a",  "1")
110
        , (oMinGainLim,   "a",  "1")
111
        , (oMaxSolLength, "x",  "10")
112
        , (oStdSpec,      "no-such-spec", "1,1,1")
113
        , (oTieredSpec,   "no-such-spec", "1,1,1")
114
        ]
115

    
116
-- | Test that all binaries support some common options.
117
case_stdopts :: Assertion
118
case_stdopts =
119
  mapM_ (\(name, (_, o)) -> checkEarlyExit defaultOptions name o)
120
      Program.personalities
121

    
122
testSuite "HTools/CLI"
123
          [ 'prop_parseISpec
124
          , 'prop_parseISpecFail
125
          , 'prop_string_arg
126
          , 'prop_numeric_arg
127
          , 'case_bool_arg
128
          , 'case_wrong_arg
129
          , 'case_stdopts
130
          ]