Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Server.hs @ c87997d2

History | View | Annotate | Download (10.9 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of the Ganeti Query2 server.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2012, 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.Query.Server
29
  ( main
30
  , checkMain
31
  , prepMain
32
  ) where
33

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

    
46
import qualified Ganeti.Constants as C
47
import qualified Ganeti.ConstantUtils as ConstantUtils (unFrozenSet)
48
import Ganeti.Errors
49
import qualified Ganeti.Path as Path
50
import Ganeti.Daemon
51
import Ganeti.Objects
52
import qualified Ganeti.Config as Config
53
import Ganeti.ConfigReader
54
import Ganeti.BasicTypes
55
import Ganeti.Logging
56
import Ganeti.Luxi
57
import qualified Ganeti.Query.Language as Qlang
58
import qualified Ganeti.Query.Cluster as QCluster
59
import Ganeti.Query.Query
60
import Ganeti.Query.Filter (makeSimpleFilter)
61
import Ganeti.Types
62

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

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

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

    
153
  in case master of
154
    Ok _ -> return . Ok . J.makeObj $ obj
155
    Bad ex -> return $ Bad ex
156

    
157
handleCall cfg (QueryTags kind name) = do
158
  let tags = case kind of
159
               TagKindCluster  -> Ok . clusterTags $ configCluster cfg
160
               TagKindGroup    -> groupTags <$> Config.getGroup    cfg name
161
               TagKindNode     -> nodeTags  <$> Config.getNode     cfg name
162
               TagKindInstance -> instTags  <$> Config.getInstance cfg name
163
               TagKindNetwork  -> Bad $ OpPrereqError
164
                                        "Network tag is not allowed"
165
                                        ECodeInval
166
  return (J.showJSON <$> tags)
167

    
168
handleCall cfg (Query qkind qfields qfilter) = do
169
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
170
  return $ J.showJSON <$> result
171

    
172
handleCall _ (QueryFields qkind qfields) = do
173
  let result = queryFields (Qlang.QueryFields qkind qfields)
174
  return $ J.showJSON <$> result
175

    
176
handleCall cfg (QueryNodes names fields lock) =
177
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
178
    (map Left names) fields lock
179

    
180
handleCall cfg (QueryGroups names fields lock) =
181
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
182
    (map Left names) fields lock
183

    
184
handleCall cfg (QueryJobs names fields) =
185
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
186
    (map (Right . fromIntegral . fromJobId) names)  fields False
187

    
188
handleCall cfg (QueryNetworks names fields lock) =
189
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
190
    (map Left names) fields lock
191

    
192
handleCall _ op =
193
  return . Bad $
194
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
195

    
196
-- | Given a decoded luxi request, executes it and sends the luxi
197
-- response back to the client.
198
handleClientMsg :: Client -> ConfigReader -> LuxiOp -> IO Bool
199
handleClientMsg client creader args = do
200
  cfg <- creader
201
  logDebug $ "Request: " ++ show args
202
  call_result <- handleCallWrapper cfg args
203
  (!status, !rval) <-
204
    case call_result of
205
      Bad err -> do
206
        logWarning $ "Failed to execute request " ++ show args ++ ": "
207
                     ++ show err
208
        return (False, showJSON err)
209
      Ok result -> do
210
        -- only log the first 2,000 chars of the result
211
        logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
212
        logInfo $ "Successfully handled " ++ strOfOp args
213
        return (True, result)
214
  sendMsg client $ buildResponse status rval
215
  return True
216

    
217
-- | Handles one iteration of the client protocol: receives message,
218
-- checks it for validity and decodes it, returns response.
219
handleClient :: Client -> ConfigReader -> IO Bool
220
handleClient client creader = do
221
  !msg <- recvMsgExt client
222
  logDebug $ "Received message: " ++ show msg
223
  case msg of
224
    RecvConnClosed -> logDebug "Connection closed" >> return False
225
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
226
                     return False
227
    RecvOk payload ->
228
      case validateCall payload >>= decodeCall of
229
        Bad err -> do
230
             let errmsg = "Failed to parse request: " ++ err
231
             logWarning errmsg
232
             sendMsg client $ buildResponse False (showJSON errmsg)
233
             return False
234
        Ok args -> handleClientMsg client creader args
235

    
236
-- | Main client loop: runs one loop of 'handleClient', and if that
237
-- doesn't report a finished (closed) connection, restarts itself.
238
clientLoop :: Client -> ConfigReader -> IO ()
239
clientLoop client creader = do
240
  result <- handleClient client creader
241
  if result
242
    then clientLoop client creader
243
    else closeClient client
244

    
245
-- | Main listener loop: accepts clients, forks an I/O thread to handle
246
-- that client.
247
listener :: ConfigReader -> S.Socket -> IO ()
248
listener creader socket = do
249
  client <- acceptClient socket
250
  _ <- forkIO $ clientLoop client creader
251
  return ()
252

    
253
-- | Type alias for prepMain results
254
type PrepResult = (FilePath, S.Socket, IORef (Result ConfigData))
255

    
256
-- | Check function for luxid.
257
checkMain :: CheckFn ()
258
checkMain _ = return $ Right ()
259

    
260
-- | Prepare function for luxid.
261
prepMain :: PrepFn () PrepResult
262
prepMain _ _ = do
263
  socket_path <- Path.defaultQuerySocket
264
  cleanupSocket socket_path
265
  s <- describeError "binding to the Luxi socket"
266
         Nothing (Just socket_path) $ getServer True socket_path
267
  cref <- newIORef (Bad "Configuration not yet loaded")
268
  return (socket_path, s, cref)
269

    
270
-- | Main function.
271
main :: MainFn () PrepResult
272
main _ _ (socket_path, server, cref) = do
273
  initConfigReader id cref
274
  let creader = readIORef cref
275

    
276
  finally
277
    (forever $ listener creader server)
278
    (closeServer socket_path server)