Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / Types.hs @ b54ecf12

History | View | Annotate | Download (4.8 kB)

1 13d3acab Michele Tartara
{-# LANGUAGE TemplateHaskell #-}
2 13d3acab Michele Tartara
3 13d3acab Michele Tartara
{-| Implementation of the Ganeti data collector types.
4 13d3acab Michele Tartara
5 13d3acab Michele Tartara
-}
6 13d3acab Michele Tartara
7 13d3acab Michele Tartara
{-
8 13d3acab Michele Tartara
9 a895fa19 Michele Tartara
Copyright (C) 2012, 2013 Google Inc.
10 13d3acab Michele Tartara
11 13d3acab Michele Tartara
This program is free software; you can redistribute it and/or modify
12 13d3acab Michele Tartara
it under the terms of the GNU General Public License as published by
13 13d3acab Michele Tartara
the Free Software Foundation; either version 2 of the License, or
14 13d3acab Michele Tartara
(at your option) any later version.
15 13d3acab Michele Tartara
16 13d3acab Michele Tartara
This program is distributed in the hope that it will be useful, but
17 13d3acab Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
18 13d3acab Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 13d3acab Michele Tartara
General Public License for more details.
20 13d3acab Michele Tartara
21 13d3acab Michele Tartara
You should have received a copy of the GNU General Public License
22 13d3acab Michele Tartara
along with this program; if not, write to the Free Software
23 13d3acab Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 13d3acab Michele Tartara
02110-1301, USA.
25 13d3acab Michele Tartara
26 13d3acab Michele Tartara
-}
27 13d3acab Michele Tartara
28 13d3acab Michele Tartara
module Ganeti.DataCollectors.Types
29 82437b28 Michele Tartara
  ( addStatus
30 f0e4b2a4 Michele Tartara
  , DCCategory(..)
31 54c7dff7 Michele Tartara
  , DCKind(..)
32 82437b28 Michele Tartara
  , DCReport(..)
33 82437b28 Michele Tartara
  , DCStatus(..)
34 82437b28 Michele Tartara
  , DCStatusCode(..)
35 a895fa19 Michele Tartara
  , DCVersion(..)
36 13d3acab Michele Tartara
  , buildReport
37 dd69cd3c Michele Tartara
  , mergeStatuses
38 13d3acab Michele Tartara
  ) where
39 13d3acab Michele Tartara
40 a5ec6d88 Michele Tartara
import Data.Char
41 13d3acab Michele Tartara
import Text.JSON
42 13d3acab Michele Tartara
43 13d3acab Michele Tartara
import Ganeti.Constants as C
44 13d3acab Michele Tartara
import Ganeti.THH
45 13d3acab Michele Tartara
import Ganeti.Utils (getCurrentTime)
46 13d3acab Michele Tartara
47 f0e4b2a4 Michele Tartara
-- | The possible classes a data collector can belong to.
48 f0e4b2a4 Michele Tartara
data DCCategory = DCInstance | DCStorage | DCDaemon | DCHypervisor
49 f0e4b2a4 Michele Tartara
  deriving (Show, Eq)
50 f0e4b2a4 Michele Tartara
51 f0e4b2a4 Michele Tartara
-- | The JSON instance for DCCategory.
52 f0e4b2a4 Michele Tartara
instance JSON DCCategory where
53 a5ec6d88 Michele Tartara
  showJSON = showJSON . map toLower . drop 2 . show
54 f0e4b2a4 Michele Tartara
  readJSON =
55 f0e4b2a4 Michele Tartara
    error "JSON read instance not implemented for type DCCategory"
56 f0e4b2a4 Michele Tartara
57 82437b28 Michele Tartara
-- | The possible status codes of a data collector.
58 82437b28 Michele Tartara
data DCStatusCode = DCSCOk      -- ^ Everything is OK
59 82437b28 Michele Tartara
                  | DCSCTempBad -- ^ Bad, but being automatically fixed
60 82437b28 Michele Tartara
                  | DCSCUnknown -- ^ Unable to determine the status
61 82437b28 Michele Tartara
                  | DCSCBad     -- ^ Bad. External intervention required
62 82437b28 Michele Tartara
                  deriving (Show, Eq, Ord)
63 82437b28 Michele Tartara
64 82437b28 Michele Tartara
-- | The JSON instance for CollectorStatus.
65 82437b28 Michele Tartara
instance JSON DCStatusCode where
66 82437b28 Michele Tartara
  showJSON DCSCOk      = showJSON (0 :: Int)
67 82437b28 Michele Tartara
  showJSON DCSCTempBad = showJSON (1 :: Int)
68 82437b28 Michele Tartara
  showJSON DCSCUnknown = showJSON (2 :: Int)
69 82437b28 Michele Tartara
  showJSON DCSCBad     = showJSON (4 :: Int)
70 82437b28 Michele Tartara
  readJSON = error "JSON read instance not implemented for type DCStatusCode"
71 82437b28 Michele Tartara
72 82437b28 Michele Tartara
-- | The status of a \"status reporting data collector\".
73 82437b28 Michele Tartara
$(buildObject "DCStatus" "dcStatus"
74 82437b28 Michele Tartara
  [ simpleField "code"    [t| DCStatusCode |]
75 82437b28 Michele Tartara
  , simpleField "message" [t| String |]
76 82437b28 Michele Tartara
  ])
77 82437b28 Michele Tartara
78 54c7dff7 Michele Tartara
-- | The type representing the kind of the collector.
79 54c7dff7 Michele Tartara
data DCKind = DCKPerf   -- ^ Performance reporting collector
80 54c7dff7 Michele Tartara
            | DCKStatus -- ^ Status reporting collector
81 54c7dff7 Michele Tartara
            deriving (Show, Eq)
82 54c7dff7 Michele Tartara
83 54c7dff7 Michele Tartara
-- | The JSON instance for CollectorKind.
84 54c7dff7 Michele Tartara
instance JSON DCKind where
85 54c7dff7 Michele Tartara
  showJSON DCKPerf   = showJSON (0 :: Int)
86 54c7dff7 Michele Tartara
  showJSON DCKStatus = showJSON (1 :: Int)
87 54c7dff7 Michele Tartara
  readJSON = error "JSON read instance not implemented for type DCKind"
88 54c7dff7 Michele Tartara
89 a895fa19 Michele Tartara
-- | Type representing the version number of a data collector.
90 a895fa19 Michele Tartara
data DCVersion = DCVerBuiltin | DCVersion String deriving (Show, Eq)
91 a895fa19 Michele Tartara
92 a895fa19 Michele Tartara
-- | The JSON instance for DCVersion.
93 a895fa19 Michele Tartara
instance JSON DCVersion where
94 a895fa19 Michele Tartara
  showJSON DCVerBuiltin = showJSON C.builtinDataCollectorVersion
95 a895fa19 Michele Tartara
  showJSON (DCVersion v) = showJSON v
96 a895fa19 Michele Tartara
  readJSON = error "JSON read instance not implemented for type DCVersion"
97 a895fa19 Michele Tartara
98 13d3acab Michele Tartara
-- | This is the format of the report produced by each data collector.
99 13d3acab Michele Tartara
$(buildObject "DCReport" "dcReport"
100 13d3acab Michele Tartara
  [ simpleField "name"           [t| String |]
101 a895fa19 Michele Tartara
  , simpleField "version"        [t| DCVersion |]
102 13d3acab Michele Tartara
  , simpleField "format_version" [t| Int |]
103 13d3acab Michele Tartara
  , simpleField "timestamp"      [t| Integer |]
104 f0e4b2a4 Michele Tartara
  , optionalNullSerField $
105 f0e4b2a4 Michele Tartara
      simpleField "category"     [t| DCCategory |]
106 54c7dff7 Michele Tartara
  , simpleField "kind"           [t| DCKind |]
107 13d3acab Michele Tartara
  , simpleField "data"           [t| JSValue |]
108 13d3acab Michele Tartara
  ])
109 13d3acab Michele Tartara
110 82437b28 Michele Tartara
-- | Add the data collector status information to the JSON representation of
111 82437b28 Michele Tartara
-- the collector data.
112 82437b28 Michele Tartara
addStatus :: DCStatus -> JSValue -> JSValue
113 82437b28 Michele Tartara
addStatus dcStatus (JSObject obj) =
114 82437b28 Michele Tartara
  makeObj $ ("status", showJSON dcStatus) : fromJSObject obj
115 82437b28 Michele Tartara
addStatus dcStatus value = makeObj
116 82437b28 Michele Tartara
  [ ("status", showJSON dcStatus)
117 82437b28 Michele Tartara
  , ("data", value)
118 82437b28 Michele Tartara
  ]
119 82437b28 Michele Tartara
120 dd69cd3c Michele Tartara
-- | Helper function for merging statuses.
121 dd69cd3c Michele Tartara
mergeStatuses :: (DCStatusCode, String) -> (DCStatusCode, [String])
122 dd69cd3c Michele Tartara
              -> (DCStatusCode, [String])
123 dd69cd3c Michele Tartara
mergeStatuses (newStat, newStr) (storedStat, storedStrs) =
124 dd69cd3c Michele Tartara
  let resStat = max newStat storedStat
125 dd69cd3c Michele Tartara
      resStrs =
126 dd69cd3c Michele Tartara
        if newStr == ""
127 dd69cd3c Michele Tartara
          then storedStrs
128 dd69cd3c Michele Tartara
          else storedStrs ++ [newStr]
129 dd69cd3c Michele Tartara
  in (resStat, resStrs)
130 dd69cd3c Michele Tartara
131 13d3acab Michele Tartara
-- | Utility function for building a report automatically adding the current
132 13d3acab Michele Tartara
-- timestamp (rounded up to seconds).
133 13d3acab Michele Tartara
-- If the version is not specified, it will be set to the value indicating
134 13d3acab Michele Tartara
-- a builtin collector.
135 54c7dff7 Michele Tartara
buildReport :: String -> DCVersion -> Int -> Maybe DCCategory -> DCKind
136 54c7dff7 Michele Tartara
            -> JSValue -> IO DCReport
137 54c7dff7 Michele Tartara
buildReport name version format_version category kind jsonData = do
138 13d3acab Michele Tartara
  now <- getCurrentTime
139 13d3acab Michele Tartara
  let timestamp = now * 1000000000 :: Integer
140 54c7dff7 Michele Tartara
  return $
141 54c7dff7 Michele Tartara
    DCReport name version format_version timestamp category kind
142 54c7dff7 Michele Tartara
      jsonData