Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Server.hs @ 3cb9bd38

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
import qualified Ganeti.Version as Version
63

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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