Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ ecb783f0

History | View | Annotate | Download (4.5 kB)

1
{-# LANGUAGE OverloadedStrings #-}
2

    
3
{-| Implementation of the Ganeti confd server functionality.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 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.Monitoring.Server
29
  ( main
30
  , checkMain
31
  , prepMain
32
  ) where
33

    
34
import Control.Applicative
35
import Control.Monad
36
import Snap.Core
37
import Snap.Http.Server
38
import Data.ByteString.Char8 hiding (map)
39
import qualified Text.JSON as J
40

    
41
import Ganeti.Daemon
42
import qualified Ganeti.DataCollectors.Drbd as Drbd
43
import Ganeti.DataCollectors.Types
44
import qualified Ganeti.Constants as C
45

    
46
-- * Types and constants definitions
47

    
48
-- | Type alias for checkMain results.
49
type CheckResult = ()
50

    
51
-- | Type alias for prepMain results.
52
type PrepResult = Config Snap ()
53

    
54
-- | Version of the latest supported http API.
55
latestAPIVersion :: Int
56
latestAPIVersion = 1
57

    
58
-- | Type describing a data collector basic information
59
data DataCollector = DataCollector
60
  { dName     :: String           -- ^ Name of the data collector
61
  , dCategory :: Maybe DCCategory -- ^ Category (storage, instance, ecc)
62
                                  --   of the collector
63
  , dKind     :: DCKind           -- ^ Kind (performance or status reporting) of
64
                                  --   the data collector
65
  }
66

    
67
-- | The list of available builtin data collectors.
68
collectors :: [DataCollector]
69
collectors =
70
  [ DataCollector Drbd.dcName Drbd.dcCategory Drbd.dcKind
71
  ]
72

    
73

    
74
-- * Configuration handling
75

    
76
-- | The default configuration for the HTTP server.
77
defaultHttpConf :: Config Snap ()
78
defaultHttpConf =
79
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
80
  setCompression False .
81
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
82
  setVerbose False
83
  emptyConfig
84

    
85
-- * Helper functions
86

    
87
-- | Check function for the monitoring agent.
88
checkMain :: CheckFn CheckResult
89
checkMain _ = return $ Right ()
90

    
91
-- | Prepare function for monitoring agent.
92
prepMain :: PrepFn CheckResult PrepResult
93
prepMain opts _ =
94
  return $
95
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
96
      defaultHttpConf
97

    
98
-- * Query answers
99

    
100
-- | Reply to the supported API version numbers query.
101
versionQ :: Snap ()
102
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
103

    
104
-- | Version 1 of the monitoring HTTP API.
105
version1Api :: Snap ()
106
version1Api =
107
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
108
  in ifTop returnNull <|>
109
     route
110
       [ ("list", listHandler)
111
       , ("report", reportHandler)
112
       ]
113

    
114
-- | Get the JSON representation of a data collector to be used in the collector
115
-- list.
116
dcListItem :: DataCollector -> J.JSValue
117
dcListItem dc =
118
  J.JSArray
119
    [ J.showJSON $ dName dc
120
    , maybe J.JSNull J.showJSON $ dCategory dc
121
    , J.showJSON $ dKind dc
122
    ]
123

    
124
-- | Handler for returning lists.
125
listHandler :: Snap ()
126
listHandler =
127
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
128

    
129
-- | Handler for returning data collector reports.
130
reportHandler :: Snap ()
131
reportHandler =
132
  route
133
    [ ("all", allReports)
134
    , (":category/:collector", oneReport)
135
    ]
136

    
137
-- | Return the report of all the available collectors
138
allReports :: Snap ()
139
allReports = writeText "TODO: return the reports of all the collectors"
140

    
141
-- | Return the report of one collector
142
oneReport :: Snap ()
143
oneReport = do
144
  category <- fmap (maybe mzero unpack) $ getParam "category"
145
  collector <- fmap (maybe mzero unpack) $ getParam "collector"
146
  writeBS . pack $
147
    "TODO: return the report for collector " ++ category
148
      ++ "/" ++ collector
149

    
150
-- | The function implementing the HTTP API of the monitoring agent.
151
-- TODO: Currently it only replies to the API version query: implement all the
152
-- missing features.
153
monitoringApi :: Snap ()
154
monitoringApi =
155
  ifTop versionQ <|>
156
  dir "1" version1Api
157

    
158
-- | Main function.
159
main :: MainFn CheckResult PrepResult
160
main _ _ httpConf =
161
  httpServe httpConf $ method GET monitoringApi