Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 885759da

History | View | Annotate | Download (8.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 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
import Ganeti.Runtime
55

    
56
-- * Types and constants definitions
57

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

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

    
64
-- | Version of the latest supported http API.
65
latestAPIVersion :: Int
66
latestAPIVersion = C.mondLatestApiVersion
67

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

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

    
84

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

    
100
-- * Configuration handling
101

    
102
-- | The default configuration for the HTTP server.
103
defaultHttpConf :: FilePath -> FilePath -> Config Snap ()
104
defaultHttpConf accessLog errorLog =
105
  setAccessLog (ConfigFileLog accessLog) .
106
  setCompression False .
107
  setErrorLog (ConfigFileLog errorLog) $
108
  setVerbose False
109
  emptyConfig
110

    
111
-- * Helper functions
112

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

    
117
-- | Prepare function for monitoring agent.
118
prepMain :: PrepFn CheckResult PrepResult
119
prepMain opts _ = do
120
  accessLog <- daemonsExtraLogFile GanetiMond AccessLog
121
  errorLog <- daemonsExtraLogFile GanetiMond ErrorLog
122
  return .
123
    setPort
124
      (maybe C.defaultMondPort fromIntegral (optPort opts)) .
125
    maybe id (setBind . pack) (optBindAddress opts)
126
    $ defaultHttpConf accessLog errorLog
127

    
128
-- * Query answers
129

    
130
-- | Reply to the supported API version numbers query.
131
versionQ :: Snap ()
132
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
133

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

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

    
154
-- | Handler for returning lists.
155
listHandler :: Snap ()
156
listHandler =
157
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
158

    
159
-- | Handler for returning data collector reports.
160
reportHandler :: MVar CollectorMap -> Snap ()
161
reportHandler mvar =
162
  route
163
    [ ("all", allReports mvar)
164
    , (":category/:collector", oneReport mvar)
165
    ] <|>
166
  errorReport
167

    
168
-- | Return the report of all the available collectors.
169
allReports :: MVar CollectorMap -> Snap ()
170
allReports mvar = do
171
  reports <- mapM (liftIO . getReport mvar) collectors
172
  writeBS . pack . J.encode $ reports
173

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

    
184
-- | Returns the data for the corresponding collector.
185
getColData :: String -> MVar CollectorMap -> IO (Maybe CollectorData)
186
getColData name mvar = do
187
  m <- readMVar mvar
188
  return $ Map.lookup name m
189

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

    
201
errorReport :: Snap ()
202
errorReport = do
203
  modifyResponse $ setResponseStatus 404 "Not found"
204
  writeBS "Unable to produce a report for the requested resource"
205

    
206
error404 :: Snap ()
207
error404 = do
208
  modifyResponse $ setResponseStatus 404 "Not found"
209
  writeBS "Resource not found"
210

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

    
229
-- | The function implementing the HTTP API of the monitoring agent.
230
monitoringApi :: MVar CollectorMap -> Snap ()
231
monitoringApi mvar =
232
  ifTop versionQ <|>
233
  dir "1" (version1Api mvar) <|>
234
  error404
235

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

    
248
-- | Invokes collect for each data collector.
249
collection :: CollectorMap -> IO CollectorMap
250
collection m = foldM collect m collectors
251

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

    
262
-- | Main function.
263
main :: MainFn CheckResult PrepResult
264
main _ _ httpConf = do
265
  mvar <- newMVar Map.empty
266
  _ <- forkIO $ collectord mvar
267
  httpServe httpConf . method GET $ monitoringApi mvar