Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Queryd.hs @ 0d0ac025

History | View | Annotate | Download (7.4 kB)

1
{-# LANGUAGE BangPatterns #-}
2

    
3
{-| Implementation of the Ganeti confd types.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2012 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.Queryd
29
  ( ConfigReader
30
  , runQueryD
31
  ) where
32

    
33
import Control.Applicative
34
import Control.Concurrent
35
import Control.Exception
36
import Data.Bits (bitSize)
37
import Data.Maybe
38
import qualified Network.Socket as S
39
import qualified Text.JSON as J
40
import Text.JSON (showJSON, JSValue(..))
41
import Text.JSON.Pretty (pp_value)
42
import System.Info (arch)
43

    
44
import qualified Ganeti.Constants as C
45
import Ganeti.Daemon
46
import Ganeti.Objects
47
import qualified Ganeti.Config as Config
48
import Ganeti.BasicTypes
49
import Ganeti.Logging
50
import Ganeti.Luxi
51

    
52

    
53
-- | A type for functions that can return the configuration when
54
-- executed.
55
type ConfigReader = IO (Result ConfigData)
56

    
57
-- | Minimal wrapper to handle the missing config case.
58
handleCallWrapper :: Result ConfigData -> LuxiOp -> IO (Result JSValue)
59
handleCallWrapper (Bad msg) _ =
60
  return . Bad $ "I do not have access to a valid configuration, cannot\
61
                 \ process queries: " ++ msg
62
handleCallWrapper (Ok config) op = handleCall config op
63

    
64
-- | Actual luxi operation handler.
65
handleCall :: ConfigData -> LuxiOp -> IO (Result JSValue)
66
handleCall cdata QueryClusterInfo =
67
  let cluster = configCluster cdata
68
      hypervisors = clusterEnabledHypervisors cluster
69
      bits = show (bitSize (0::Int)) ++ "bits"
70
      arch_tuple = [bits, arch]
71
      obj = [ ("software_version", showJSON $ C.releaseVersion)
72
            , ("protocol_version", showJSON $ C.protocolVersion)
73
            , ("config_version", showJSON $ C.configVersion)
74
            , ("os_api_version", showJSON $ maximum C.osApiVersions)
75
            , ("export_version", showJSON $ C.exportVersion)
76
            , ("architecture", showJSON $ arch_tuple)
77
            , ("name", showJSON $ clusterClusterName cluster)
78
            , ("master", showJSON $ clusterMasterNode cluster)
79
            , ("default_hypervisor", showJSON $ head hypervisors)
80
            , ("enabled_hypervisors", showJSON $ hypervisors)
81
            , ("hvparams", showJSON $ clusterHvparams cluster)
82
            , ("os_hvp", showJSON $ clusterOsHvp cluster)
83
            , ("beparams", showJSON $ clusterBeparams cluster)
84
            , ("osparams", showJSON $ clusterOsparams cluster)
85
            , ("ipolicy", showJSON $ clusterIpolicy cluster)
86
            , ("nicparams", showJSON $ clusterNicparams cluster)
87
            , ("ndparams", showJSON $ clusterNdparams cluster)
88
            , ("diskparams", showJSON $ clusterDiskparams cluster)
89
            , ("candidate_pool_size",
90
               showJSON $ clusterCandidatePoolSize cluster)
91
            , ("master_netdev",  showJSON $ clusterMasterNetdev cluster)
92
            , ("master_netmask", showJSON $ clusterMasterNetmask cluster)
93
            , ("use_external_mip_script",
94
               showJSON $ clusterUseExternalMipScript cluster)
95
            , ("volume_group_name", showJSON $clusterVolumeGroupName cluster)
96
            , ("drbd_usermode_helper",
97
               maybe JSNull showJSON (clusterDrbdUsermodeHelper cluster))
98
            , ("file_storage_dir", showJSON $ clusterFileStorageDir cluster)
99
            , ("shared_file_storage_dir",
100
               showJSON $ clusterSharedFileStorageDir cluster)
101
            , ("maintain_node_health",
102
               showJSON $ clusterMaintainNodeHealth cluster)
103
            , ("ctime", showJSON $ clusterCtime cluster)
104
            , ("mtime", showJSON $ clusterMtime cluster)
105
            , ("uuid", showJSON $ clusterUuid cluster)
106
            , ("tags", showJSON $ clusterTags cluster)
107
            , ("uid_pool", showJSON $ clusterUidPool cluster)
108
            , ("default_iallocator",
109
               showJSON $ clusterDefaultIallocator cluster)
110
            , ("reserved_lvs", showJSON $ clusterReservedLvs cluster)
111
            , ("primary_ip_version",
112
               showJSON . ipFamilyToVersion $ clusterPrimaryIpFamily cluster)
113
             , ("prealloc_wipe_disks",
114
                showJSON $ clusterPreallocWipeDisks cluster)
115
             , ("hidden_os", showJSON $ clusterHiddenOs cluster)
116
             , ("blacklisted_os", showJSON $ clusterBlacklistedOs cluster)
117
            ]
118

    
119
  in return . Ok . J.makeObj $ obj
120

    
121
handleCall cfg (QueryTags kind name) =
122
  let tags = case kind of
123
               TagCluster -> Ok . clusterTags $ configCluster cfg
124
               TagGroup -> groupTags <$> Config.getGroup cfg name
125
               TagNode -> nodeTags <$> Config.getNode cfg name
126
               TagInstance -> instTags <$> Config.getInstance cfg name
127
  in return (J.showJSON <$> tags)
128

    
129
handleCall _ op =
130
  return . Bad $ "Luxi call '" ++ strOfOp op ++ "' not implemented"
131

    
132

    
133
-- | Given a decoded luxi request, executes it and sends the luxi
134
-- response back to the client.
135
handleClientMsg :: Client -> ConfigReader -> LuxiOp -> IO Bool
136
handleClientMsg client creader args = do
137
  cfg <- creader
138
  logDebug $ "Request: " ++ show args
139
  call_result <- handleCallWrapper cfg args
140
  (!status, !rval) <-
141
    case call_result of
142
      Bad x -> do
143
        logWarning $ "Failed to execute request: " ++ x
144
        return (False, JSString $ J.toJSString x)
145
      Ok result -> do
146
        logDebug $ "Result " ++ show (pp_value result)
147
        return (True, result)
148
  sendMsg client $ buildResponse status rval
149
  return True
150

    
151
-- | Handles one iteration of the client protocol: receives message,
152
-- checks for validity and decods, returns response.
153
handleClient :: Client -> ConfigReader -> IO Bool
154
handleClient client creader = do
155
  !msg <- recvMsgExt client
156
  case msg of
157
    RecvConnClosed -> logDebug "Connection closed" >> return False
158
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
159
                     return False
160
    RecvOk payload ->
161
      case validateCall payload >>= decodeCall of
162
        Bad err -> logWarning ("Failed to parse request: " ++ err) >>
163
                   return False
164
        Ok args -> handleClientMsg client creader args
165

    
166
-- | Main client loop: runs one loop of 'handleClient', and if that
167
-- doesn't repot a finished (closed) connection, restarts itself.
168
clientLoop :: Client -> ConfigReader -> IO ()
169
clientLoop client creader = do
170
  result <- handleClient client creader
171
  if result
172
    then clientLoop client creader
173
    else closeClient client
174

    
175
-- | Main loop: accepts clients, forks an I/O thread to handle that
176
-- client, and then restarts.
177
mainLoop :: ConfigReader -> S.Socket -> IO ()
178
mainLoop creader socket = do
179
  client <- acceptClient socket
180
  _ <- forkIO $ clientLoop client creader
181
  mainLoop creader socket
182

    
183
-- | Main function that runs the query endpoint. This should be the
184
-- only one exposed from this module.
185
runQueryD :: Maybe FilePath -> ConfigReader -> IO ()
186
runQueryD fpath creader = do
187
  let socket_path = fromMaybe C.querySocket fpath
188
  cleanupSocket socket_path
189
  bracket
190
    (getServer socket_path)
191
    (closeServer socket_path)
192
    (mainLoop creader)