Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / HTools / CLI.hs @ 559c4a98

History | View | Annotate | Download (4.4 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.BasicTypes
43
import Ganeti.HTools.CLI as CLI
44
import qualified Ganeti.HTools.Program as Program
45
import qualified Ganeti.HTools.Types as Types
46

    
47
{-# ANN module "HLint: ignore Use camelCase" #-}
48

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

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

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

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

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

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

    
119
-- | Test that all binaries support some common options.
120
case_stdopts :: Assertion
121
case_stdopts =
122
  mapM_ (\(name, (_, o, a, _)) -> do
123
           o' <- o
124
           checkEarlyExit defaultOptions name
125
             (o' ++ genericOpts) a) Program.personalities
126

    
127
testSuite "HTools/CLI"
128
          [ 'prop_parseISpec
129
          , 'prop_parseISpecFail
130
          , 'prop_string_arg
131
          , 'prop_numeric_arg
132
          , 'case_bool_arg
133
          , 'case_wrong_arg
134
          , 'case_stdopts
135
          ]