Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / Types.hs @ 834dc290

History | View | Annotate | Download (2.2 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 13d3acab Michele Tartara
  ( DCReport(..)
30 a895fa19 Michele Tartara
  , DCVersion(..)
31 13d3acab Michele Tartara
  , buildReport
32 13d3acab Michele Tartara
  ) where
33 13d3acab Michele Tartara
34 13d3acab Michele Tartara
import Text.JSON
35 13d3acab Michele Tartara
36 13d3acab Michele Tartara
import Ganeti.Constants as C
37 13d3acab Michele Tartara
import Ganeti.THH
38 13d3acab Michele Tartara
import Ganeti.Utils (getCurrentTime)
39 13d3acab Michele Tartara
40 a895fa19 Michele Tartara
-- | Type representing the version number of a data collector.
41 a895fa19 Michele Tartara
data DCVersion = DCVerBuiltin | DCVersion String deriving (Show, Eq)
42 a895fa19 Michele Tartara
43 a895fa19 Michele Tartara
-- | The JSON instance for DCVersion.
44 a895fa19 Michele Tartara
instance JSON DCVersion where
45 a895fa19 Michele Tartara
  showJSON DCVerBuiltin = showJSON C.builtinDataCollectorVersion
46 a895fa19 Michele Tartara
  showJSON (DCVersion v) = showJSON v
47 a895fa19 Michele Tartara
  readJSON = error "JSON read instance not implemented for type DCVersion"
48 a895fa19 Michele Tartara
49 13d3acab Michele Tartara
-- | This is the format of the report produced by each data collector.
50 13d3acab Michele Tartara
$(buildObject "DCReport" "dcReport"
51 13d3acab Michele Tartara
  [ simpleField "name"           [t| String |]
52 a895fa19 Michele Tartara
  , simpleField "version"        [t| DCVersion |]
53 13d3acab Michele Tartara
  , simpleField "format_version" [t| Int |]
54 13d3acab Michele Tartara
  , simpleField "timestamp"      [t| Integer |]
55 13d3acab Michele Tartara
  , simpleField "data"           [t| JSValue |]
56 13d3acab Michele Tartara
  ])
57 13d3acab Michele Tartara
58 13d3acab Michele Tartara
-- | Utility function for building a report automatically adding the current
59 13d3acab Michele Tartara
-- timestamp (rounded up to seconds).
60 13d3acab Michele Tartara
-- If the version is not specified, it will be set to the value indicating
61 13d3acab Michele Tartara
-- a builtin collector.
62 a895fa19 Michele Tartara
buildReport :: String -> DCVersion -> Int -> JSValue -> IO DCReport
63 13d3acab Michele Tartara
buildReport name version format_version jsonData = do
64 13d3acab Michele Tartara
  now <- getCurrentTime
65 13d3acab Michele Tartara
  let timestamp = now * 1000000000 :: Integer
66 a895fa19 Michele Tartara
  return $ DCReport name version format_version timestamp jsonData