Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 3792fa8e

History | View | Annotate | Download (8.3 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 Control.Monad.IO.Class
37
import Data.ByteString.Char8 hiding (map, filter, find)
38
import Data.List
39
import qualified Data.Map as Map
40
import Snap.Core
41
import Snap.Http.Server
42
import qualified Text.JSON as J
43
import Control.Concurrent
44

    
45
import qualified Ganeti.BasicTypes as BT
46
import Ganeti.Daemon
47
import qualified Ganeti.DataCollectors.CPUload as CPUload
48
import qualified Ganeti.DataCollectors.Diskstats as Diskstats
49
import qualified Ganeti.DataCollectors.Drbd as Drbd
50
import qualified Ganeti.DataCollectors.InstStatus as InstStatus
51
import qualified Ganeti.DataCollectors.Lv as Lv
52
import Ganeti.DataCollectors.Types
53
import qualified Ganeti.Constants as C
54

    
55
-- * Types and constants definitions
56

    
57
-- | Type alias for checkMain results.
58
type CheckResult = ()
59

    
60
-- | Type alias for prepMain results.
61
type PrepResult = Config Snap ()
62

    
63
-- | Version of the latest supported http API.
64
latestAPIVersion :: Int
65
latestAPIVersion = 1
66

    
67
-- | A report of a data collector might be stateful or stateless.
68
data Report = StatelessR (IO DCReport)
69
            | StatefulR (Maybe CollectorData -> IO DCReport)
70

    
71
-- | Type describing a data collector basic information
72
data DataCollector = DataCollector
73
  { dName     :: String           -- ^ Name of the data collector
74
  , dCategory :: Maybe DCCategory -- ^ Category (storage, instance, ecc)
75
                                  --   of the collector
76
  , dKind     :: DCKind           -- ^ Kind (performance or status reporting) of
77
                                  --   the data collector
78
  , dReport   :: Report           -- ^ Report produced by the collector
79
  , dUpdate   :: Maybe (Maybe CollectorData -> IO CollectorData)
80
                                  -- ^ Update operation for stateful collectors.
81
  }
82

    
83

    
84
-- | The list of available builtin data collectors.
85
collectors :: [DataCollector]
86
collectors =
87
  [ DataCollector Diskstats.dcName Diskstats.dcCategory Diskstats.dcKind
88
      (StatelessR Diskstats.dcReport) Nothing
89
  , DataCollector Drbd.dcName Drbd.dcCategory Drbd.dcKind
90
      (StatelessR Drbd.dcReport) Nothing
91
  , DataCollector InstStatus.dcName InstStatus.dcCategory InstStatus.dcKind
92
      (StatelessR InstStatus.dcReport) Nothing
93
  , DataCollector Lv.dcName Lv.dcCategory Lv.dcKind
94
      (StatelessR Lv.dcReport) Nothing
95
  , DataCollector CPUload.dcName CPUload.dcCategory CPUload.dcKind
96
      (StatefulR CPUload.dcReport) (Just CPUload.dcUpdate)
97
  ]
98

    
99
-- * Configuration handling
100

    
101
-- | The default configuration for the HTTP server.
102
defaultHttpConf :: Config Snap ()
103
defaultHttpConf =
104
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
105
  setCompression False .
106
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
107
  setVerbose False
108
  emptyConfig
109

    
110
-- * Helper functions
111

    
112
-- | Check function for the monitoring agent.
113
checkMain :: CheckFn CheckResult
114
checkMain _ = return $ Right ()
115

    
116
-- | Prepare function for monitoring agent.
117
prepMain :: PrepFn CheckResult PrepResult
118
prepMain opts _ =
119
  return $
120
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
121
      defaultHttpConf
122

    
123
-- * Query answers
124

    
125
-- | Reply to the supported API version numbers query.
126
versionQ :: Snap ()
127
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
128

    
129
-- | Version 1 of the monitoring HTTP API.
130
version1Api :: MVar CollectorMap -> Snap ()
131
version1Api mvar =
132
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
133
  in ifTop returnNull <|>
134
     route
135
       [ ("list", listHandler)
136
       , ("report", reportHandler mvar)
137
       ]
138

    
139
-- | Get the JSON representation of a data collector to be used in the collector
140
-- list.
141
dcListItem :: DataCollector -> J.JSValue
142
dcListItem dc =
143
  J.JSArray
144
    [ J.showJSON $ dName dc
145
    , maybe J.JSNull J.showJSON $ dCategory dc
146
    , J.showJSON $ dKind dc
147
    ]
148

    
149
-- | Handler for returning lists.
150
listHandler :: Snap ()
151
listHandler =
152
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
153

    
154
-- | Handler for returning data collector reports.
155
reportHandler :: MVar CollectorMap -> Snap ()
156
reportHandler mvar =
157
  route
158
    [ ("all", allReports mvar)
159
    , (":category/:collector", oneReport mvar)
160
    ] <|>
161
  errorReport
162

    
163
-- | Return the report of all the available collectors.
164
allReports :: MVar CollectorMap -> Snap ()
165
allReports mvar = do
166
  reports <- mapM (liftIO . getReport mvar) collectors
167
  writeBS . pack . J.encode $ reports
168

    
169
-- | Takes the CollectorMap and a DataCollector and returns the report for this
170
-- collector.
171
getReport :: MVar CollectorMap -> DataCollector -> IO DCReport
172
getReport mvar collector =
173
  case dReport collector of
174
    StatelessR r -> r
175
    StatefulR r -> do
176
      colData <- getColData (dName collector) mvar
177
      r colData
178

    
179
-- | Returns the data for the corresponding collector.
180
getColData :: String -> MVar CollectorMap -> IO (Maybe CollectorData)
181
getColData name mvar = do
182
  m <- readMVar mvar
183
  return $ Map.lookup name m
184

    
185
-- | Returns a category given its name.
186
-- If "collector" is given as the name, the collector has no category, and
187
-- Nothing will be returned.
188
catFromName :: String -> BT.Result (Maybe DCCategory)
189
catFromName "instance"   = BT.Ok $ Just DCInstance
190
catFromName "storage"    = BT.Ok $ Just DCStorage
191
catFromName "daemon"     = BT.Ok $ Just DCDaemon
192
catFromName "hypervisor" = BT.Ok $ Just DCHypervisor
193
catFromName "default"    = BT.Ok Nothing
194
catFromName _            = BT.Bad "No such category"
195

    
196
errorReport :: Snap ()
197
errorReport = do
198
  modifyResponse $ setResponseStatus 404 "Not found"
199
  writeBS "Unable to produce a report for the requested resource"
200

    
201
error404 :: Snap ()
202
error404 = do
203
  modifyResponse $ setResponseStatus 404 "Not found"
204
  writeBS "Resource not found"
205

    
206
-- | Return the report of one collector.
207
oneReport :: MVar CollectorMap -> Snap ()
208
oneReport mvar = do
209
  categoryName <- fmap (maybe mzero unpack) $ getParam "category"
210
  collectorName <- fmap (maybe mzero unpack) $ getParam "collector"
211
  category <-
212
    case catFromName categoryName of
213
      BT.Ok cat -> return cat
214
      BT.Bad msg -> fail msg
215
  collector <-
216
    case
217
      find (\col -> collectorName == dName col) $
218
        filter (\c -> category == dCategory c) collectors of
219
      Just col -> return col
220
      Nothing -> fail "Unable to find the requested collector"
221
  dcr <- liftIO $ getReport mvar collector
222
  writeBS . pack . J.encode $ dcr
223

    
224
-- | The function implementing the HTTP API of the monitoring agent.
225
monitoringApi :: MVar CollectorMap -> Snap ()
226
monitoringApi mvar =
227
  ifTop versionQ <|>
228
  dir "1" (version1Api mvar) <|>
229
  error404
230

    
231
-- | The function collecting data for each data collector providing a dcUpdate
232
-- function.
233
collect :: CollectorMap -> DataCollector -> IO CollectorMap
234
collect m collector =
235
  case dUpdate collector of
236
    Nothing -> return m
237
    Just update -> do
238
      let name = dName collector
239
          existing = Map.lookup name m
240
      new_data <- update existing
241
      return $ Map.insert name new_data m
242

    
243
-- | Invokes collect for each data collector.
244
collection :: CollectorMap -> IO CollectorMap
245
collection m = foldM collect m collectors
246

    
247
-- | The thread responsible for the periodical collection of data for each data
248
-- data collector.
249
collectord :: MVar CollectorMap -> IO ()
250
collectord mvar = do
251
  m <- takeMVar mvar
252
  m' <- collection m
253
  putMVar mvar m'
254
  threadDelay $ 10^(6 :: Int) * C.mondTimeInterval
255
  collectord mvar
256

    
257
-- | Main function.
258
main :: MainFn CheckResult PrepResult
259
main _ _ httpConf = do
260
  mvar <- newMVar Map.empty
261
  _ <- forkIO $ collectord mvar
262
  httpServe httpConf . method GET $ monitoringApi mvar