Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 006d6bc9

History | View | Annotate | Download (6.1 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 Snap.Core
40
import Snap.Http.Server
41
import qualified Text.JSON as J
42

    
43
import qualified Ganeti.BasicTypes as BT
44
import Ganeti.Daemon
45
import qualified Ganeti.DataCollectors.Diskstats as Diskstats
46
import qualified Ganeti.DataCollectors.Drbd as Drbd
47
import qualified Ganeti.DataCollectors.InstStatus as InstStatus
48
import qualified Ganeti.DataCollectors.Lv as Lv
49
import Ganeti.DataCollectors.Types
50
import qualified Ganeti.Constants as C
51

    
52
-- * Types and constants definitions
53

    
54
-- | Type alias for checkMain results.
55
type CheckResult = ()
56

    
57
-- | Type alias for prepMain results.
58
type PrepResult = Config Snap ()
59

    
60
-- | Version of the latest supported http API.
61
latestAPIVersion :: Int
62
latestAPIVersion = 1
63

    
64
-- | Type describing a data collector basic information
65
data DataCollector = DataCollector
66
  { dName     :: String           -- ^ Name of the data collector
67
  , dCategory :: Maybe DCCategory -- ^ Category (storage, instance, ecc)
68
                                  --   of the collector
69
  , dKind     :: DCKind           -- ^ Kind (performance or status reporting) of
70
                                  --   the data collector
71
  , dReport   :: IO DCReport      -- ^ Report produced by the collector
72
  }
73

    
74
-- | The list of available builtin data collectors.
75
collectors :: [DataCollector]
76
collectors =
77
  [ DataCollector Diskstats.dcName Diskstats.dcCategory Diskstats.dcKind
78
      Diskstats.dcReport
79
  , DataCollector Drbd.dcName Drbd.dcCategory Drbd.dcKind Drbd.dcReport
80
  , DataCollector InstStatus.dcName InstStatus.dcCategory InstStatus.dcKind
81
      InstStatus.dcReport
82
  , DataCollector Lv.dcName Lv.dcCategory Lv.dcKind Lv.dcReport
83
  ]
84

    
85
-- * Configuration handling
86

    
87
-- | The default configuration for the HTTP server.
88
defaultHttpConf :: Config Snap ()
89
defaultHttpConf =
90
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
91
  setCompression False .
92
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
93
  setVerbose False
94
  emptyConfig
95

    
96
-- * Helper functions
97

    
98
-- | Check function for the monitoring agent.
99
checkMain :: CheckFn CheckResult
100
checkMain _ = return $ Right ()
101

    
102
-- | Prepare function for monitoring agent.
103
prepMain :: PrepFn CheckResult PrepResult
104
prepMain opts _ =
105
  return $
106
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
107
      defaultHttpConf
108

    
109
-- * Query answers
110

    
111
-- | Reply to the supported API version numbers query.
112
versionQ :: Snap ()
113
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
114

    
115
-- | Version 1 of the monitoring HTTP API.
116
version1Api :: Snap ()
117
version1Api =
118
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
119
  in ifTop returnNull <|>
120
     route
121
       [ ("list", listHandler)
122
       , ("report", reportHandler)
123
       ]
124

    
125
-- | Get the JSON representation of a data collector to be used in the collector
126
-- list.
127
dcListItem :: DataCollector -> J.JSValue
128
dcListItem dc =
129
  J.JSArray
130
    [ J.showJSON $ dName dc
131
    , maybe J.JSNull J.showJSON $ dCategory dc
132
    , J.showJSON $ dKind dc
133
    ]
134

    
135
-- | Handler for returning lists.
136
listHandler :: Snap ()
137
listHandler =
138
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
139

    
140
-- | Handler for returning data collector reports.
141
reportHandler :: Snap ()
142
reportHandler =
143
  route
144
    [ ("all", allReports)
145
    , (":category/:collector", oneReport)
146
    ] <|>
147
  errorReport
148

    
149
-- | Return the report of all the available collectors.
150
allReports :: Snap ()
151
allReports = do
152
  reports <- mapM (liftIO . dReport) collectors
153
  writeBS . pack . J.encode $ reports
154

    
155
-- | Returns a category given its name.
156
-- If "collector" is given as the name, the collector has no category, and
157
-- Nothing will be returned.
158
catFromName :: String -> BT.Result (Maybe DCCategory)
159
catFromName "instance"   = BT.Ok $ Just DCInstance
160
catFromName "storage"    = BT.Ok $ Just DCStorage
161
catFromName "daemon"     = BT.Ok $ Just DCDaemon
162
catFromName "hypervisor" = BT.Ok $ Just DCHypervisor
163
catFromName "default"    = BT.Ok Nothing
164
catFromName _            = BT.Bad "No such category"
165

    
166
errorReport :: Snap ()
167
errorReport = do
168
  modifyResponse $ setResponseStatus 404 "Not found"
169
  writeBS "Unable to produce a report for the requested resource"
170

    
171
error404 :: Snap ()
172
error404 = do
173
  modifyResponse $ setResponseStatus 404 "Not found"
174
  writeBS "Resource not found"
175

    
176
-- | Return the report of one collector
177
oneReport :: Snap ()
178
oneReport = do
179
  categoryName <- fmap (maybe mzero unpack) $ getParam "category"
180
  collectorName <- fmap (maybe mzero unpack) $ getParam "collector"
181
  category <-
182
    case catFromName categoryName of
183
      BT.Ok cat -> return cat
184
      BT.Bad msg -> fail msg
185
  collector <-
186
    case
187
      find (\col -> collectorName == dName col) $
188
        filter (\c -> category == dCategory c) collectors of
189
      Just col -> return col
190
      Nothing -> fail "Unable to find the requested collector"
191
  report <- liftIO $ dReport collector
192
  writeBS . pack . J.encode $ report
193

    
194
-- | The function implementing the HTTP API of the monitoring agent.
195
monitoringApi :: Snap ()
196
monitoringApi =
197
  ifTop versionQ <|>
198
  dir "1" version1Api <|>
199
  error404
200

    
201
-- | Main function.
202
main :: MainFn CheckResult PrepResult
203
main _ _ httpConf =
204
  httpServe httpConf $ method GET monitoringApi