Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / HTools / ExtLoader.hs @ 5c40076b

History | View | Annotate | Download (4.1 kB)

1
{-| Unittests for the MonD data parse function -}
2

    
3
{-
4

    
5
Copyright (C) 2013 Google Inc.
6

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

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

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

    
22
-}
23

    
24
module Test.Ganeti.HTools.ExtLoader where
25

    
26
import Data.Ratio
27

    
28
import qualified Test.HUnit as HUnit
29
import qualified Text.JSON as J
30

    
31
import qualified Ganeti.BasicTypes as BT
32
import qualified Ganeti.DataCollectors.CPUload as CPUload
33

    
34
import Ganeti.Cpu.Types (CPUavgload(..))
35
import Ganeti.DataCollectors.Types (DCReport(..))
36
import Ganeti.HTools.ExtLoader
37
import Ganeti.JSON
38
import Test.Ganeti.TestCommon
39

    
40
{-# ANN module "HLint: ignore Use camelCase" #-}
41

    
42
-- | Test a MonD data file.
43
case_parseMonDData :: HUnit.Assertion
44
case_parseMonDData = do
45
  let mond_data_file = "mond-data.txt"
46
      n1 = "node1.example.com"
47
      n2 = "node2.example.com"
48
      t1 = 1379507272000000000
49
      t2 = 1379507280000000000
50
      cpu_number1 = 4
51
      cpu_number2 = 2
52
      cpus1 = [ 0.04108859597350646,0.04456554528165781
53
               , 0.06203619909502262,0.05595448881893895]
54
      cpus2 = [0.004155409618511363,0.0034586452012150787]
55
      cpu_total1 = 0.203643517607712
56
      cpu_total2 = 0.007614031289927129
57
      dcr1 = DCReport CPUload.dcName CPUload.dcVersion CPUload.dcFormatVersion
58
               t1 CPUload.dcCategory CPUload.dcKind
59
               (J.showJSON (CPUavgload cpu_number1 cpus1 cpu_total1))
60
      dcr2 = DCReport CPUload.dcName CPUload.dcVersion CPUload.dcFormatVersion
61
               t2 CPUload.dcCategory CPUload.dcKind
62
               (J.showJSON (CPUavgload cpu_number2 cpus2 cpu_total2))
63
      expected_list = [(n1,[dcr1]),(n2,[dcr2])]
64
  ans <- readTestData mond_data_file
65
  case pMonDData ans of
66
    BT.Ok l -> HUnit.assertBool ("Parsing " ++ mond_data_file ++ " failed")
67
                 (isAlEqual expected_list l)
68
    BT.Bad s -> HUnit.assertFailure $ "Parsing failed: " ++ s
69

    
70
-- | Check for quality two list of tuples.
71
isAlEqual :: [(String, [DCReport])] -> [(String, [DCReport])] -> Bool
72
isAlEqual a b = and (zipWith tupleIsAlEqual a b)
73

    
74
-- | Check a tuple for quality.
75
tupleIsAlEqual :: (String, [DCReport]) -> (String, [DCReport]) -> Bool
76
tupleIsAlEqual (na, a) (nb, b) =
77
  na == nb
78
  && and (zipWith dcReportIsAlmostEqual a b)
79

    
80
-- | Check if two DCReports are equal. Only reports from CPUload Data
81
-- Collectors are supported.
82
dcReportIsAlmostEqual :: DCReport -> DCReport -> Bool
83
dcReportIsAlmostEqual a b =
84
  dcReportName a == dcReportName b
85
  && dcReportVersion a == dcReportVersion b
86
  && dcReportFormatVersion a == dcReportFormatVersion b
87
  && dcReportTimestamp a == dcReportTimestamp b
88
  && dcReportCategory a == dcReportCategory b
89
  && dcReportKind a == dcReportKind b
90
  && case () of
91
       _ | CPUload.dcName == dcReportName a ->
92
             cpuavgloadDataIsAlmostEq (dcReportData a) (dcReportData b)
93
         | otherwise -> False
94

    
95
-- | Converts two JSValue objects and compares them.
96
cpuavgloadDataIsAlmostEq :: J.JSValue -> J.JSValue -> Bool
97
cpuavgloadDataIsAlmostEq a b =
98
  case fromJVal a :: BT.Result CPUavgload of
99
    BT.Bad _ -> False
100
    BT.Ok cavA ->
101
      case fromJVal b :: BT.Result CPUavgload of
102
           BT.Bad _ -> False
103
           BT.Ok cavB -> compareCPUavgload cavA cavB
104

    
105
-- | Compares two CPuavgload objects.
106
compareCPUavgload :: CPUavgload -> CPUavgload -> Bool
107
compareCPUavgload a b =
108
  let relError x y = relativeError x y <= 1e-9
109
  in cavCpuNumber a == cavCpuNumber b
110
     && relError (cavCpuTotal a) (cavCpuTotal b)
111
     && length (cavCpus a) == length (cavCpus b)
112
     && and (zipWith relError (cavCpus a) (cavCpus b))