Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Utils.hs @ a5b270c5

History | View | Annotate | Download (4.8 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 26d62e4c Iustin Pop
module Test.Ganeti.Utils (testUtils) where
30 e1ee7d5a Iustin Pop
31 e1ee7d5a Iustin Pop
import Test.QuickCheck
32 e1ee7d5a Iustin Pop
33 e1ee7d5a Iustin Pop
import qualified Text.JSON as J
34 e1ee7d5a Iustin Pop
35 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
36 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
37 e1ee7d5a Iustin Pop
38 f3baf5ef Iustin Pop
import qualified Ganeti.JSON as JSON
39 e1ee7d5a Iustin Pop
import qualified Ganeti.HTools.Types as Types
40 a5b270c5 Iustin Pop
import Ganeti.Utils
41 e1ee7d5a Iustin Pop
42 e1ee7d5a Iustin Pop
-- | Helper to generate a small string that doesn't contain commas.
43 5b11f8db Iustin Pop
genNonCommaString :: Gen String
44 e1ee7d5a Iustin Pop
genNonCommaString = do
45 e1ee7d5a Iustin Pop
  size <- choose (0, 20) -- arbitrary max size
46 5b11f8db Iustin Pop
  vectorOf size (arbitrary `suchThat` (/=) ',')
47 e1ee7d5a Iustin Pop
48 e1ee7d5a Iustin Pop
-- | If the list is not just an empty element, and if the elements do
49 e1ee7d5a Iustin Pop
-- not contain commas, then join+split should be idempotent.
50 20bc5360 Iustin Pop
prop_commaJoinSplit :: Property
51 20bc5360 Iustin Pop
prop_commaJoinSplit =
52 e1ee7d5a Iustin Pop
  forAll (choose (0, 20)) $ \llen ->
53 5b11f8db Iustin Pop
  forAll (vectorOf llen genNonCommaString `suchThat` (/=) [""]) $ \lst ->
54 a5b270c5 Iustin Pop
  sepSplit ',' (commaJoin lst) ==? lst
55 e1ee7d5a Iustin Pop
56 e1ee7d5a Iustin Pop
-- | Split and join should always be idempotent.
57 5b11f8db Iustin Pop
prop_commaSplitJoin :: String -> Property
58 20bc5360 Iustin Pop
prop_commaSplitJoin s =
59 a5b270c5 Iustin Pop
  commaJoin (sepSplit ',' s) ==? s
60 e1ee7d5a Iustin Pop
61 e1ee7d5a Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
62 e1ee7d5a Iustin Pop
-- value.
63 20bc5360 Iustin Pop
prop_fromObjWithDefault :: Integer -> String -> Bool
64 20bc5360 Iustin Pop
prop_fromObjWithDefault def_value random_key =
65 e1ee7d5a Iustin Pop
  -- a missing key will be returned with the default
66 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
67 e1ee7d5a Iustin Pop
  -- a found key will be returned as is, not with default
68 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
69 e1ee7d5a Iustin Pop
       random_key (def_value+1) == Just def_value
70 e1ee7d5a Iustin Pop
71 e1ee7d5a Iustin Pop
-- | Test that functional if' behaves like the syntactic sugar if.
72 20bc5360 Iustin Pop
prop_if'if :: Bool -> Int -> Int -> Gen Prop
73 20bc5360 Iustin Pop
prop_if'if cnd a b =
74 a5b270c5 Iustin Pop
  if' cnd a b ==? if cnd then a else b
75 e1ee7d5a Iustin Pop
76 e1ee7d5a Iustin Pop
-- | Test basic select functionality
77 20bc5360 Iustin Pop
prop_select :: Int      -- ^ Default result
78 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of False values
79 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of True values
80 20bc5360 Iustin Pop
            -> Gen Prop -- ^ Test result
81 20bc5360 Iustin Pop
prop_select def lst1 lst2 =
82 a5b270c5 Iustin Pop
  select def (flist ++ tlist) ==? expectedresult
83 a5b270c5 Iustin Pop
    where expectedresult = if' (null lst2) def (head lst2)
84 e1ee7d5a Iustin Pop
          flist = zip (repeat False) lst1
85 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
86 e1ee7d5a Iustin Pop
87 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined default
88 20bc5360 Iustin Pop
prop_select_undefd :: [Int]            -- ^ List of False values
89 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
90 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
91 20bc5360 Iustin Pop
prop_select_undefd lst1 (NonEmpty lst2) =
92 a5b270c5 Iustin Pop
  select undefined (flist ++ tlist) ==? head lst2
93 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
94 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
95 e1ee7d5a Iustin Pop
96 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined list values
97 20bc5360 Iustin Pop
prop_select_undefv :: [Int]            -- ^ List of False values
98 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
99 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
100 20bc5360 Iustin Pop
prop_select_undefv lst1 (NonEmpty lst2) =
101 a5b270c5 Iustin Pop
  select undefined cndlist ==? head lst2
102 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
103 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
104 e1ee7d5a Iustin Pop
          cndlist = flist ++ tlist ++ [undefined]
105 e1ee7d5a Iustin Pop
106 20bc5360 Iustin Pop
prop_parseUnit :: NonNegative Int -> Property
107 20bc5360 Iustin Pop
prop_parseUnit (NonNegative n) =
108 a5b270c5 Iustin Pop
  parseUnit (show n) ==? Types.Ok n .&&.
109 a5b270c5 Iustin Pop
  parseUnit (show n ++ "m") ==? Types.Ok n .&&.
110 a5b270c5 Iustin Pop
  parseUnit (show n ++ "M") ==? Types.Ok (truncate n_mb::Int) .&&.
111 a5b270c5 Iustin Pop
  parseUnit (show n ++ "g") ==? Types.Ok (n*1024) .&&.
112 a5b270c5 Iustin Pop
  parseUnit (show n ++ "G") ==? Types.Ok (truncate n_gb::Int) .&&.
113 a5b270c5 Iustin Pop
  parseUnit (show n ++ "t") ==? Types.Ok (n*1048576) .&&.
114 a5b270c5 Iustin Pop
  parseUnit (show n ++ "T") ==? Types.Ok (truncate n_tb::Int) .&&.
115 e1ee7d5a Iustin Pop
  printTestCase "Internal error/overflow?"
116 e1ee7d5a Iustin Pop
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0) .&&.
117 a5b270c5 Iustin Pop
  property (Types.isBad (parseUnit (show n ++ "x")::Types.Result Int))
118 e1ee7d5a Iustin Pop
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
119 e1ee7d5a Iustin Pop
        n_gb = n_mb * 1000
120 e1ee7d5a Iustin Pop
        n_tb = n_gb * 1000
121 e1ee7d5a Iustin Pop
122 e1ee7d5a Iustin Pop
-- | Test list for the Utils module.
123 26d62e4c Iustin Pop
testSuite "Utils"
124 20bc5360 Iustin Pop
            [ 'prop_commaJoinSplit
125 20bc5360 Iustin Pop
            , 'prop_commaSplitJoin
126 20bc5360 Iustin Pop
            , 'prop_fromObjWithDefault
127 20bc5360 Iustin Pop
            , 'prop_if'if
128 20bc5360 Iustin Pop
            , 'prop_select
129 20bc5360 Iustin Pop
            , 'prop_select_undefd
130 20bc5360 Iustin Pop
            , 'prop_select_undefv
131 20bc5360 Iustin Pop
            , 'prop_parseUnit
132 e1ee7d5a Iustin Pop
            ]