Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.5 kB)

1 13cc7b84 Michele Tartara
{-# LANGUAGE OverloadedStrings #-}
2 13cc7b84 Michele Tartara
3 13cc7b84 Michele Tartara
{-| Implementation of the Ganeti confd server functionality.
4 13cc7b84 Michele Tartara
5 13cc7b84 Michele Tartara
-}
6 13cc7b84 Michele Tartara
7 13cc7b84 Michele Tartara
{-
8 13cc7b84 Michele Tartara
9 13cc7b84 Michele Tartara
Copyright (C) 2013 Google Inc.
10 13cc7b84 Michele Tartara
11 13cc7b84 Michele Tartara
This program is free software; you can redistribute it and/or modify
12 13cc7b84 Michele Tartara
it under the terms of the GNU General Public License as published by
13 13cc7b84 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
14 13cc7b84 Michele Tartara
(at your option) any later version.
15 13cc7b84 Michele Tartara
16 13cc7b84 Michele Tartara
This program is distributed in the hope that it will be useful, but
17 13cc7b84 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
18 13cc7b84 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 13cc7b84 Michele Tartara
General Public License for more details.
20 13cc7b84 Michele Tartara
21 13cc7b84 Michele Tartara
You should have received a copy of the GNU General Public License
22 13cc7b84 Michele Tartara
along with this program; if not, write to the Free Software
23 13cc7b84 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 13cc7b84 Michele Tartara
02110-1301, USA.
25 13cc7b84 Michele Tartara
26 13cc7b84 Michele Tartara
-}
27 13cc7b84 Michele Tartara
28 13cc7b84 Michele Tartara
module Ganeti.Monitoring.Server
29 13cc7b84 Michele Tartara
  ( main
30 13cc7b84 Michele Tartara
  , checkMain
31 13cc7b84 Michele Tartara
  , prepMain
32 13cc7b84 Michele Tartara
  ) where
33 13cc7b84 Michele Tartara
34 423b2dd5 Michele Tartara
import Control.Applicative
35 423b2dd5 Michele Tartara
import Control.Monad
36 db1ad1d5 Michele Tartara
import Control.Monad.IO.Class
37 db1ad1d5 Michele Tartara
import Data.ByteString.Char8 hiding (map, filter, find)
38 db1ad1d5 Michele Tartara
import Data.List
39 eb65c915 Michele Tartara
import Snap.Core
40 eb65c915 Michele Tartara
import Snap.Http.Server
41 eb65c915 Michele Tartara
import qualified Text.JSON as J
42 eb65c915 Michele Tartara
43 db1ad1d5 Michele Tartara
import qualified Ganeti.BasicTypes as BT
44 13cc7b84 Michele Tartara
import Ganeti.Daemon
45 ecb783f0 Michele Tartara
import qualified Ganeti.DataCollectors.Drbd as Drbd
46 ecb783f0 Michele Tartara
import Ganeti.DataCollectors.Types
47 eb65c915 Michele Tartara
import qualified Ganeti.Constants as C
48 13cc7b84 Michele Tartara
49 13cc7b84 Michele Tartara
-- * Types and constants definitions
50 13cc7b84 Michele Tartara
51 13cc7b84 Michele Tartara
-- | Type alias for checkMain results.
52 13cc7b84 Michele Tartara
type CheckResult = ()
53 13cc7b84 Michele Tartara
54 13cc7b84 Michele Tartara
-- | Type alias for prepMain results.
55 eb65c915 Michele Tartara
type PrepResult = Config Snap ()
56 eb65c915 Michele Tartara
57 eb65c915 Michele Tartara
-- | Version of the latest supported http API.
58 eb65c915 Michele Tartara
latestAPIVersion :: Int
59 eb65c915 Michele Tartara
latestAPIVersion = 1
60 eb65c915 Michele Tartara
61 ecb783f0 Michele Tartara
-- | Type describing a data collector basic information
62 ecb783f0 Michele Tartara
data DataCollector = DataCollector
63 ecb783f0 Michele Tartara
  { dName     :: String           -- ^ Name of the data collector
64 ecb783f0 Michele Tartara
  , dCategory :: Maybe DCCategory -- ^ Category (storage, instance, ecc)
65 ecb783f0 Michele Tartara
                                  --   of the collector
66 ecb783f0 Michele Tartara
  , dKind     :: DCKind           -- ^ Kind (performance or status reporting) of
67 ecb783f0 Michele Tartara
                                  --   the data collector
68 db1ad1d5 Michele Tartara
  , dReport   :: IO DCReport      -- ^ Report produced by the collector
69 ecb783f0 Michele Tartara
  }
70 ecb783f0 Michele Tartara
71 ecb783f0 Michele Tartara
-- | The list of available builtin data collectors.
72 ecb783f0 Michele Tartara
collectors :: [DataCollector]
73 ecb783f0 Michele Tartara
collectors =
74 db1ad1d5 Michele Tartara
  [ DataCollector Drbd.dcName Drbd.dcCategory Drbd.dcKind Drbd.dcReport
75 ecb783f0 Michele Tartara
  ]
76 ecb783f0 Michele Tartara
77 eb65c915 Michele Tartara
-- * Configuration handling
78 eb65c915 Michele Tartara
79 eb65c915 Michele Tartara
-- | The default configuration for the HTTP server.
80 eb65c915 Michele Tartara
defaultHttpConf :: Config Snap ()
81 eb65c915 Michele Tartara
defaultHttpConf =
82 eb65c915 Michele Tartara
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
83 eb65c915 Michele Tartara
  setCompression False .
84 eb65c915 Michele Tartara
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
85 eb65c915 Michele Tartara
  setVerbose False
86 eb65c915 Michele Tartara
  emptyConfig
87 13cc7b84 Michele Tartara
88 13cc7b84 Michele Tartara
-- * Helper functions
89 13cc7b84 Michele Tartara
90 13cc7b84 Michele Tartara
-- | Check function for the monitoring agent.
91 13cc7b84 Michele Tartara
checkMain :: CheckFn CheckResult
92 13cc7b84 Michele Tartara
checkMain _ = return $ Right ()
93 13cc7b84 Michele Tartara
94 13cc7b84 Michele Tartara
-- | Prepare function for monitoring agent.
95 13cc7b84 Michele Tartara
prepMain :: PrepFn CheckResult PrepResult
96 eb65c915 Michele Tartara
prepMain opts _ =
97 eb65c915 Michele Tartara
  return $
98 eb65c915 Michele Tartara
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
99 eb65c915 Michele Tartara
      defaultHttpConf
100 eb65c915 Michele Tartara
101 eb65c915 Michele Tartara
-- * Query answers
102 eb65c915 Michele Tartara
103 eb65c915 Michele Tartara
-- | Reply to the supported API version numbers query.
104 eb65c915 Michele Tartara
versionQ :: Snap ()
105 423b2dd5 Michele Tartara
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
106 423b2dd5 Michele Tartara
107 423b2dd5 Michele Tartara
-- | Version 1 of the monitoring HTTP API.
108 423b2dd5 Michele Tartara
version1Api :: Snap ()
109 423b2dd5 Michele Tartara
version1Api =
110 423b2dd5 Michele Tartara
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
111 423b2dd5 Michele Tartara
  in ifTop returnNull <|>
112 423b2dd5 Michele Tartara
     route
113 423b2dd5 Michele Tartara
       [ ("list", listHandler)
114 423b2dd5 Michele Tartara
       , ("report", reportHandler)
115 423b2dd5 Michele Tartara
       ]
116 423b2dd5 Michele Tartara
117 ecb783f0 Michele Tartara
-- | Get the JSON representation of a data collector to be used in the collector
118 ecb783f0 Michele Tartara
-- list.
119 ecb783f0 Michele Tartara
dcListItem :: DataCollector -> J.JSValue
120 ecb783f0 Michele Tartara
dcListItem dc =
121 ecb783f0 Michele Tartara
  J.JSArray
122 ecb783f0 Michele Tartara
    [ J.showJSON $ dName dc
123 ecb783f0 Michele Tartara
    , maybe J.JSNull J.showJSON $ dCategory dc
124 ecb783f0 Michele Tartara
    , J.showJSON $ dKind dc
125 ecb783f0 Michele Tartara
    ]
126 ecb783f0 Michele Tartara
127 423b2dd5 Michele Tartara
-- | Handler for returning lists.
128 423b2dd5 Michele Tartara
listHandler :: Snap ()
129 423b2dd5 Michele Tartara
listHandler =
130 ecb783f0 Michele Tartara
  dir "collectors" . writeBS . pack . J.encode $ map dcListItem collectors
131 423b2dd5 Michele Tartara
132 423b2dd5 Michele Tartara
-- | Handler for returning data collector reports.
133 423b2dd5 Michele Tartara
reportHandler :: Snap ()
134 423b2dd5 Michele Tartara
reportHandler =
135 423b2dd5 Michele Tartara
  route
136 423b2dd5 Michele Tartara
    [ ("all", allReports)
137 423b2dd5 Michele Tartara
    , (":category/:collector", oneReport)
138 423b2dd5 Michele Tartara
    ]
139 423b2dd5 Michele Tartara
140 db1ad1d5 Michele Tartara
-- | Return the report of all the available collectors.
141 423b2dd5 Michele Tartara
allReports :: Snap ()
142 423b2dd5 Michele Tartara
allReports = writeText "TODO: return the reports of all the collectors"
143 423b2dd5 Michele Tartara
144 db1ad1d5 Michele Tartara
-- | Returns a category given its name.
145 db1ad1d5 Michele Tartara
-- If "collector" is given as the name, the collector has no category, and
146 db1ad1d5 Michele Tartara
-- Nothing will be returned.
147 db1ad1d5 Michele Tartara
catFromName :: String -> BT.Result (Maybe DCCategory)
148 db1ad1d5 Michele Tartara
catFromName "instance"   = BT.Ok $ Just DCInstance
149 db1ad1d5 Michele Tartara
catFromName "storage"    = BT.Ok $ Just DCStorage
150 db1ad1d5 Michele Tartara
catFromName "daemon"     = BT.Ok $ Just DCDaemon
151 db1ad1d5 Michele Tartara
catFromName "hypervisor" = BT.Ok $ Just DCHypervisor
152 db1ad1d5 Michele Tartara
catFromName "default"    = BT.Ok Nothing
153 db1ad1d5 Michele Tartara
catFromName _            = BT.Bad "No such category"
154 db1ad1d5 Michele Tartara
155 423b2dd5 Michele Tartara
-- | Return the report of one collector
156 423b2dd5 Michele Tartara
oneReport :: Snap ()
157 423b2dd5 Michele Tartara
oneReport = do
158 db1ad1d5 Michele Tartara
  categoryName <- fmap (maybe mzero unpack) $ getParam "category"
159 db1ad1d5 Michele Tartara
  collectorName <- fmap (maybe mzero unpack) $ getParam "collector"
160 db1ad1d5 Michele Tartara
  category <-
161 db1ad1d5 Michele Tartara
    case catFromName categoryName of
162 db1ad1d5 Michele Tartara
      BT.Ok cat -> return cat
163 db1ad1d5 Michele Tartara
      BT.Bad msg -> fail msg
164 db1ad1d5 Michele Tartara
  collector <-
165 db1ad1d5 Michele Tartara
    case
166 db1ad1d5 Michele Tartara
      find (\col -> collectorName == dName col) $
167 db1ad1d5 Michele Tartara
        filter (\c -> category == dCategory c) collectors of
168 db1ad1d5 Michele Tartara
      Just col -> return col
169 db1ad1d5 Michele Tartara
      Nothing -> fail "Unable to find the requested collector"
170 db1ad1d5 Michele Tartara
  report <- liftIO $ dReport collector
171 db1ad1d5 Michele Tartara
  writeBS . pack . J.encode $ report
172 eb65c915 Michele Tartara
173 eb65c915 Michele Tartara
-- | The function implementing the HTTP API of the monitoring agent.
174 eb65c915 Michele Tartara
-- TODO: Currently it only replies to the API version query: implement all the
175 eb65c915 Michele Tartara
-- missing features.
176 eb65c915 Michele Tartara
monitoringApi :: Snap ()
177 eb65c915 Michele Tartara
monitoringApi =
178 423b2dd5 Michele Tartara
  ifTop versionQ <|>
179 423b2dd5 Michele Tartara
  dir "1" version1Api
180 13cc7b84 Michele Tartara
181 13cc7b84 Michele Tartara
-- | Main function.
182 13cc7b84 Michele Tartara
main :: MainFn CheckResult PrepResult
183 eb65c915 Michele Tartara
main _ _ httpConf =
184 423b2dd5 Michele Tartara
  httpServe httpConf $ method GET monitoringApi