Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Hypervisor / Xen / XmParser.hs @ c5a957c3

History | View | Annotate | Download (6.3 kB)

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

    
4
{-| Unittests for @xm list --long@ parser -}
5

    
6
{-
7

    
8
Copyright (C) 2013 Google Inc.
9

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

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

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

    
25
-}
26

    
27
module Test.Ganeti.Hypervisor.Xen.XmParser
28
  ( testHypervisor_Xen_XmParser
29
  ) where
30

    
31
import Test.HUnit
32
import Test.QuickCheck as QuickCheck hiding (Result)
33

    
34
import Test.Ganeti.TestHelper
35
import Test.Ganeti.TestCommon
36

    
37
import Control.Monad (liftM)
38
import qualified Data.Attoparsec.Text as A
39
import Data.Text (pack)
40
import Data.Char
41
import qualified Data.Map as Map
42
import Text.Printf
43

    
44
import Ganeti.Hypervisor.Xen.Types
45
import Ganeti.Hypervisor.Xen.XmParser
46

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

    
49
-- * Arbitraries
50

    
51
-- | Arbitrary instance for generating configurations.
52
-- A completely arbitrary configuration would contain too many lists and its
53
-- size would be to big to be actually parsable in reasonable time.
54
-- This Arbitrary builds a random Config that is still of a reasonable size.
55
-- Avoid generating strings that might be interpreted as numbers.
56
instance Arbitrary LispConfig where
57
  arbitrary = frequency
58
    [ (5, liftM LCString (genName `suchThat` (not . canBeNumber)))
59
    , (5, liftM LCDouble arbitrary)
60
    , (1, liftM LCList (choose(1,20) >>= (`vectorOf` arbitrary)))
61
    ]
62

    
63
-- | Determines conservatively whether a string could be a number.
64
canBeNumber :: String -> Bool
65
canBeNumber [] = False
66
canBeNumber (c:[]) = canBeNumberChar c
67
canBeNumber (c:xs) = canBeNumberChar c && canBeNumber xs
68

    
69
-- | Determines whether a char can be part of the string representation of a
70
-- number (even in scientific notation).
71
canBeNumberChar :: Char -> Bool
72
canBeNumberChar c = isDigit c || (c `elem` "eE-")
73

    
74
-- | Generates an arbitrary @xm uptime@ output line.
75
instance Arbitrary UptimeInfo where
76
  arbitrary = do
77
    name <- genFQDN
78
    NonNegative idNum <- arbitrary :: Gen (NonNegative Int)
79
    NonNegative days <- arbitrary :: Gen (NonNegative Int)
80
    hours <- choose (0, 23) :: Gen Int
81
    mins <- choose (0, 59) :: Gen Int
82
    secs <- choose (0, 59) :: Gen Int
83
    let uptime :: String
84
        uptime =
85
          if days /= 0
86
            then printf "%d days, %d:%d:%d" days hours mins secs
87
            else printf "%d:%d:%d" hours mins secs
88
    return $ UptimeInfo name idNum uptime
89

    
90
-- * Helper functions for tests
91

    
92
-- | Function for testing whether a domain configuration is parsed correctly.
93
testDomain :: String -> Map.Map String Domain -> Assertion
94
testDomain fileName expectedContent = do
95
  fileContent <- readTestData fileName
96
  case A.parseOnly xmListParser $ pack fileContent of
97
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
98
    Right obtained -> assertEqual fileName expectedContent obtained
99

    
100
-- | Function for testing whether a @xm uptime@ output (stored in a file)
101
-- is parsed correctly.
102
testUptimeInfo :: String -> Map.Map Int UptimeInfo -> Assertion
103
testUptimeInfo fileName expectedContent = do
104
  fileContent <- readTestData fileName
105
  case A.parseOnly xmUptimeParser $ pack fileContent of
106
    Left msg -> assertFailure $ "Parsing failed: " ++ msg
107
    Right obtained -> assertEqual fileName expectedContent obtained
108

    
109
-- | Determines whether two LispConfig are equal, with the exception of Double
110
-- values, that just need to be "almost equal".
111
-- Meant mainly for testing purposes, given that Double values may be slightly
112
-- rounded during parsing.
113
isAlmostEqual :: LispConfig -> LispConfig -> Bool
114
isAlmostEqual (LCList c1) (LCList c2) =
115
  (length c1 == length c2) &&
116
  foldr
117
    (\current acc -> (acc && uncurry isAlmostEqual current))
118
    True
119
    (zip c1 c2)
120
isAlmostEqual (LCString s1) (LCString s2) = s1 == s2
121
isAlmostEqual (LCDouble d1) (LCDouble d2) = abs (d1-d2) <= 1e-12
122
isAlmostEqual _ _ = False
123

    
124
-- | Function to serialize LispConfigs in such a way that they can be rebuilt
125
-- again by the lispConfigParser.
126
serializeConf :: LispConfig -> String
127
serializeConf (LCList c) = "(" ++ unwords (map serializeConf c) ++ ")"
128
serializeConf (LCString s) = s
129
serializeConf (LCDouble d) = show d
130

    
131
-- | Function to serialize UptimeInfos in such a way that they can be rebuilt
132
-- againg by the uptimeLineParser.
133
serializeUptime :: UptimeInfo -> String
134
serializeUptime (UptimeInfo name idNum uptime) =
135
  printf "%s\t%d\t%s" name idNum uptime
136

    
137
-- | Test whether a randomly generated config can be parsed.
138
-- Implicitly, this also tests that the Show instance of Config is correct.
139
prop_config :: LispConfig -> Property
140
prop_config conf =
141
  case A.parseOnly lispConfigParser . pack . serializeConf $ conf of
142
        Left msg -> fail $ "Parsing failed: " ++ msg
143
        Right obtained -> property $ isAlmostEqual obtained conf
144

    
145
-- | Test whether a randomly generated UptimeInfo text line can be parsed.
146
prop_uptimeInfo :: UptimeInfo -> Property
147
prop_uptimeInfo uInfo =
148
  case A.parseOnly uptimeLineParser . pack . serializeUptime $ uInfo of
149
    Left msg -> fail $ "Parsing failed: " ++ msg
150
    Right obtained -> obtained ==? uInfo
151

    
152
-- | Test a Xen 4.0.1 @xm list --long@ output.
153
case_xen401list :: Assertion
154
case_xen401list = testDomain "xen-xm-list-long-4.0.1.txt" $
155
  Map.fromList
156
    [ ("Domain-0", Domain 0 "Domain-0" 184000.41332 ActualRunning Nothing)
157
    , ("instance1.example.com", Domain 119 "instance1.example.com" 24.116146647
158
      ActualBlocked Nothing)
159
    ]
160

    
161
-- | Test a Xen 4.0.1 @xm uptime@ output.
162
case_xen401uptime :: Assertion
163
case_xen401uptime = testUptimeInfo "xen-xm-uptime-4.0.1.txt" $
164
  Map.fromList
165
    [ (0, UptimeInfo "Domain-0" 0 "98 days,  2:27:44")
166
    , (119, UptimeInfo "instance1.example.com" 119 "15 days, 20:57:07")
167
    ]
168

    
169
testSuite "Hypervisor/Xen/XmParser"
170
          [ 'prop_config
171
          , 'prop_uptimeInfo
172
          , 'case_xen401list
173
          , 'case_xen401uptime
174
          ]