Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (10.7 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 Data.IORef
40
import qualified Network.Socket as S
41
import qualified Text.JSON as J
42
import Text.JSON (showJSON, JSValue(..))
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.ConfigReader
52
import Ganeti.BasicTypes
53
import Ganeti.Logging
54
import Ganeti.Luxi
55
import qualified Ganeti.Query.Language as Qlang
56
import qualified Ganeti.Query.Cluster as QCluster
57
import Ganeti.Query.Query
58
import Ganeti.Query.Filter (makeSimpleFilter)
59
import Ganeti.Types
60

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

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

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

    
149
  in case master of
150
    Ok _ -> return . Ok . J.makeObj $ obj
151
    Bad ex -> return $ Bad ex
152

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

    
164
handleCall cfg (Query qkind qfields qfilter) = do
165
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
166
  return $ J.showJSON <$> result
167

    
168
handleCall _ (QueryFields qkind qfields) = do
169
  let result = queryFields (Qlang.QueryFields qkind qfields)
170
  return $ J.showJSON <$> result
171

    
172
handleCall cfg (QueryNodes names fields lock) =
173
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
174
    (map Left names) fields lock
175

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

    
180
handleCall cfg (QueryJobs names fields) =
181
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
182
    (map (Right . fromIntegral . fromJobId) names)  fields False
183

    
184
handleCall cfg (QueryNetworks names fields lock) =
185
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
186
    (map Left names) fields lock
187

    
188
handleCall _ op =
189
  return . Bad $
190
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
191

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

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

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

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

    
249
-- | Type alias for prepMain results
250
type PrepResult = (FilePath, S.Socket, IORef (Result ConfigData))
251

    
252
-- | Check function for luxid.
253
checkMain :: CheckFn ()
254
checkMain _ = return $ Right ()
255

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

    
266
-- | Main function.
267
main :: MainFn () PrepResult
268
main _ _ (socket_path, server, cref) = do
269
  initConfigReader id cref
270
  let creader = readIORef cref
271

    
272
  finally
273
    (forever $ listener creader server)
274
    (closeServer socket_path server)