Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Server.hs @ 37904802

History | View | Annotate | Download (9.3 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of the Ganeti Query2 server.
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
  , prepQueryD
31
  , runQueryD
32
  ) where
33

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

    
45
import qualified Ganeti.Constants as C
46
import Ganeti.Errors
47
import qualified Ganeti.Path as Path
48
import Ganeti.Daemon
49
import Ganeti.Objects
50
import qualified Ganeti.Config as Config
51
import Ganeti.BasicTypes
52
import Ganeti.Logging
53
import Ganeti.Luxi
54
import Ganeti.OpCodes (TagObject(..))
55
import qualified Ganeti.Query.Language as Qlang
56
import Ganeti.Query.Query
57
import Ganeti.Query.Filter (makeSimpleFilter)
58

    
59
-- | A type for functions that can return the configuration when
60
-- executed.
61
type ConfigReader = IO (Result ConfigData)
62

    
63
-- | Helper for classic queries.
64
handleClassicQuery :: ConfigData      -- ^ Cluster config
65
                   -> Qlang.ItemType  -- ^ Query type
66
                   -> [String]        -- ^ Requested names (empty means all)
67
                   -> [String]        -- ^ Requested fields
68
                   -> Bool            -- ^ Whether to do sync queries or not
69
                   -> IO (GenericResult GanetiException JSValue)
70
handleClassicQuery _ _ _ _ True =
71
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
72
handleClassicQuery cfg qkind names fields _ = do
73
  let flt = makeSimpleFilter (nameField qkind) names
74
  qr <- query cfg True (Qlang.Query qkind fields flt)
75
  return $ showJSON <$> (qr >>= queryCompat)
76

    
77
-- | Minimal wrapper to handle the missing config case.
78
handleCallWrapper :: Result ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
79
handleCallWrapper (Bad msg) _ =
80
  return . Bad . ConfigurationError $
81
           "I do not have access to a valid configuration, cannot\
82
           \ process queries: " ++ msg
83
handleCallWrapper (Ok config) op = handleCall config op
84

    
85
-- | Actual luxi operation handler.
86
handleCall :: ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
87
handleCall cdata QueryClusterInfo =
88
  let cluster = configCluster cdata
89
      hypervisors = clusterEnabledHypervisors cluster
90
      bits = show (bitSize (0::Int)) ++ "bits"
91
      arch_tuple = [bits, arch]
92
      obj = [ ("software_version", showJSON C.releaseVersion)
93
            , ("protocol_version", showJSON C.protocolVersion)
94
            , ("config_version", showJSON C.configVersion)
95
            , ("os_api_version", showJSON $ maximum C.osApiVersions)
96
            , ("export_version", showJSON C.exportVersion)
97
            , ("architecture", showJSON arch_tuple)
98
            , ("name", showJSON $ clusterClusterName cluster)
99
            , ("master", showJSON $ clusterMasterNode cluster)
100
            , ("default_hypervisor", showJSON $ head hypervisors)
101
            , ("enabled_hypervisors", showJSON hypervisors)
102
            , ("hvparams", showJSON $ clusterHvparams cluster)
103
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
104
            , ("beparams", showJSON $ clusterBeparams cluster)
105
            , ("osparams", showJSON $ clusterOsparams cluster)
106
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
107
            , ("nicparams", showJSON $ clusterNicparams cluster)
108
            , ("ndparams", showJSON $ clusterNdparams cluster)
109
            , ("diskparams", showJSON $ clusterDiskparams cluster)
110
            , ("candidate_pool_size",
111
               showJSON $ clusterCandidatePoolSize cluster)
112
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
113
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
114
            , ("use_external_mip_script",
115
               showJSON $ clusterUseExternalMipScript cluster)
116
            , ("volume_group_name", showJSON $ clusterVolumeGroupName cluster)
117
            , ("drbd_usermode_helper",
118
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
119
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
120
            , ("shared_file_storage_dir",
121
               showJSON $ clusterSharedFileStorageDir cluster)
122
            , ("maintain_node_health",
123
               showJSON $ clusterMaintainNodeHealth cluster)
124
            , ("ctime", showJSON $ clusterCtime cluster)
125
            , ("mtime", showJSON $ clusterMtime cluster)
126
            , ("uuid", showJSON $ clusterUuid cluster)
127
            , ("tags", showJSON $ clusterTags cluster)
128
            , ("uid_pool", showJSON $ clusterUidPool cluster)
129
            , ("default_iallocator",
130
               showJSON $ clusterDefaultIallocator cluster)
131
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
132
            , ("primary_ip_version",
133
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
134
             , ("prealloc_wipe_disks",
135
                showJSON $ clusterPreallocWipeDisks cluster)
136
             , ("hidden_os", showJSON $ clusterHiddenOs cluster)
137
             , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
138
            ]
139

    
140
  in return . Ok . J.makeObj $ obj
141

    
142
handleCall cfg (QueryTags kind) =
143
  let tags = case kind of
144
               TagCluster       -> Ok . clusterTags $ configCluster cfg
145
               TagGroup    name -> groupTags <$> Config.getGroup    cfg name
146
               TagNode     name -> nodeTags  <$> Config.getNode     cfg name
147
               TagInstance name -> instTags  <$> Config.getInstance cfg name
148
  in return (J.showJSON <$> tags)
149

    
150
handleCall cfg (Query qkind qfields qfilter) = do
151
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
152
  return $ J.showJSON <$> result
153

    
154
handleCall _ (QueryFields qkind qfields) = do
155
  let result = queryFields (Qlang.QueryFields qkind qfields)
156
  return $ J.showJSON <$> result
157

    
158
handleCall cfg (QueryNodes names fields lock) =
159
  handleClassicQuery cfg Qlang.QRNode names fields lock
160

    
161
handleCall cfg (QueryGroups names fields lock) =
162
  handleClassicQuery cfg Qlang.QRGroup names fields lock
163

    
164
handleCall _ op =
165
  return . Bad $
166
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
167

    
168

    
169
-- | Given a decoded luxi request, executes it and sends the luxi
170
-- response back to the client.
171
handleClientMsg :: Client -> ConfigReader -> LuxiOp -> IO Bool
172
handleClientMsg client creader args = do
173
  cfg <- creader
174
  logDebug $ "Request: " ++ show args
175
  call_result <- handleCallWrapper cfg args
176
  (!status, !rval) <-
177
    case call_result of
178
      Bad err -> do
179
        logWarning $ "Failed to execute request: " ++ show err
180
        return (False, showJSON err)
181
      Ok result -> do
182
        logDebug $ "Result " ++ show (pp_value result)
183
        return (True, result)
184
  sendMsg client $ buildResponse status rval
185
  return True
186

    
187
-- | Handles one iteration of the client protocol: receives message,
188
-- checks for validity and decods, returns response.
189
handleClient :: Client -> ConfigReader -> IO Bool
190
handleClient client creader = do
191
  !msg <- recvMsgExt client
192
  case msg of
193
    RecvConnClosed -> logDebug "Connection closed" >> return False
194
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
195
                     return False
196
    RecvOk payload ->
197
      case validateCall payload >>= decodeCall of
198
        Bad err -> do
199
             let errmsg = "Failed to parse request: " ++ err
200
             logWarning errmsg
201
             sendMsg client $ buildResponse False (showJSON errmsg)
202
             return False
203
        Ok args -> handleClientMsg client creader args
204

    
205
-- | Main client loop: runs one loop of 'handleClient', and if that
206
-- doesn't repot a finished (closed) connection, restarts itself.
207
clientLoop :: Client -> ConfigReader -> IO ()
208
clientLoop client creader = do
209
  result <- handleClient client creader
210
  if result
211
    then clientLoop client creader
212
    else closeClient client
213

    
214
-- | Main loop: accepts clients, forks an I/O thread to handle that
215
-- client, and then restarts.
216
mainLoop :: ConfigReader -> S.Socket -> IO ()
217
mainLoop creader socket = do
218
  client <- acceptClient socket
219
  _ <- forkIO $ clientLoop client creader
220
  mainLoop creader socket
221

    
222
-- | Function that prepares the server socket.
223
prepQueryD :: Maybe FilePath -> IO (FilePath, S.Socket)
224
prepQueryD fpath = do
225
  let socket_path = fromMaybe Path.defaultQuerySocket fpath
226
  cleanupSocket socket_path
227
  s <- describeError "binding to the Luxi socket"
228
         Nothing (Just socket_path) $ getServer socket_path
229
  return (socket_path, s)
230

    
231
-- | Main function that runs the query endpoint.
232
runQueryD :: (FilePath, S.Socket) -> ConfigReader -> IO ()
233
runQueryD (socket_path, server) creader =
234
  finally
235
    (mainLoop creader server)
236
    (closeServer socket_path server)