ed1854682c01e9fa2451005281950c27dbda0f53
[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   , DCVersion(..)
32   , buildReport
33   ) where
34
35 import Text.JSON
36
37 import Ganeti.Constants as C
38 import Ganeti.THH
39 import Ganeti.Utils (getCurrentTime)
40
41 -- | The possible classes a data collector can belong to.
42 data DCCategory = DCInstance | DCStorage | DCDaemon | DCHypervisor
43   deriving (Show, Eq)
44
45 -- | The JSON instance for DCCategory.
46 instance JSON DCCategory where
47   showJSON = showJSON . show
48   readJSON =
49     error "JSON read instance not implemented for type DCCategory"
50
51 -- | Type representing the version number of a data collector.
52 data DCVersion = DCVerBuiltin | DCVersion String deriving (Show, Eq)
53
54 -- | The JSON instance for DCVersion.
55 instance JSON DCVersion where
56   showJSON DCVerBuiltin = showJSON C.builtinDataCollectorVersion
57   showJSON (DCVersion v) = showJSON v
58   readJSON = error "JSON read instance not implemented for type DCVersion"
59
60 -- | This is the format of the report produced by each data collector.
61 $(buildObject "DCReport" "dcReport"
62   [ simpleField "name"           [t| String |]
63   , simpleField "version"        [t| DCVersion |]
64   , simpleField "format_version" [t| Int |]
65   , simpleField "timestamp"      [t| Integer |]
66   , optionalNullSerField $
67       simpleField "category"     [t| DCCategory |]
68   , simpleField "data"           [t| JSValue |]
69   ])
70
71 -- | Utility function for building a report automatically adding the current
72 -- timestamp (rounded up to seconds).
73 -- If the version is not specified, it will be set to the value indicating
74 -- a builtin collector.
75 buildReport :: String -> DCVersion -> Int -> Maybe DCCategory -> JSValue
76             -> IO DCReport
77 buildReport name version format_version category jsonData = do
78   now <- getCurrentTime
79   let timestamp = now * 1000000000 :: Integer
80   return $ DCReport name version format_version timestamp category jsonData