Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Server.hs @ 1c3231aa

History | View | Annotate | Download (10.2 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
  ( 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 System.Info (arch)
43

    
44
import qualified Ganeti.Constants as C
45
import Ganeti.Errors
46
import qualified Ganeti.Path as Path
47
import Ganeti.Daemon
48
import Ganeti.Objects
49
import qualified Ganeti.Config as Config
50
import Ganeti.BasicTypes
51
import Ganeti.Logging
52
import Ganeti.Luxi
53
import Ganeti.OpCodes (TagObject(..))
54
import qualified Ganeti.Query.Language as Qlang
55
import qualified Ganeti.Query.Cluster as QCluster
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
                   -> [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 C.osApiVersions)
102
            , ("export_version", showJSON C.exportVersion)
103
            , ("architecture", showJSON arch_tuple)
104
            , ("name", showJSON $ clusterClusterName cluster)
105
            , ("master", showJSON (case master of
106
                                     Ok name -> name
107
                                     _ -> undefined))
108
            , ("default_hypervisor", def_hv)
109
            , ("enabled_hypervisors", showJSON hypervisors)
110
            , ("hvparams", showJSON $ clusterHvparams cluster)
111
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
112
            , ("beparams", showJSON $ clusterBeparams cluster)
113
            , ("osparams", showJSON $ clusterOsparams cluster)
114
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
115
            , ("nicparams", showJSON $ clusterNicparams cluster)
116
            , ("ndparams", showJSON $ clusterNdparams cluster)
117
            , ("diskparams", showJSON $ clusterDiskparams cluster)
118
            , ("candidate_pool_size",
119
               showJSON $ clusterCandidatePoolSize cluster)
120
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
121
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
122
            , ("use_external_mip_script",
123
               showJSON $ clusterUseExternalMipScript cluster)
124
            , ("volume_group_name",
125
               maybe JSNull showJSON (clusterVolumeGroupName cluster))
126
            , ("drbd_usermode_helper",
127
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
128
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
129
            , ("shared_file_storage_dir",
130
               showJSON $ clusterSharedFileStorageDir cluster)
131
            , ("maintain_node_health",
132
               showJSON $ clusterMaintainNodeHealth cluster)
133
            , ("ctime", showJSON $ clusterCtime cluster)
134
            , ("mtime", showJSON $ clusterMtime cluster)
135
            , ("uuid", showJSON $ clusterUuid cluster)
136
            , ("tags", showJSON $ clusterTags cluster)
137
            , ("uid_pool", showJSON $ clusterUidPool cluster)
138
            , ("default_iallocator",
139
               showJSON $ clusterDefaultIallocator cluster)
140
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
141
            , ("primary_ip_version",
142
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
143
            , ("prealloc_wipe_disks",
144
               showJSON $ clusterPreallocWipeDisks cluster)
145
            , ("hidden_os", showJSON $ clusterHiddenOs cluster)
146
            , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
147
            , ("enabled_disk_templates", showJSON diskTemplates)
148
            ]
149

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

    
154
handleCall cfg (QueryTags kind) =
155
  let tags = case kind of
156
               TagCluster       -> Ok . clusterTags $ configCluster cfg
157
               TagGroup    name -> groupTags <$> Config.getGroup    cfg name
158
               TagNode     name -> nodeTags  <$> Config.getNode     cfg name
159
               TagInstance name -> instTags  <$> Config.getInstance cfg name
160
  in return (J.showJSON <$> tags)
161

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

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

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

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

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

    
182
handleCall _ op =
183
  return . Bad $
184
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
185

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

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

    
225
-- | Main client loop: runs one loop of 'handleClient', and if that
226
-- doesn't report a finished (closed) connection, restarts itself.
227
clientLoop :: Client -> ConfigReader -> IO ()
228
clientLoop client creader = do
229
  result <- handleClient client creader
230
  if result
231
    then clientLoop client creader
232
    else closeClient client
233

    
234
-- | Main loop: accepts clients, forks an I/O thread to handle that
235
-- client, and then restarts.
236
mainLoop :: ConfigReader -> S.Socket -> IO ()
237
mainLoop creader socket = do
238
  client <- acceptClient socket
239
  _ <- forkIO $ clientLoop client creader
240
  mainLoop creader socket
241

    
242
-- | Function that prepares the server socket.
243
prepQueryD :: Maybe FilePath -> IO (FilePath, S.Socket)
244
prepQueryD fpath = do
245
  def_socket <- Path.defaultQuerySocket
246
  let socket_path = fromMaybe def_socket fpath
247
  cleanupSocket socket_path
248
  s <- describeError "binding to the Luxi socket"
249
         Nothing (Just socket_path) $ getServer socket_path
250
  return (socket_path, s)
251

    
252
-- | Main function that runs the query endpoint.
253
runQueryD :: (FilePath, S.Socket) -> ConfigReader -> IO ()
254
runQueryD (socket_path, server) creader =
255
  finally
256
    (mainLoop creader server)
257
    (closeServer socket_path server)