Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Server.hs @ 9eeb0aa5

History | View | Annotate | Download (8 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of the Ganeti confd types.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2012 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.Query.Server
29
  ( ConfigReader
30
  , runQueryD
31
  ) where
32

    
33
import Control.Applicative
34
import Control.Concurrent
35
import Control.Exception
36
import Data.Bits (bitSize)
37
import Data.Maybe
38
import qualified Network.Socket as S
39
import qualified Text.JSON as J
40
import Text.JSON (showJSON, JSValue(..))
41
import Text.JSON.Pretty (pp_value)
42
import System.Info (arch)
43

    
44
import qualified Ganeti.Constants as C
45
import qualified Ganeti.Path as Path
46
import Ganeti.Daemon
47
import Ganeti.Objects
48
import qualified Ganeti.Config as Config
49
import Ganeti.BasicTypes
50
import Ganeti.Logging
51
import Ganeti.Luxi
52
import qualified Ganeti.Query.Language as Qlang
53
import Ganeti.Query.Query
54

    
55
-- | A type for functions that can return the configuration when
56
-- executed.
57
type ConfigReader = IO (Result ConfigData)
58

    
59
-- | Minimal wrapper to handle the missing config case.
60
handleCallWrapper :: Result ConfigData -> LuxiOp -> IO (Result JSValue)
61
handleCallWrapper (Bad msg) _ =
62
  return . Bad $ "I do not have access to a valid configuration, cannot\
63
                 \ process queries: " ++ msg
64
handleCallWrapper (Ok config) op = handleCall config op
65

    
66
-- | Actual luxi operation handler.
67
handleCall :: ConfigData -> LuxiOp -> IO (Result JSValue)
68
handleCall cdata QueryClusterInfo =
69
  let cluster = configCluster cdata
70
      hypervisors = clusterEnabledHypervisors cluster
71
      bits = show (bitSize (0::Int)) ++ "bits"
72
      arch_tuple = [bits, arch]
73
      obj = [ ("software_version", showJSON C.releaseVersion)
74
            , ("protocol_version", showJSON C.protocolVersion)
75
            , ("config_version", showJSON C.configVersion)
76
            , ("os_api_version", showJSON $ maximum C.osApiVersions)
77
            , ("export_version", showJSON C.exportVersion)
78
            , ("architecture", showJSON arch_tuple)
79
            , ("name", showJSON $ clusterClusterName cluster)
80
            , ("master", showJSON $ clusterMasterNode cluster)
81
            , ("default_hypervisor", showJSON $ head hypervisors)
82
            , ("enabled_hypervisors", showJSON hypervisors)
83
            , ("hvparams", showJSON $ clusterHvparams cluster)
84
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
85
            , ("beparams", showJSON $ clusterBeparams cluster)
86
            , ("osparams", showJSON $ clusterOsparams cluster)
87
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
88
            , ("nicparams", showJSON $ clusterNicparams cluster)
89
            , ("ndparams", showJSON $ clusterNdparams cluster)
90
            , ("diskparams", showJSON $ clusterDiskparams cluster)
91
            , ("candidate_pool_size",
92
               showJSON $ clusterCandidatePoolSize cluster)
93
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
94
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
95
            , ("use_external_mip_script",
96
               showJSON $ clusterUseExternalMipScript cluster)
97
            , ("volume_group_name", showJSON $ clusterVolumeGroupName cluster)
98
            , ("drbd_usermode_helper",
99
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
100
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
101
            , ("shared_file_storage_dir",
102
               showJSON $ clusterSharedFileStorageDir cluster)
103
            , ("maintain_node_health",
104
               showJSON $ clusterMaintainNodeHealth cluster)
105
            , ("ctime", showJSON $ clusterCtime cluster)
106
            , ("mtime", showJSON $ clusterMtime cluster)
107
            , ("uuid", showJSON $ clusterUuid cluster)
108
            , ("tags", showJSON $ clusterTags cluster)
109
            , ("uid_pool", showJSON $ clusterUidPool cluster)
110
            , ("default_iallocator",
111
               showJSON $ clusterDefaultIallocator cluster)
112
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
113
            , ("primary_ip_version",
114
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
115
             , ("prealloc_wipe_disks",
116
                showJSON $ clusterPreallocWipeDisks cluster)
117
             , ("hidden_os", showJSON $ clusterHiddenOs cluster)
118
             , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
119
            ]
120

    
121
  in return . Ok . J.makeObj $ obj
122

    
123
handleCall cfg (QueryTags kind name) =
124
  let tags = case kind of
125
               TagCluster -> Ok . clusterTags $ configCluster cfg
126
               TagGroup -> groupTags <$> Config.getGroup cfg name
127
               TagNode -> nodeTags <$> Config.getNode cfg name
128
               TagInstance -> instTags <$> Config.getInstance cfg name
129
  in return (J.showJSON <$> tags)
130

    
131
handleCall cfg (Query qkind qfields qfilter) = do
132
  result <- query cfg (Qlang.Query qkind qfields qfilter)
133
  return $ J.showJSON <$> result
134

    
135
handleCall _ (QueryFields qkind qfields) = do
136
  let result = queryFields (Qlang.QueryFields qkind qfields)
137
  return $ J.showJSON <$> result
138

    
139
handleCall _ op =
140
  return . Bad $ "Luxi call '" ++ strOfOp op ++ "' not implemented"
141

    
142

    
143
-- | Given a decoded luxi request, executes it and sends the luxi
144
-- response back to the client.
145
handleClientMsg :: Client -> ConfigReader -> LuxiOp -> IO Bool
146
handleClientMsg client creader args = do
147
  cfg <- creader
148
  logDebug $ "Request: " ++ show args
149
  call_result <- handleCallWrapper cfg args
150
  (!status, !rval) <-
151
    case call_result of
152
      Bad err -> do
153
        let errmsg = "Failed to execute request: " ++ err
154
        logWarning errmsg
155
        return (False, showJSON errmsg)
156
      Ok result -> do
157
        logDebug $ "Result " ++ show (pp_value result)
158
        return (True, result)
159
  sendMsg client $ buildResponse status rval
160
  return True
161

    
162
-- | Handles one iteration of the client protocol: receives message,
163
-- checks for validity and decods, returns response.
164
handleClient :: Client -> ConfigReader -> IO Bool
165
handleClient client creader = do
166
  !msg <- recvMsgExt client
167
  case msg of
168
    RecvConnClosed -> logDebug "Connection closed" >> return False
169
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
170
                     return False
171
    RecvOk payload ->
172
      case validateCall payload >>= decodeCall of
173
        Bad err -> do
174
             let errmsg = "Failed to parse request: " ++ err
175
             logWarning errmsg
176
             sendMsg client $ buildResponse False (showJSON errmsg)
177
             return False
178
        Ok args -> handleClientMsg client creader args
179

    
180
-- | Main client loop: runs one loop of 'handleClient', and if that
181
-- doesn't repot a finished (closed) connection, restarts itself.
182
clientLoop :: Client -> ConfigReader -> IO ()
183
clientLoop client creader = do
184
  result <- handleClient client creader
185
  if result
186
    then clientLoop client creader
187
    else closeClient client
188

    
189
-- | Main loop: accepts clients, forks an I/O thread to handle that
190
-- client, and then restarts.
191
mainLoop :: ConfigReader -> S.Socket -> IO ()
192
mainLoop creader socket = do
193
  client <- acceptClient socket
194
  _ <- forkIO $ clientLoop client creader
195
  mainLoop creader socket
196

    
197
-- | Main function that runs the query endpoint. This should be the
198
-- only one exposed from this module.
199
runQueryD :: Maybe FilePath -> ConfigReader -> IO ()
200
runQueryD fpath creader = do
201
  let socket_path = fromMaybe Path.defaultQuerySocket fpath
202
  cleanupSocket socket_path
203
  bracket
204
    (getServer socket_path)
205
    (closeServer socket_path)
206
    (mainLoop creader)