Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (4.4 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

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

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

    
48
-- * Arbitraries
49

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

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

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

    
73
-- * Helper functions for tests
74

    
75
-- | Function for testing whether a domain configuration is parsed correctly.
76
testDomain :: String -> Map.Map String Domain -> Assertion
77
testDomain fileName expectedContent = do
78
    fileContent <- readTestData fileName
79
    case A.parseOnly xmListParser $ pack fileContent of
80
        Left msg -> assertFailure $ "Parsing failed: " ++ msg
81
        Right obtained -> assertEqual fileName expectedContent obtained
82

    
83
-- | Determines whether two LispConfig are equal, with the exception of Double
84
-- values, that just need to be "almost equal".
85
-- Meant mainly for testing purposes, given that Double values may be slightly
86
-- rounded during parsing.
87
isAlmostEqual :: LispConfig -> LispConfig -> Bool
88
isAlmostEqual (LCList c1) (LCList c2) =
89
  (length c1 == length c2) &&
90
  foldr
91
    (\current acc -> (acc && uncurry isAlmostEqual current))
92
    True
93
    (zip c1 c2)
94
isAlmostEqual (LCString s1) (LCString s2) = s1 == s2
95
isAlmostEqual (LCDouble d1) (LCDouble d2) = abs (d1-d2) <= 1e-12
96
isAlmostEqual _ _ = False
97

    
98
-- | Function to serialize LispConfigs in such a way that they can be rebuilt
99
-- again by the lispConfigParser.
100
serializeConf :: LispConfig -> String
101
serializeConf (LCList c) = "(" ++ unwords (map serializeConf c) ++ ")"
102
serializeConf (LCString s) = s
103
serializeConf (LCDouble d) = show d
104

    
105
-- | Test whether a randomly generated config can be parsed.
106
-- Implicitly, this also tests that the Show instance of Config is correct.
107
prop_config :: LispConfig -> Property
108
prop_config conf =
109
  case A.parseOnly lispConfigParser . pack . serializeConf $ conf of
110
        Left msg -> fail $ "Parsing failed: " ++ msg
111
        Right obtained -> property $ isAlmostEqual obtained conf
112

    
113
-- | Test a Xen 4.0.1 @xm list --long@ output.
114
case_xen401list :: Assertion
115
case_xen401list = testDomain "xen-xm-list-long-4.0.1.txt" $
116
  Map.fromList
117
    [ ("Domain-0", Domain 0 "Domain-0" 184000.41332 ActualRunning Nothing)
118
    , ("instance1.example.com", Domain 119 "instance1.example.com" 24.116146647
119
      ActualBlocked Nothing)
120
    ]
121

    
122
testSuite "Hypervisor/Xen/XmParser"
123
          [ 'prop_config
124
          , 'case_xen401list
125
          ]