Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / TestCommon.hs @ 2733df51

History | View | Annotate | Download (2.7 kB)

1
{-| Unittest helpers for ganeti-htools.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Test.Ganeti.TestCommon where
27

    
28
import Control.Applicative
29
import Data.List
30
import Test.QuickCheck
31

    
32
-- * Constants
33

    
34
-- | Maximum memory (1TiB, somewhat random value).
35
maxMem :: Int
36
maxMem = 1024 * 1024
37

    
38
-- | Maximum disk (8TiB, somewhat random value).
39
maxDsk :: Int
40
maxDsk = 1024 * 1024 * 8
41

    
42
-- | Max CPUs (1024, somewhat random value).
43
maxCpu :: Int
44
maxCpu = 1024
45

    
46
-- | Max vcpu ratio (random value).
47
maxVcpuRatio :: Double
48
maxVcpuRatio = 1024.0
49

    
50
-- | Max spindle ratio (random value).
51
maxSpindleRatio :: Double
52
maxSpindleRatio = 1024.0
53

    
54
-- | Max nodes, used just to limit arbitrary instances for smaller
55
-- opcode definitions (e.g. list of nodes in OpTestDelay).
56
maxNodes :: Int
57
maxNodes = 32
58

    
59
-- | Max opcodes or jobs in a submit job and submit many jobs.
60
maxOpCodes :: Int
61
maxOpCodes = 16
62

    
63
-- * Helper functions
64

    
65
-- | Checks for equality with proper annotation.
66
(==?) :: (Show a, Eq a) => a -> a -> Property
67
(==?) x y = printTestCase
68
            ("Expected equality, but '" ++
69
             show x ++ "' /= '" ++ show y ++ "'") (x == y)
70
infix 3 ==?
71

    
72
-- | Show a message and fail the test.
73
failTest :: String -> Property
74
failTest msg = printTestCase msg False
75

    
76

    
77
-- * Arbitrary instances
78

    
79
-- | Defines a DNS name.
80
newtype DNSChar = DNSChar { dnsGetChar::Char }
81

    
82
instance Arbitrary DNSChar where
83
  arbitrary = do
84
    x <- elements (['a'..'z'] ++ ['0'..'9'] ++ "_-")
85
    return (DNSChar x)
86

    
87
instance Show DNSChar where
88
  show = show . dnsGetChar
89

    
90
-- | Generates a single name component.
91
getName :: Gen String
92
getName = do
93
  n <- choose (1, 64)
94
  dn <- vector n
95
  return (map dnsGetChar dn)
96

    
97
-- | Generates an entire FQDN.
98
getFQDN :: Gen String
99
getFQDN = do
100
  ncomps <- choose (1, 4)
101
  names <- vectorOf ncomps getName
102
  return $ intercalate "." names
103

    
104
-- | Combinator that generates a 'Maybe' using a sub-combinator.
105
getMaybe :: Gen a -> Gen (Maybe a)
106
getMaybe subgen = do
107
  bool <- arbitrary
108
  if bool
109
    then Just <$> subgen
110
    else return Nothing