Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 8a049311

History | View | Annotate | Download (5.8 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.Drbd as Drbd
46
import qualified Ganeti.DataCollectors.InstStatus as InstStatus
47
import Ganeti.DataCollectors.Types
48
import qualified Ganeti.Constants as C
49

    
50
-- * Types and constants definitions
51

    
52
-- | Type alias for checkMain results.
53
type CheckResult = ()
54

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

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

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

    
72
-- | The list of available builtin data collectors.
73
collectors :: [DataCollector]
74
collectors =
75
  [ DataCollector Drbd.dcName Drbd.dcCategory Drbd.dcKind Drbd.dcReport
76
  , DataCollector InstStatus.dcName InstStatus.dcCategory InstStatus.dcKind
77
      InstStatus.dcReport
78
  ]
79

    
80
-- * Configuration handling
81

    
82
-- | The default configuration for the HTTP server.
83
defaultHttpConf :: Config Snap ()
84
defaultHttpConf =
85
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
86
  setCompression False .
87
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
88
  setVerbose False
89
  emptyConfig
90

    
91
-- * Helper functions
92

    
93
-- | Check function for the monitoring agent.
94
checkMain :: CheckFn CheckResult
95
checkMain _ = return $ Right ()
96

    
97
-- | Prepare function for monitoring agent.
98
prepMain :: PrepFn CheckResult PrepResult
99
prepMain opts _ =
100
  return $
101
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
102
      defaultHttpConf
103

    
104
-- * Query answers
105

    
106
-- | Reply to the supported API version numbers query.
107
versionQ :: Snap ()
108
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
109

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

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

    
130
-- | Handler for returning lists.
131
listHandler :: Snap ()
132
listHandler =
133
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
134

    
135
-- | Handler for returning data collector reports.
136
reportHandler :: Snap ()
137
reportHandler =
138
  route
139
    [ ("all", allReports)
140
    , (":category/:collector", oneReport)
141
    ] <|>
142
  errorReport
143

    
144
-- | Return the report of all the available collectors.
145
allReports :: Snap ()
146
allReports = do
147
  reports <- mapM (liftIO . dReport) collectors
148
  writeBS . pack . J.encode $ reports
149

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

    
161
errorReport :: Snap ()
162
errorReport = do
163
  modifyResponse $ setResponseStatus 404 "Not found"
164
  writeBS "Unable to produce a report for the requested resource"
165

    
166
error404 :: Snap ()
167
error404 = do
168
  modifyResponse $ setResponseStatus 404 "Not found"
169
  writeBS "Resource not found"
170

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

    
189
-- | The function implementing the HTTP API of the monitoring agent.
190
monitoringApi :: Snap ()
191
monitoringApi =
192
  ifTop versionQ <|>
193
  dir "1" version1Api <|>
194
  error404
195

    
196
-- | Main function.
197
main :: MainFn CheckResult PrepResult
198
main _ _ httpConf =
199
  httpServe httpConf $ method GET monitoringApi