Add Kind data type for data collectors
[ganeti-local] / src / Ganeti / DataCollectors / Types.hs
1 {-# LANGUAGE TemplateHaskell #-}
2
3 {-| Implementation of the Ganeti data collector types.
4
5 -}
6
7 {-
8
9 Copyright (C) 2012, 2013 Google Inc.
10
11 This program is free software; you can redistribute it and/or modify
12 it under the terms of the GNU General Public License as published by
13 the Free Software Foundation; either version 2 of the License, or
14 (at your option) any later version.
15
16 This program is distributed in the hope that it will be useful, but
17 WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 General Public License for more details.
20
21 You should have received a copy of the GNU General Public License
22 along with this program; if not, write to the Free Software
23 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 02110-1301, USA.
25
26 -}
27
28 module Ganeti.DataCollectors.Types
29   ( DCReport(..)
30   , DCCategory(..)
31   , DCKind(..)
32   , DCVersion(..)
33   , buildReport
34   ) where
35
36 import Text.JSON
37
38 import Ganeti.Constants as C
39 import Ganeti.THH
40 import Ganeti.Utils (getCurrentTime)
41
42 -- | The possible classes a data collector can belong to.
43 data DCCategory = DCInstance | DCStorage | DCDaemon | DCHypervisor
44   deriving (Show, Eq)
45
46 -- | The JSON instance for DCCategory.
47 instance JSON DCCategory where
48   showJSON = showJSON . show
49   readJSON =
50     error "JSON read instance not implemented for type DCCategory"
51
52 -- | The type representing the kind of the collector.
53 data DCKind = DCKPerf   -- ^ Performance reporting collector
54             | DCKStatus -- ^ Status reporting collector
55             deriving (Show, Eq)
56
57 -- | The JSON instance for CollectorKind.
58 instance JSON DCKind where
59   showJSON DCKPerf   = showJSON (0 :: Int)
60   showJSON DCKStatus = showJSON (1 :: Int)
61   readJSON = error "JSON read instance not implemented for type DCKind"
62
63 -- | Type representing the version number of a data collector.
64 data DCVersion = DCVerBuiltin | DCVersion String deriving (Show, Eq)
65
66 -- | The JSON instance for DCVersion.
67 instance JSON DCVersion where
68   showJSON DCVerBuiltin = showJSON C.builtinDataCollectorVersion
69   showJSON (DCVersion v) = showJSON v
70   readJSON = error "JSON read instance not implemented for type DCVersion"
71
72 -- | This is the format of the report produced by each data collector.
73 $(buildObject "DCReport" "dcReport"
74   [ simpleField "name"           [t| String |]
75   , simpleField "version"        [t| DCVersion |]
76   , simpleField "format_version" [t| Int |]
77   , simpleField "timestamp"      [t| Integer |]
78   , optionalNullSerField $
79       simpleField "category"     [t| DCCategory |]
80   , simpleField "kind"           [t| DCKind |]
81   , simpleField "data"           [t| JSValue |]
82   ])
83
84 -- | Utility function for building a report automatically adding the current
85 -- timestamp (rounded up to seconds).
86 -- If the version is not specified, it will be set to the value indicating
87 -- a builtin collector.
88 buildReport :: String -> DCVersion -> Int -> Maybe DCCategory -> DCKind
89             -> JSValue -> IO DCReport
90 buildReport name version format_version category kind jsonData = do
91   now <- getCurrentTime
92   let timestamp = now * 1000000000 :: Integer
93   return $
94     DCReport name version format_version timestamp category kind
95       jsonData