Add the core of the instance status collector
[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   ( addStatus
30   , DCCategory(..)
31   , DCKind(..)
32   , DCReport(..)
33   , DCStatus(..)
34   , DCStatusCode(..)
35   , DCVersion(..)
36   , buildReport
37   ) where
38
39 import Data.Char
40 import Text.JSON
41
42 import Ganeti.Constants as C
43 import Ganeti.THH
44 import Ganeti.Utils (getCurrentTime)
45
46 -- | The possible classes a data collector can belong to.
47 data DCCategory = DCInstance | DCStorage | DCDaemon | DCHypervisor
48   deriving (Show, Eq)
49
50 -- | The JSON instance for DCCategory.
51 instance JSON DCCategory where
52   showJSON = showJSON . map toLower . drop 2 . show
53   readJSON =
54     error "JSON read instance not implemented for type DCCategory"
55
56 -- | The possible status codes of a data collector.
57 data DCStatusCode = DCSCOk      -- ^ Everything is OK
58                   | DCSCTempBad -- ^ Bad, but being automatically fixed
59                   | DCSCUnknown -- ^ Unable to determine the status
60                   | DCSCBad     -- ^ Bad. External intervention required
61                   deriving (Show, Eq, Ord)
62
63 -- | The JSON instance for CollectorStatus.
64 instance JSON DCStatusCode where
65   showJSON DCSCOk      = showJSON (0 :: Int)
66   showJSON DCSCTempBad = showJSON (1 :: Int)
67   showJSON DCSCUnknown = showJSON (2 :: Int)
68   showJSON DCSCBad     = showJSON (4 :: Int)
69   readJSON = error "JSON read instance not implemented for type DCStatusCode"
70
71 -- | The status of a \"status reporting data collector\".
72 $(buildObject "DCStatus" "dcStatus"
73   [ simpleField "code"    [t| DCStatusCode |]
74   , simpleField "message" [t| String |]
75   ])
76
77 -- | The type representing the kind of the collector.
78 data DCKind = DCKPerf   -- ^ Performance reporting collector
79             | DCKStatus -- ^ Status reporting collector
80             deriving (Show, Eq)
81
82 -- | The JSON instance for CollectorKind.
83 instance JSON DCKind where
84   showJSON DCKPerf   = showJSON (0 :: Int)
85   showJSON DCKStatus = showJSON (1 :: Int)
86   readJSON = error "JSON read instance not implemented for type DCKind"
87
88 -- | Type representing the version number of a data collector.
89 data DCVersion = DCVerBuiltin | DCVersion String deriving (Show, Eq)
90
91 -- | The JSON instance for DCVersion.
92 instance JSON DCVersion where
93   showJSON DCVerBuiltin = showJSON C.builtinDataCollectorVersion
94   showJSON (DCVersion v) = showJSON v
95   readJSON = error "JSON read instance not implemented for type DCVersion"
96
97 -- | This is the format of the report produced by each data collector.
98 $(buildObject "DCReport" "dcReport"
99   [ simpleField "name"           [t| String |]
100   , simpleField "version"        [t| DCVersion |]
101   , simpleField "format_version" [t| Int |]
102   , simpleField "timestamp"      [t| Integer |]
103   , optionalNullSerField $
104       simpleField "category"     [t| DCCategory |]
105   , simpleField "kind"           [t| DCKind |]
106   , simpleField "data"           [t| JSValue |]
107   ])
108
109 -- | Add the data collector status information to the JSON representation of
110 -- the collector data.
111 addStatus :: DCStatus -> JSValue -> JSValue
112 addStatus dcStatus (JSObject obj) =
113   makeObj $ ("status", showJSON dcStatus) : fromJSObject obj
114 addStatus dcStatus value = makeObj
115   [ ("status", showJSON dcStatus)
116   , ("data", value)
117   ]
118
119 -- | Utility function for building a report automatically adding the current
120 -- timestamp (rounded up to seconds).
121 -- If the version is not specified, it will be set to the value indicating
122 -- a builtin collector.
123 buildReport :: String -> DCVersion -> Int -> Maybe DCCategory -> DCKind
124             -> JSValue -> IO DCReport
125 buildReport name version format_version category kind jsonData = do
126   now <- getCurrentTime
127   let timestamp = now * 1000000000 :: Integer
128   return $
129     DCReport name version format_version timestamp category kind
130       jsonData