Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 53822ec4

History | View | Annotate | Download (3.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 eb65c915 Michele Tartara
import Snap.Core
37 eb65c915 Michele Tartara
import Snap.Http.Server
38 423b2dd5 Michele Tartara
import Data.ByteString.Char8
39 eb65c915 Michele Tartara
import qualified Text.JSON as J
40 eb65c915 Michele Tartara
41 13cc7b84 Michele Tartara
import Ganeti.Daemon
42 eb65c915 Michele Tartara
import qualified Ganeti.Constants as C
43 13cc7b84 Michele Tartara
44 13cc7b84 Michele Tartara
-- * Types and constants definitions
45 13cc7b84 Michele Tartara
46 13cc7b84 Michele Tartara
-- | Type alias for checkMain results.
47 13cc7b84 Michele Tartara
type CheckResult = ()
48 13cc7b84 Michele Tartara
49 13cc7b84 Michele Tartara
-- | Type alias for prepMain results.
50 eb65c915 Michele Tartara
type PrepResult = Config Snap ()
51 eb65c915 Michele Tartara
52 eb65c915 Michele Tartara
-- | Version of the latest supported http API.
53 eb65c915 Michele Tartara
latestAPIVersion :: Int
54 eb65c915 Michele Tartara
latestAPIVersion = 1
55 eb65c915 Michele Tartara
56 eb65c915 Michele Tartara
-- * Configuration handling
57 eb65c915 Michele Tartara
58 eb65c915 Michele Tartara
-- | The default configuration for the HTTP server.
59 eb65c915 Michele Tartara
defaultHttpConf :: Config Snap ()
60 eb65c915 Michele Tartara
defaultHttpConf =
61 eb65c915 Michele Tartara
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
62 eb65c915 Michele Tartara
  setCompression False .
63 eb65c915 Michele Tartara
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
64 eb65c915 Michele Tartara
  setVerbose False
65 eb65c915 Michele Tartara
  emptyConfig
66 13cc7b84 Michele Tartara
67 13cc7b84 Michele Tartara
-- * Helper functions
68 13cc7b84 Michele Tartara
69 13cc7b84 Michele Tartara
-- | Check function for the monitoring agent.
70 13cc7b84 Michele Tartara
checkMain :: CheckFn CheckResult
71 13cc7b84 Michele Tartara
checkMain _ = return $ Right ()
72 13cc7b84 Michele Tartara
73 13cc7b84 Michele Tartara
-- | Prepare function for monitoring agent.
74 13cc7b84 Michele Tartara
prepMain :: PrepFn CheckResult PrepResult
75 eb65c915 Michele Tartara
prepMain opts _ =
76 eb65c915 Michele Tartara
  return $
77 eb65c915 Michele Tartara
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
78 eb65c915 Michele Tartara
      defaultHttpConf
79 eb65c915 Michele Tartara
80 eb65c915 Michele Tartara
-- * Query answers
81 eb65c915 Michele Tartara
82 eb65c915 Michele Tartara
-- | Reply to the supported API version numbers query.
83 eb65c915 Michele Tartara
versionQ :: Snap ()
84 423b2dd5 Michele Tartara
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
85 423b2dd5 Michele Tartara
86 423b2dd5 Michele Tartara
-- | Version 1 of the monitoring HTTP API.
87 423b2dd5 Michele Tartara
version1Api :: Snap ()
88 423b2dd5 Michele Tartara
version1Api =
89 423b2dd5 Michele Tartara
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
90 423b2dd5 Michele Tartara
  in ifTop returnNull <|>
91 423b2dd5 Michele Tartara
     route
92 423b2dd5 Michele Tartara
       [ ("list", listHandler)
93 423b2dd5 Michele Tartara
       , ("report", reportHandler)
94 423b2dd5 Michele Tartara
       ]
95 423b2dd5 Michele Tartara
96 423b2dd5 Michele Tartara
-- | Handler for returning lists.
97 423b2dd5 Michele Tartara
listHandler :: Snap ()
98 423b2dd5 Michele Tartara
listHandler =
99 423b2dd5 Michele Tartara
  dir "collectors" $ writeText "TODO: return the list of collectors"
100 423b2dd5 Michele Tartara
101 423b2dd5 Michele Tartara
-- | Handler for returning data collector reports.
102 423b2dd5 Michele Tartara
reportHandler :: Snap ()
103 423b2dd5 Michele Tartara
reportHandler =
104 423b2dd5 Michele Tartara
  route
105 423b2dd5 Michele Tartara
    [ ("all", allReports)
106 423b2dd5 Michele Tartara
    , (":category/:collector", oneReport)
107 423b2dd5 Michele Tartara
    ]
108 423b2dd5 Michele Tartara
109 423b2dd5 Michele Tartara
-- | Return the report of all the available collectors
110 423b2dd5 Michele Tartara
allReports :: Snap ()
111 423b2dd5 Michele Tartara
allReports = writeText "TODO: return the reports of all the collectors"
112 423b2dd5 Michele Tartara
113 423b2dd5 Michele Tartara
-- | Return the report of one collector
114 423b2dd5 Michele Tartara
oneReport :: Snap ()
115 423b2dd5 Michele Tartara
oneReport = do
116 423b2dd5 Michele Tartara
  category <- fmap (maybe mzero unpack) $ getParam "category"
117 423b2dd5 Michele Tartara
  collector <- fmap (maybe mzero unpack) $ getParam "collector"
118 423b2dd5 Michele Tartara
  writeBS . pack $
119 423b2dd5 Michele Tartara
    "TODO: return the report for collector " ++ category
120 423b2dd5 Michele Tartara
      ++ "/" ++ collector
121 eb65c915 Michele Tartara
122 eb65c915 Michele Tartara
-- | The function implementing the HTTP API of the monitoring agent.
123 eb65c915 Michele Tartara
-- TODO: Currently it only replies to the API version query: implement all the
124 eb65c915 Michele Tartara
-- missing features.
125 eb65c915 Michele Tartara
monitoringApi :: Snap ()
126 eb65c915 Michele Tartara
monitoringApi =
127 423b2dd5 Michele Tartara
  ifTop versionQ <|>
128 423b2dd5 Michele Tartara
  dir "1" version1Api
129 13cc7b84 Michele Tartara
130 13cc7b84 Michele Tartara
-- | Main function.
131 13cc7b84 Michele Tartara
main :: MainFn CheckResult PrepResult
132 eb65c915 Michele Tartara
main _ _ httpConf =
133 423b2dd5 Michele Tartara
  httpServe httpConf $ method GET monitoringApi