Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (10.9 kB)

1 25b54de0 Iustin Pop
{-# LANGUAGE BangPatterns #-}
2 25b54de0 Iustin Pop
3 d120506c Agata Murawska
{-| Implementation of the Ganeti Query2 server.
4 25b54de0 Iustin Pop
5 25b54de0 Iustin Pop
-}
6 25b54de0 Iustin Pop
7 25b54de0 Iustin Pop
{-
8 25b54de0 Iustin Pop
9 72747d91 Iustin Pop
Copyright (C) 2012, 2013 Google Inc.
10 25b54de0 Iustin Pop
11 25b54de0 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 25b54de0 Iustin Pop
it under the terms of the GNU General Public License as published by
13 25b54de0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 25b54de0 Iustin Pop
(at your option) any later version.
15 25b54de0 Iustin Pop
16 25b54de0 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 25b54de0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 25b54de0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 25b54de0 Iustin Pop
General Public License for more details.
20 25b54de0 Iustin Pop
21 25b54de0 Iustin Pop
You should have received a copy of the GNU General Public License
22 25b54de0 Iustin Pop
along with this program; if not, write to the Free Software
23 25b54de0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 25b54de0 Iustin Pop
02110-1301, USA.
25 25b54de0 Iustin Pop
26 25b54de0 Iustin Pop
-}
27 25b54de0 Iustin Pop
28 4cab6703 Iustin Pop
module Ganeti.Query.Server
29 670e954a Thomas Thrainer
  ( main
30 670e954a Thomas Thrainer
  , checkMain
31 670e954a Thomas Thrainer
  , prepMain
32 0d0ac025 Iustin Pop
  ) where
33 25b54de0 Iustin Pop
34 f2374060 Iustin Pop
import Control.Applicative
35 25b54de0 Iustin Pop
import Control.Concurrent
36 25b54de0 Iustin Pop
import Control.Exception
37 670e954a Thomas Thrainer
import Control.Monad (forever)
38 25b54de0 Iustin Pop
import Data.Bits (bitSize)
39 c87997d2 Jose A. Lopes
import qualified Data.Set as Set (toList)
40 670e954a Thomas Thrainer
import Data.IORef
41 25b54de0 Iustin Pop
import qualified Network.Socket as S
42 25b54de0 Iustin Pop
import qualified Text.JSON as J
43 25b54de0 Iustin Pop
import Text.JSON (showJSON, JSValue(..))
44 25b54de0 Iustin Pop
import System.Info (arch)
45 25b54de0 Iustin Pop
46 25b54de0 Iustin Pop
import qualified Ganeti.Constants as C
47 c87997d2 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils (unFrozenSet)
48 5183e8be Iustin Pop
import Ganeti.Errors
49 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
50 0d0ac025 Iustin Pop
import Ganeti.Daemon
51 25b54de0 Iustin Pop
import Ganeti.Objects
52 f2374060 Iustin Pop
import qualified Ganeti.Config as Config
53 218e3b0f Thomas Thrainer
import Ganeti.ConfigReader
54 25b54de0 Iustin Pop
import Ganeti.BasicTypes
55 25b54de0 Iustin Pop
import Ganeti.Logging
56 25b54de0 Iustin Pop
import Ganeti.Luxi
57 4cab6703 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
58 1c3231aa Thomas Thrainer
import qualified Ganeti.Query.Cluster as QCluster
59 4cbe9bda Iustin Pop
import Ganeti.Query.Query
60 c4e0d065 Klaus Aehlig
import Ganeti.Query.Filter (makeSimpleFilter)
61 6e94b75c Jose A. Lopes
import Ganeti.Types
62 25b54de0 Iustin Pop
63 cd67e337 Iustin Pop
-- | Helper for classic queries.
64 cd67e337 Iustin Pop
handleClassicQuery :: ConfigData      -- ^ Cluster config
65 cd67e337 Iustin Pop
                   -> Qlang.ItemType  -- ^ Query type
66 037762a9 Iustin Pop
                   -> [Either String Integer] -- ^ Requested names
67 037762a9 Iustin Pop
                                              -- (empty means all)
68 cd67e337 Iustin Pop
                   -> [String]        -- ^ Requested fields
69 cd67e337 Iustin Pop
                   -> Bool            -- ^ Whether to do sync queries or not
70 5183e8be Iustin Pop
                   -> IO (GenericResult GanetiException JSValue)
71 c4e0d065 Klaus Aehlig
handleClassicQuery _ _ _ _ True =
72 5183e8be Iustin Pop
  return . Bad $ OpPrereqError "Sync queries are not allowed" ECodeInval
73 c4e0d065 Klaus Aehlig
handleClassicQuery cfg qkind names fields _ = do
74 c4e0d065 Klaus Aehlig
  let flt = makeSimpleFilter (nameField qkind) names
75 cd67e337 Iustin Pop
  qr <- query cfg True (Qlang.Query qkind fields flt)
76 cd67e337 Iustin Pop
  return $ showJSON <$> (qr >>= queryCompat)
77 cd67e337 Iustin Pop
78 25b54de0 Iustin Pop
-- | Minimal wrapper to handle the missing config case.
79 5183e8be Iustin Pop
handleCallWrapper :: Result ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
80 25b54de0 Iustin Pop
handleCallWrapper (Bad msg) _ =
81 5183e8be Iustin Pop
  return . Bad . ConfigurationError $
82 5183e8be Iustin Pop
           "I do not have access to a valid configuration, cannot\
83 5183e8be Iustin Pop
           \ process queries: " ++ msg
84 25b54de0 Iustin Pop
handleCallWrapper (Ok config) op = handleCall config op
85 25b54de0 Iustin Pop
86 25b54de0 Iustin Pop
-- | Actual luxi operation handler.
87 5183e8be Iustin Pop
handleCall :: ConfigData -> LuxiOp -> IO (ErrorResult JSValue)
88 25b54de0 Iustin Pop
handleCall cdata QueryClusterInfo =
89 25b54de0 Iustin Pop
  let cluster = configCluster cdata
90 1c3231aa Thomas Thrainer
      master = QCluster.clusterMasterNodeName cdata
91 25b54de0 Iustin Pop
      hypervisors = clusterEnabledHypervisors cluster
92 966e1580 Helga Velroyen
      diskTemplates = clusterEnabledDiskTemplates cluster
93 72747d91 Iustin Pop
      def_hv = case hypervisors of
94 72747d91 Iustin Pop
                 x:_ -> showJSON x
95 72747d91 Iustin Pop
                 [] -> JSNull
96 25b54de0 Iustin Pop
      bits = show (bitSize (0::Int)) ++ "bits"
97 25b54de0 Iustin Pop
      arch_tuple = [bits, arch]
98 5b11f8db Iustin Pop
      obj = [ ("software_version", showJSON C.releaseVersion)
99 5b11f8db Iustin Pop
            , ("protocol_version", showJSON C.protocolVersion)
100 5b11f8db Iustin Pop
            , ("config_version", showJSON C.configVersion)
101 c87997d2 Jose A. Lopes
            , ("os_api_version", showJSON . maximum .
102 c87997d2 Jose A. Lopes
                                 Set.toList . ConstantUtils.unFrozenSet $
103 c87997d2 Jose A. Lopes
                                 C.osApiVersions)
104 5b11f8db Iustin Pop
            , ("export_version", showJSON C.exportVersion)
105 026f444f Thomas Thrainer
            , ("vcs_version", showJSON C.vcsVersion)
106 5b11f8db Iustin Pop
            , ("architecture", showJSON arch_tuple)
107 25b54de0 Iustin Pop
            , ("name", showJSON $ clusterClusterName cluster)
108 1c3231aa Thomas Thrainer
            , ("master", showJSON (case master of
109 1c3231aa Thomas Thrainer
                                     Ok name -> name
110 1c3231aa Thomas Thrainer
                                     _ -> undefined))
111 72747d91 Iustin Pop
            , ("default_hypervisor", def_hv)
112 5b11f8db Iustin Pop
            , ("enabled_hypervisors", showJSON hypervisors)
113 a2160e57 Iustin Pop
            , ("hvparams", showJSON $ clusterHvparams cluster)
114 a2160e57 Iustin Pop
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
115 25b54de0 Iustin Pop
            , ("beparams", showJSON $ clusterBeparams cluster)
116 25b54de0 Iustin Pop
            , ("osparams", showJSON $ clusterOsparams cluster)
117 25b54de0 Iustin Pop
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
118 25b54de0 Iustin Pop
            , ("nicparams", showJSON $ clusterNicparams cluster)
119 25b54de0 Iustin Pop
            , ("ndparams", showJSON $ clusterNdparams cluster)
120 a2160e57 Iustin Pop
            , ("diskparams", showJSON $ clusterDiskparams cluster)
121 25b54de0 Iustin Pop
            , ("candidate_pool_size",
122 25b54de0 Iustin Pop
               showJSON $ clusterCandidatePoolSize cluster)
123 25b54de0 Iustin Pop
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
124 25b54de0 Iustin Pop
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
125 25b54de0 Iustin Pop
            , ("use_external_mip_script",
126 25b54de0 Iustin Pop
               showJSON $ clusterUseExternalMipScript cluster)
127 64b0309a Dimitris Aragiorgis
            , ("volume_group_name",
128 64b0309a Dimitris Aragiorgis
               maybe JSNull showJSON (clusterVolumeGroupName cluster))
129 25b54de0 Iustin Pop
            , ("drbd_usermode_helper",
130 25b54de0 Iustin Pop
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
131 25b54de0 Iustin Pop
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
132 25b54de0 Iustin Pop
            , ("shared_file_storage_dir",
133 25b54de0 Iustin Pop
               showJSON $ clusterSharedFileStorageDir cluster)
134 25b54de0 Iustin Pop
            , ("maintain_node_health",
135 25b54de0 Iustin Pop
               showJSON $ clusterMaintainNodeHealth cluster)
136 25b54de0 Iustin Pop
            , ("ctime", showJSON $ clusterCtime cluster)
137 25b54de0 Iustin Pop
            , ("mtime", showJSON $ clusterMtime cluster)
138 25b54de0 Iustin Pop
            , ("uuid", showJSON $ clusterUuid cluster)
139 25b54de0 Iustin Pop
            , ("tags", showJSON $ clusterTags cluster)
140 25b54de0 Iustin Pop
            , ("uid_pool", showJSON $ clusterUidPool cluster)
141 25b54de0 Iustin Pop
            , ("default_iallocator",
142 25b54de0 Iustin Pop
               showJSON $ clusterDefaultIallocator cluster)
143 25b54de0 Iustin Pop
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
144 25b54de0 Iustin Pop
            , ("primary_ip_version",
145 25b54de0 Iustin Pop
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
146 7b9ceea7 Helga Velroyen
            , ("prealloc_wipe_disks",
147 7b9ceea7 Helga Velroyen
               showJSON $ clusterPreallocWipeDisks cluster)
148 7b9ceea7 Helga Velroyen
            , ("hidden_os", showJSON $ clusterHiddenOs cluster)
149 7b9ceea7 Helga Velroyen
            , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
150 966e1580 Helga Velroyen
            , ("enabled_disk_templates", showJSON diskTemplates)
151 25b54de0 Iustin Pop
            ]
152 25b54de0 Iustin Pop
153 1c3231aa Thomas Thrainer
  in case master of
154 1c3231aa Thomas Thrainer
    Ok _ -> return . Ok . J.makeObj $ obj
155 1c3231aa Thomas Thrainer
    Bad ex -> return $ Bad ex
156 25b54de0 Iustin Pop
157 6e94b75c Jose A. Lopes
handleCall cfg (QueryTags kind name) = do
158 f2374060 Iustin Pop
  let tags = case kind of
159 6e94b75c Jose A. Lopes
               TagKindCluster  -> Ok . clusterTags $ configCluster cfg
160 6e94b75c Jose A. Lopes
               TagKindGroup    -> groupTags <$> Config.getGroup    cfg name
161 6e94b75c Jose A. Lopes
               TagKindNode     -> nodeTags  <$> Config.getNode     cfg name
162 6e94b75c Jose A. Lopes
               TagKindInstance -> instTags  <$> Config.getInstance cfg name
163 a8633d70 Jose A. Lopes
               TagKindNetwork  -> Bad $ OpPrereqError
164 a8633d70 Jose A. Lopes
                                        "Network tag is not allowed"
165 a8633d70 Jose A. Lopes
                                        ECodeInval
166 6e94b75c Jose A. Lopes
  return (J.showJSON <$> tags)
167 f2374060 Iustin Pop
168 4cbe9bda Iustin Pop
handleCall cfg (Query qkind qfields qfilter) = do
169 fa2c927c Agata Murawska
  result <- query cfg True (Qlang.Query qkind qfields qfilter)
170 4cbe9bda Iustin Pop
  return $ J.showJSON <$> result
171 4cbe9bda Iustin Pop
172 518023a9 Iustin Pop
handleCall _ (QueryFields qkind qfields) = do
173 518023a9 Iustin Pop
  let result = queryFields (Qlang.QueryFields qkind qfields)
174 518023a9 Iustin Pop
  return $ J.showJSON <$> result
175 518023a9 Iustin Pop
176 cd67e337 Iustin Pop
handleCall cfg (QueryNodes names fields lock) =
177 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNode)
178 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
179 cd67e337 Iustin Pop
180 cd67e337 Iustin Pop
handleCall cfg (QueryGroups names fields lock) =
181 037762a9 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRGroup)
182 c4e0d065 Klaus Aehlig
    (map Left names) fields lock
183 cd67e337 Iustin Pop
184 a7e484c4 Iustin Pop
handleCall cfg (QueryJobs names fields) =
185 a7e484c4 Iustin Pop
  handleClassicQuery cfg (Qlang.ItemTypeLuxi Qlang.QRJob)
186 c4e0d065 Klaus Aehlig
    (map (Right . fromIntegral . fromJobId) names)  fields False
187 a7e484c4 Iustin Pop
188 795d035d Klaus Aehlig
handleCall cfg (QueryNetworks names fields lock) =
189 795d035d Klaus Aehlig
  handleClassicQuery cfg (Qlang.ItemTypeOpCode Qlang.QRNetwork)
190 795d035d Klaus Aehlig
    (map Left names) fields lock
191 795d035d Klaus Aehlig
192 25b54de0 Iustin Pop
handleCall _ op =
193 5183e8be Iustin Pop
  return . Bad $
194 5183e8be Iustin Pop
    GenericError ("Luxi call '" ++ strOfOp op ++ "' not implemented")
195 25b54de0 Iustin Pop
196 25b54de0 Iustin Pop
-- | Given a decoded luxi request, executes it and sends the luxi
197 25b54de0 Iustin Pop
-- response back to the client.
198 25b54de0 Iustin Pop
handleClientMsg :: Client -> ConfigReader -> LuxiOp -> IO Bool
199 25b54de0 Iustin Pop
handleClientMsg client creader args = do
200 25b54de0 Iustin Pop
  cfg <- creader
201 25b54de0 Iustin Pop
  logDebug $ "Request: " ++ show args
202 25b54de0 Iustin Pop
  call_result <- handleCallWrapper cfg args
203 25b54de0 Iustin Pop
  (!status, !rval) <-
204 25b54de0 Iustin Pop
    case call_result of
205 9abbb084 Iustin Pop
      Bad err -> do
206 3e0c2a24 Klaus Aehlig
        logWarning $ "Failed to execute request " ++ show args ++ ": "
207 3e0c2a24 Klaus Aehlig
                     ++ show err
208 5183e8be Iustin Pop
        return (False, showJSON err)
209 25b54de0 Iustin Pop
      Ok result -> do
210 f74b88fa Iustin Pop
        -- only log the first 2,000 chars of the result
211 f74b88fa Iustin Pop
        logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
212 3e0c2a24 Klaus Aehlig
        logInfo $ "Successfully handled " ++ strOfOp args
213 25b54de0 Iustin Pop
        return (True, result)
214 25b54de0 Iustin Pop
  sendMsg client $ buildResponse status rval
215 25b54de0 Iustin Pop
  return True
216 25b54de0 Iustin Pop
217 25b54de0 Iustin Pop
-- | Handles one iteration of the client protocol: receives message,
218 3e02cd3c Michele Tartara
-- checks it for validity and decodes it, returns response.
219 25b54de0 Iustin Pop
handleClient :: Client -> ConfigReader -> IO Bool
220 25b54de0 Iustin Pop
handleClient client creader = do
221 25b54de0 Iustin Pop
  !msg <- recvMsgExt client
222 385d4574 Klaus Aehlig
  logDebug $ "Received message: " ++ show msg
223 25b54de0 Iustin Pop
  case msg of
224 25b54de0 Iustin Pop
    RecvConnClosed -> logDebug "Connection closed" >> return False
225 25b54de0 Iustin Pop
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
226 25b54de0 Iustin Pop
                     return False
227 25b54de0 Iustin Pop
    RecvOk payload ->
228 25b54de0 Iustin Pop
      case validateCall payload >>= decodeCall of
229 9abbb084 Iustin Pop
        Bad err -> do
230 9abbb084 Iustin Pop
             let errmsg = "Failed to parse request: " ++ err
231 9abbb084 Iustin Pop
             logWarning errmsg
232 9abbb084 Iustin Pop
             sendMsg client $ buildResponse False (showJSON errmsg)
233 9abbb084 Iustin Pop
             return False
234 25b54de0 Iustin Pop
        Ok args -> handleClientMsg client creader args
235 25b54de0 Iustin Pop
236 25b54de0 Iustin Pop
-- | Main client loop: runs one loop of 'handleClient', and if that
237 cb44e3db Helga Velroyen
-- doesn't report a finished (closed) connection, restarts itself.
238 25b54de0 Iustin Pop
clientLoop :: Client -> ConfigReader -> IO ()
239 25b54de0 Iustin Pop
clientLoop client creader = do
240 25b54de0 Iustin Pop
  result <- handleClient client creader
241 25b54de0 Iustin Pop
  if result
242 25b54de0 Iustin Pop
    then clientLoop client creader
243 25b54de0 Iustin Pop
    else closeClient client
244 25b54de0 Iustin Pop
245 670e954a Thomas Thrainer
-- | Main listener loop: accepts clients, forks an I/O thread to handle
246 670e954a Thomas Thrainer
-- that client.
247 670e954a Thomas Thrainer
listener :: ConfigReader -> S.Socket -> IO ()
248 670e954a Thomas Thrainer
listener creader socket = do
249 25b54de0 Iustin Pop
  client <- acceptClient socket
250 25b54de0 Iustin Pop
  _ <- forkIO $ clientLoop client creader
251 670e954a Thomas Thrainer
  return ()
252 25b54de0 Iustin Pop
253 670e954a Thomas Thrainer
-- | Type alias for prepMain results
254 670e954a Thomas Thrainer
type PrepResult = (FilePath, S.Socket, IORef (Result ConfigData))
255 25b54de0 Iustin Pop
256 3695a4e0 Thomas Thrainer
-- | Check function for luxid.
257 670e954a Thomas Thrainer
checkMain :: CheckFn ()
258 670e954a Thomas Thrainer
checkMain _ = return $ Right ()
259 670e954a Thomas Thrainer
260 3695a4e0 Thomas Thrainer
-- | Prepare function for luxid.
261 670e954a Thomas Thrainer
prepMain :: PrepFn () PrepResult
262 670e954a Thomas Thrainer
prepMain _ _ = do
263 670e954a Thomas Thrainer
  socket_path <- Path.defaultQuerySocket
264 0d0ac025 Iustin Pop
  cleanupSocket socket_path
265 73b16ca1 Iustin Pop
  s <- describeError "binding to the Luxi socket"
266 e455a3e8 Michele Tartara
         Nothing (Just socket_path) $ getServer True socket_path
267 670e954a Thomas Thrainer
  cref <- newIORef (Bad "Configuration not yet loaded")
268 670e954a Thomas Thrainer
  return (socket_path, s, cref)
269 670e954a Thomas Thrainer
270 670e954a Thomas Thrainer
-- | Main function.
271 670e954a Thomas Thrainer
main :: MainFn () PrepResult
272 670e954a Thomas Thrainer
main _ _ (socket_path, server, cref) = do
273 670e954a Thomas Thrainer
  initConfigReader id cref
274 670e954a Thomas Thrainer
  let creader = readIORef cref
275 4c3f55b8 Iustin Pop
276 4c3f55b8 Iustin Pop
  finally
277 670e954a Thomas Thrainer
    (forever $ listener creader server)
278 4c3f55b8 Iustin Pop
    (closeServer socket_path server)