Statistics
| Branch: | Tag: | Revision:

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

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 Ganeti.Query.Query
56
import Ganeti.Query.Filter (FilterConstructor, makeSimpleFilter
57
                           , makeHostnameFilter)
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
                   -> Maybe FilterConstructor -- ^ the filter algorithm
70
                                              -- to be used, defaults to
71
                                              -- makeSimpleFilter
72
                   -> Bool            -- ^ Whether to do sync queries or not
73
                   -> IO (GenericResult GanetiException JSValue)
74
handleClassicQuery _ _ _ _ _ True =
75
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
76
handleClassicQuery cfg qkind names fields filterconstr _ = do
77
  let fltcon = fromMaybe makeSimpleFilter filterconstr
78
      flt = fltcon (nameField qkind) names
79
  qr <- query cfg True (Qlang.Query qkind fields flt)
80
  return $ showJSON <$> (qr >>= queryCompat)
81

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

    
90
-- | Actual luxi operation handler.
91
handleCall :: ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
92
handleCall cdata QueryClusterInfo =
93
  let cluster = configCluster cdata
94
      hypervisors = clusterEnabledHypervisors cluster
95
      def_hv = case hypervisors of
96
                 x:_ -> showJSON x
97
                 [] -> JSNull
98
      bits = show (bitSize (0::Int)) ++ "bits"
99
      arch_tuple = [bits, arch]
100
      obj = [ ("software_version", showJSON C.releaseVersion)
101
            , ("protocol_version", showJSON C.protocolVersion)
102
            , ("config_version", showJSON C.configVersion)
103
            , ("os_api_version", showJSON $ maximum C.osApiVersions)
104
            , ("export_version", showJSON C.exportVersion)
105
            , ("architecture", showJSON arch_tuple)
106
            , ("name", showJSON $ clusterClusterName cluster)
107
            , ("master", showJSON $ clusterMasterNode cluster)
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
            ]
148

    
149
  in return . Ok . J.makeObj $ obj
150

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

    
159
handleCall cfg (Query qkind qfields qfilter) = do
160
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
161
  return $ J.showJSON <$> result
162

    
163
handleCall _ (QueryFields qkind qfields) = do
164
  let result = queryFields (Qlang.QueryFields qkind qfields)
165
  return $ J.showJSON <$> result
166

    
167
handleCall cfg (QueryNodes names fields lock) =
168
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
169
    (map Left names) fields (Just makeHostnameFilter) lock
170

    
171
handleCall cfg (QueryGroups names fields lock) =
172
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
173
    (map Left names) fields Nothing lock
174

    
175
handleCall cfg (QueryJobs names fields) =
176
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
177
    (map (Right . fromIntegral . fromJobId) names)  fields Nothing False
178

    
179
handleCall _ op =
180
  return . Bad $
181
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
182

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

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

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

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

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

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