Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Common.hs @ 51000365

History | View | Annotate | Download (4.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for the 'Ganeti.Common' module.
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.Common
30
  ( testCommon
31
  , checkOpt
32
  , passFailOpt
33
  , checkEarlyExit
34
  ) where
35

    
36
import Test.QuickCheck hiding (Result)
37
import Test.HUnit
38

    
39
import qualified System.Console.GetOpt as GetOpt
40
import System.Exit
41

    
42
import Test.Ganeti.TestHelper
43
import Test.Ganeti.TestCommon
44

    
45
import Ganeti.BasicTypes
46
import Ganeti.Common
47

    
48
-- | Helper to check for correct parsing of an option.
49
checkOpt :: (StandardOptions b) =>
50
            (a -> Maybe String) -- ^ Converts the value into a cmdline form
51
         -> b                   -- ^ The default options
52
         -> (String -> c)       -- ^ Fail test function
53
         -> (String -> d -> d -> c) -- ^ Check for equality function
54
         -> (a -> d)            -- ^ Transforms the value to a compare val
55
         -> (a, GenericOptType b, b -> d) -- ^ Triple of value, the
56
                                          -- option, function to
57
                                          -- extract the set value
58
                                          -- from the options
59
         -> c
60
checkOpt repr defaults failfn eqcheck valfn
61
         (val, opt@(GetOpt.Option _ longs _ _), fn) =
62
  case longs of
63
    [] -> failfn "no long options?"
64
    cmdarg:_ ->
65
      case parseOptsInner defaults
66
             ["--" ++ cmdarg ++ maybe "" ("=" ++) (repr val)]
67
             "prog" [opt] of
68
        Left e -> failfn $ "Failed to parse option '" ++ cmdarg ++ ": " ++
69
                  show e
70
        Right (options, _) -> eqcheck ("Wrong value in option " ++
71
                                       cmdarg ++ "?") (valfn val) (fn options)
72

    
73
-- | Helper to check for correct and incorrect parsing of an option.
74
passFailOpt :: (StandardOptions b) =>
75
               b                 -- ^ The default options
76
            -> (String -> c)     -- ^ Fail test function
77
            -> c                 -- ^ Pass function
78
            -> (GenericOptType b, String, String)
79
            -- ^ The list of enabled options, fail value and pass value
80
            -> c
81
passFailOpt defaults failfn passfn
82
              (opt@(GetOpt.Option _ longs _ _), bad, good) =
83
  let prefix = "--" ++ head longs ++ "="
84
      good_cmd = prefix ++ good
85
      bad_cmd = prefix ++ bad in
86
  case (parseOptsInner defaults [bad_cmd]  "prog" [opt],
87
        parseOptsInner defaults [good_cmd] "prog" [opt]) of
88
    (Left _,  Right _) -> passfn
89
    (Right _, Right _) -> failfn $ "Command line '" ++ bad_cmd ++
90
                          "' succeeded when it shouldn't"
91
    (Left  _, Left  _) -> failfn $ "Command line '" ++ good_cmd ++
92
                          "' failed when it shouldn't"
93
    (Right _, Left  _) ->
94
      failfn $ "Command line '" ++ bad_cmd ++
95
               "' succeeded when it shouldn't, while command line '" ++
96
               good_cmd ++ "' failed when it shouldn't"
97

    
98
-- | Helper to test that a given option is accepted OK with quick exit.
99
checkEarlyExit :: (StandardOptions a) =>
100
                  a -> String -> [GenericOptType a] -> Assertion
101
checkEarlyExit defaults name options =
102
  mapM_ (\param ->
103
           case parseOptsInner defaults [param] name options of
104
             Left (code, _) ->
105
               assertEqual ("Program " ++ name ++
106
                            " returns invalid code " ++ show code ++
107
                            " for option " ++ param) ExitSuccess code
108
             _ -> assertFailure $ "Program " ++ name ++
109
                  " doesn't consider option " ++
110
                  param ++ " as early exit one"
111
        ) ["-h", "--help", "-V", "--version"]
112

    
113
-- | Test parseYesNo.
114
prop_parse_yes_no :: Bool -> Bool -> String -> Property
115
prop_parse_yes_no def testval val =
116
  forAll (elements [val, "yes", "no"]) $ \actual_val ->
117
  if testval
118
    then parseYesNo def Nothing ==? Ok def
119
    else let result = parseYesNo def (Just actual_val)
120
         in if actual_val `elem` ["yes", "no"]
121
              then result ==? Ok (actual_val == "yes")
122
              else property $ isBad result
123

    
124

    
125
testSuite "Common"
126
          [ 'prop_parse_yes_no
127
          ]