Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Monitoring / Server.hs @ 423b2dd5

History | View | Annotate | Download (3.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 Snap.Core
37
import Snap.Http.Server
38
import Data.ByteString.Char8
39
import qualified Text.JSON as J
40

    
41
import Ganeti.Daemon
42
import qualified Ganeti.Constants as C
43

    
44
-- * Types and constants definitions
45

    
46
-- | Type alias for checkMain results.
47
type CheckResult = ()
48

    
49
-- | Type alias for prepMain results.
50
type PrepResult = Config Snap ()
51

    
52
-- | Version of the latest supported http API.
53
latestAPIVersion :: Int
54
latestAPIVersion = 1
55

    
56
-- * Configuration handling
57

    
58
-- | The default configuration for the HTTP server.
59
defaultHttpConf :: Config Snap ()
60
defaultHttpConf =
61
  setAccessLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondAccess) .
62
  setCompression False .
63
  setErrorLog (ConfigFileLog C.daemonsExtraLogfilesGanetiMondError) $
64
  setVerbose False
65
  emptyConfig
66

    
67
-- * Helper functions
68

    
69
-- | Check function for the monitoring agent.
70
checkMain :: CheckFn CheckResult
71
checkMain _ = return $ Right ()
72

    
73
-- | Prepare function for monitoring agent.
74
prepMain :: PrepFn CheckResult PrepResult
75
prepMain opts _ =
76
  return $
77
    setPort (maybe C.defaultMondPort fromIntegral (optPort opts))
78
      defaultHttpConf
79

    
80
-- * Query answers
81

    
82
-- | Reply to the supported API version numbers query.
83
versionQ :: Snap ()
84
versionQ = writeBS . pack $ J.encode [latestAPIVersion]
85

    
86
-- | Version 1 of the monitoring HTTP API.
87
version1Api :: Snap ()
88
version1Api =
89
  let returnNull = writeBS . pack $ J.encode J.JSNull :: Snap ()
90
  in ifTop returnNull <|>
91
     route
92
       [ ("list", listHandler)
93
       , ("report", reportHandler)
94
       ]
95

    
96
-- | Handler for returning lists.
97
listHandler :: Snap ()
98
listHandler =
99
  dir "collectors" $ writeText "TODO: return the list of collectors"
100

    
101
-- | Handler for returning data collector reports.
102
reportHandler :: Snap ()
103
reportHandler =
104
  route
105
    [ ("all", allReports)
106
    , (":category/:collector", oneReport)
107
    ]
108

    
109
-- | Return the report of all the available collectors
110
allReports :: Snap ()
111
allReports = writeText "TODO: return the reports of all the collectors"
112

    
113
-- | Return the report of one collector
114
oneReport :: Snap ()
115
oneReport = do
116
  category <- fmap (maybe mzero unpack) $ getParam "category"
117
  collector <- fmap (maybe mzero unpack) $ getParam "collector"
118
  writeBS . pack $
119
    "TODO: return the report for collector " ++ category
120
      ++ "/" ++ collector
121

    
122
-- | The function implementing the HTTP API of the monitoring agent.
123
-- TODO: Currently it only replies to the API version query: implement all the
124
-- missing features.
125
monitoringApi :: Snap ()
126
monitoringApi =
127
  ifTop versionQ <|>
128
  dir "1" version1Api
129

    
130
-- | Main function.
131
main :: MainFn CheckResult PrepResult
132
main _ _ httpConf =
133
  httpServe httpConf $ method GET monitoringApi