Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ 88772d17

History | View | Annotate | Download (12.6 kB)

1 046fe3f5 Iustin Pop
{-| Implementation of the Ganeti Query2 node queries.
2 046fe3f5 Iustin Pop
3 046fe3f5 Iustin Pop
 -}
4 046fe3f5 Iustin Pop
5 046fe3f5 Iustin Pop
{-
6 046fe3f5 Iustin Pop
7 36162faf Iustin Pop
Copyright (C) 2012, 2013 Google Inc.
8 046fe3f5 Iustin Pop
9 046fe3f5 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 046fe3f5 Iustin Pop
it under the terms of the GNU General Public License as published by
11 046fe3f5 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 046fe3f5 Iustin Pop
(at your option) any later version.
13 046fe3f5 Iustin Pop
14 046fe3f5 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 046fe3f5 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 046fe3f5 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 046fe3f5 Iustin Pop
General Public License for more details.
18 046fe3f5 Iustin Pop
19 046fe3f5 Iustin Pop
You should have received a copy of the GNU General Public License
20 046fe3f5 Iustin Pop
along with this program; if not, write to the Free Software
21 046fe3f5 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 046fe3f5 Iustin Pop
02110-1301, USA.
23 046fe3f5 Iustin Pop
24 046fe3f5 Iustin Pop
-}
25 046fe3f5 Iustin Pop
26 046fe3f5 Iustin Pop
module Ganeti.Query.Node
27 36162faf Iustin Pop
  ( Runtime
28 36162faf Iustin Pop
  , fieldsMap
29 36162faf Iustin Pop
  , collectLiveData
30 046fe3f5 Iustin Pop
  ) where
31 046fe3f5 Iustin Pop
32 046fe3f5 Iustin Pop
import Control.Applicative
33 046fe3f5 Iustin Pop
import Data.List
34 64b0309a Dimitris Aragiorgis
import Data.Maybe
35 046fe3f5 Iustin Pop
import qualified Data.Map as Map
36 cca4e6fe Agata Murawska
import qualified Text.JSON as J
37 046fe3f5 Iustin Pop
38 046fe3f5 Iustin Pop
import Ganeti.Config
39 212b66c3 Helga Velroyen
import Ganeti.Common
40 046fe3f5 Iustin Pop
import Ganeti.Objects
41 cca4e6fe Agata Murawska
import Ganeti.JSON
42 7f0fd838 Agata Murawska
import Ganeti.Rpc
43 030ab01a Helga Velroyen
import Ganeti.Types
44 4cab6703 Iustin Pop
import Ganeti.Query.Language
45 046fe3f5 Iustin Pop
import Ganeti.Query.Common
46 046fe3f5 Iustin Pop
import Ganeti.Query.Types
47 3dda8127 Helga Velroyen
import Ganeti.Storage.Utils
48 c81b97f2 Iustin Pop
import Ganeti.Utils (niceSort)
49 046fe3f5 Iustin Pop
50 36162faf Iustin Pop
-- | Runtime is the resulting type for NodeInfo call.
51 36162faf Iustin Pop
type Runtime = Either RpcError RpcResultNodeInfo
52 046fe3f5 Iustin Pop
53 cca4e6fe Agata Murawska
-- | List of node live fields.
54 046fe3f5 Iustin Pop
nodeLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
55 046fe3f5 Iustin Pop
nodeLiveFieldsDefs =
56 046fe3f5 Iustin Pop
  [ ("bootid", "BootID", QFTText, "bootid",
57 046fe3f5 Iustin Pop
     "Random UUID renewed for each system reboot, can be used\
58 046fe3f5 Iustin Pop
     \ for detecting reboots by tracking changes")
59 046fe3f5 Iustin Pop
  , ("cnodes", "CNodes", QFTNumber, "cpu_nodes",
60 046fe3f5 Iustin Pop
     "Number of NUMA domains on node (if exported by hypervisor)")
61 f43c898d Bernardo Dal Seno
  , ("cnos", "CNOs", QFTNumber, "cpu_dom0",
62 f43c898d Bernardo Dal Seno
     "Number of logical processors used by the node OS (dom0 for Xen)")
63 046fe3f5 Iustin Pop
  , ("csockets", "CSockets", QFTNumber, "cpu_sockets",
64 046fe3f5 Iustin Pop
     "Number of physical CPU sockets (if exported by hypervisor)")
65 046fe3f5 Iustin Pop
  , ("ctotal", "CTotal", QFTNumber, "cpu_total",
66 046fe3f5 Iustin Pop
     "Number of logical processors")
67 32389d91 Helga Velroyen
  , ("dfree", "DFree", QFTUnit, "storage_free",
68 32389d91 Helga Velroyen
     "Available storage space on storage unit")
69 32389d91 Helga Velroyen
  , ("dtotal", "DTotal", QFTUnit, "storage_size",
70 32389d91 Helga Velroyen
     "Total storage space on storage unit for instance disk allocation")
71 06fb92cf Bernardo Dal Seno
  , ("spfree", "SpFree", QFTNumber, "spindles_free",
72 06fb92cf Bernardo Dal Seno
     "Available spindles in volume group (exclusive storage only)")
73 06fb92cf Bernardo Dal Seno
  , ("sptotal", "SpTotal", QFTNumber, "spindles_total",
74 06fb92cf Bernardo Dal Seno
     "Total spindles in volume group (exclusive storage only)")
75 046fe3f5 Iustin Pop
  , ("mfree", "MFree", QFTUnit, "memory_free",
76 046fe3f5 Iustin Pop
     "Memory available for instance allocations")
77 046fe3f5 Iustin Pop
  , ("mnode", "MNode", QFTUnit, "memory_dom0",
78 046fe3f5 Iustin Pop
     "Amount of memory used by node (dom0 for Xen)")
79 046fe3f5 Iustin Pop
  , ("mtotal", "MTotal", QFTUnit, "memory_total",
80 046fe3f5 Iustin Pop
     "Total amount of memory of physical machine")
81 046fe3f5 Iustin Pop
  ]
82 046fe3f5 Iustin Pop
83 e78a8c0b Helga Velroyen
-- | Helper function to extract an attribute from a maybe StorageType
84 e78a8c0b Helga Velroyen
getAttrFromStorageInfo :: (J.JSON a) => (StorageInfo -> Maybe a)
85 e78a8c0b Helga Velroyen
                       -> Maybe StorageInfo -> J.JSValue
86 e78a8c0b Helga Velroyen
getAttrFromStorageInfo attr_fn (Just info) =
87 e78a8c0b Helga Velroyen
  case attr_fn info of
88 e78a8c0b Helga Velroyen
    Just val -> J.showJSON val
89 e78a8c0b Helga Velroyen
    Nothing -> J.JSNull
90 e78a8c0b Helga Velroyen
getAttrFromStorageInfo _ Nothing = J.JSNull
91 e78a8c0b Helga Velroyen
92 e78a8c0b Helga Velroyen
-- | Check whether the given storage info fits to the given storage type
93 e78a8c0b Helga Velroyen
isStorageInfoOfType :: StorageType -> StorageInfo -> Bool
94 e78a8c0b Helga Velroyen
isStorageInfoOfType stype sinfo = storageInfoType sinfo ==
95 e78a8c0b Helga Velroyen
    storageTypeToRaw stype
96 e78a8c0b Helga Velroyen
97 e78a8c0b Helga Velroyen
-- | Get storage info for the default storage unit
98 e78a8c0b Helga Velroyen
getStorageInfoForDefault :: [StorageInfo] -> Maybe StorageInfo
99 e78a8c0b Helga Velroyen
getStorageInfoForDefault sinfos = listToMaybe $ filter
100 e78a8c0b Helga Velroyen
    (not . isStorageInfoOfType StorageLvmPv) sinfos
101 e78a8c0b Helga Velroyen
102 e78a8c0b Helga Velroyen
-- | Gets the storage info for a storage type
103 e78a8c0b Helga Velroyen
-- FIXME: This needs to be extended when storage pools are implemented,
104 e78a8c0b Helga Velroyen
-- because storage types are not necessarily unique then
105 e78a8c0b Helga Velroyen
getStorageInfoForType :: [StorageInfo] -> StorageType -> Maybe StorageInfo
106 e78a8c0b Helga Velroyen
getStorageInfoForType sinfos stype = listToMaybe $ filter
107 e78a8c0b Helga Velroyen
    (isStorageInfoOfType stype) sinfos
108 e78a8c0b Helga Velroyen
109 cca4e6fe Agata Murawska
-- | Map each name to a function that extracts that value from
110 cca4e6fe Agata Murawska
-- the RPC result.
111 edb3f937 Iustin Pop
nodeLiveFieldExtract :: FieldName -> RpcResultNodeInfo -> J.JSValue
112 cca4e6fe Agata Murawska
nodeLiveFieldExtract "bootid" res =
113 edb3f937 Iustin Pop
  J.showJSON $ rpcResNodeInfoBootId res
114 edb3f937 Iustin Pop
nodeLiveFieldExtract "cnodes" res =
115 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuNodes
116 f43c898d Bernardo Dal Seno
nodeLiveFieldExtract "cnos" res =
117 f43c898d Bernardo Dal Seno
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuDom0
118 edb3f937 Iustin Pop
nodeLiveFieldExtract "csockets" res =
119 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuSockets
120 edb3f937 Iustin Pop
nodeLiveFieldExtract "ctotal" res =
121 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuTotal
122 edb3f937 Iustin Pop
nodeLiveFieldExtract "dfree" res =
123 e78a8c0b Helga Velroyen
  getAttrFromStorageInfo storageInfoStorageFree (getStorageInfoForDefault
124 e78a8c0b Helga Velroyen
      (rpcResNodeInfoStorageInfo res))
125 edb3f937 Iustin Pop
nodeLiveFieldExtract "dtotal" res =
126 e78a8c0b Helga Velroyen
  getAttrFromStorageInfo storageInfoStorageSize (getStorageInfoForDefault
127 e78a8c0b Helga Velroyen
      (rpcResNodeInfoStorageInfo res))
128 06fb92cf Bernardo Dal Seno
nodeLiveFieldExtract "spfree" res =
129 e78a8c0b Helga Velroyen
  getAttrFromStorageInfo storageInfoStorageFree (getStorageInfoForType
130 e78a8c0b Helga Velroyen
      (rpcResNodeInfoStorageInfo res) StorageLvmPv)
131 06fb92cf Bernardo Dal Seno
nodeLiveFieldExtract "sptotal" res =
132 e78a8c0b Helga Velroyen
  getAttrFromStorageInfo storageInfoStorageSize (getStorageInfoForType
133 e78a8c0b Helga Velroyen
      (rpcResNodeInfoStorageInfo res) StorageLvmPv)
134 edb3f937 Iustin Pop
nodeLiveFieldExtract "mfree" res =
135 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryFree
136 edb3f937 Iustin Pop
nodeLiveFieldExtract "mnode" res =
137 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryDom0
138 edb3f937 Iustin Pop
nodeLiveFieldExtract "mtotal" res =
139 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryTotal
140 cca4e6fe Agata Murawska
nodeLiveFieldExtract _ _ = J.JSNull
141 cca4e6fe Agata Murawska
142 cca4e6fe Agata Murawska
-- | Helper for extracting field from RPC result.
143 36162faf Iustin Pop
nodeLiveRpcCall :: FieldName -> Runtime -> Node -> ResultEntry
144 cca4e6fe Agata Murawska
nodeLiveRpcCall fname (Right res) _ =
145 edb3f937 Iustin Pop
  case nodeLiveFieldExtract fname res of
146 edb3f937 Iustin Pop
    J.JSNull -> rsNoData
147 edb3f937 Iustin Pop
    x -> rsNormal x
148 cca4e6fe Agata Murawska
nodeLiveRpcCall _ (Left err) _ =
149 cca4e6fe Agata Murawska
    ResultEntry (rpcErrorToStatus err) Nothing
150 cca4e6fe Agata Murawska
151 046fe3f5 Iustin Pop
-- | Builder for node live fields.
152 046fe3f5 Iustin Pop
nodeLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
153 36162faf Iustin Pop
                     -> FieldData Node Runtime
154 046fe3f5 Iustin Pop
nodeLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
155 cca4e6fe Agata Murawska
  ( FieldDefinition fname ftitle ftype fdoc
156 f94a9680 Iustin Pop
  , FieldRuntime $ nodeLiveRpcCall fname
157 f94a9680 Iustin Pop
  , QffNormal)
158 046fe3f5 Iustin Pop
159 2412bdea Iustin Pop
-- | The docstring for the node role. Note that we use 'reverse' in
160 046fe3f5 Iustin Pop
-- order to keep the same order as Python.
161 046fe3f5 Iustin Pop
nodeRoleDoc :: String
162 046fe3f5 Iustin Pop
nodeRoleDoc =
163 046fe3f5 Iustin Pop
  "Node role; " ++
164 5b11f8db Iustin Pop
  intercalate ", "
165 5b11f8db Iustin Pop
   (map (\role ->
166 046fe3f5 Iustin Pop
          "\"" ++ nodeRoleToRaw role ++ "\" for " ++ roleDescription role)
167 046fe3f5 Iustin Pop
   (reverse [minBound..maxBound]))
168 046fe3f5 Iustin Pop
169 5227de56 Iustin Pop
-- | Get node powered status.
170 5227de56 Iustin Pop
getNodePower :: ConfigData -> Node -> ResultEntry
171 5227de56 Iustin Pop
getNodePower cfg node =
172 5227de56 Iustin Pop
  case getNodeNdParams cfg node of
173 5227de56 Iustin Pop
    Nothing -> rsNoData
174 5227de56 Iustin Pop
    Just ndp -> if null (ndpOobProgram ndp)
175 5227de56 Iustin Pop
                  then rsUnavail
176 5227de56 Iustin Pop
                  else rsNormal (nodePowered node)
177 5227de56 Iustin Pop
178 046fe3f5 Iustin Pop
-- | List of all node fields.
179 36162faf Iustin Pop
nodeFields :: FieldList Node Runtime
180 046fe3f5 Iustin Pop
nodeFields =
181 046fe3f5 Iustin Pop
  [ (FieldDefinition "drained" "Drained" QFTBool "Whether node is drained",
182 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeDrained), QffNormal)
183 046fe3f5 Iustin Pop
  , (FieldDefinition "master_candidate" "MasterC" QFTBool
184 046fe3f5 Iustin Pop
       "Whether node is a master candidate",
185 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeMasterCandidate), QffNormal)
186 046fe3f5 Iustin Pop
  , (FieldDefinition "master_capable" "MasterCapable" QFTBool
187 046fe3f5 Iustin Pop
       "Whether node can become a master candidate",
188 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeMasterCapable), QffNormal)
189 046fe3f5 Iustin Pop
  , (FieldDefinition "name" "Node" QFTText "Node name",
190 91c1a265 Iustin Pop
     FieldSimple (rsNormal . nodeName), QffHostname)
191 046fe3f5 Iustin Pop
  , (FieldDefinition "offline" "Offline" QFTBool
192 046fe3f5 Iustin Pop
       "Whether node is marked offline",
193 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeOffline), QffNormal)
194 046fe3f5 Iustin Pop
  , (FieldDefinition "vm_capable" "VMCapable" QFTBool
195 046fe3f5 Iustin Pop
       "Whether node can host instances",
196 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeVmCapable), QffNormal)
197 046fe3f5 Iustin Pop
  , (FieldDefinition "pip" "PrimaryIP" QFTText "Primary IP address",
198 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodePrimaryIp), QffNormal)
199 046fe3f5 Iustin Pop
  , (FieldDefinition "sip" "SecondaryIP" QFTText "Secondary IP address",
200 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeSecondaryIp), QffNormal)
201 046fe3f5 Iustin Pop
  , (FieldDefinition "master" "IsMaster" QFTBool "Whether node is master",
202 046fe3f5 Iustin Pop
     FieldConfig (\cfg node ->
203 ec81293c Helga Velroyen
                    rsNormal (nodeUuid node ==
204 f94a9680 Iustin Pop
                              clusterMasterNode (configCluster cfg))),
205 f94a9680 Iustin Pop
     QffNormal)
206 046fe3f5 Iustin Pop
  , (FieldDefinition "group" "Group" QFTText "Node group",
207 046fe3f5 Iustin Pop
     FieldConfig (\cfg node ->
208 a64cc96b Helga Velroyen
                    rsMaybeNoData (groupName <$> getGroupOfNode cfg node)),
209 f94a9680 Iustin Pop
     QffNormal)
210 046fe3f5 Iustin Pop
  , (FieldDefinition "group.uuid" "GroupUUID" QFTText "UUID of node group",
211 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeGroup), QffNormal)
212 046fe3f5 Iustin Pop
  ,  (FieldDefinition "ndparams" "NodeParameters" QFTOther
213 046fe3f5 Iustin Pop
        "Merged node parameters",
214 a64cc96b Helga Velroyen
      FieldConfig ((rsMaybeNoData .) . getNodeNdParams), QffNormal)
215 046fe3f5 Iustin Pop
  , (FieldDefinition "custom_ndparams" "CustomNodeParameters" QFTOther
216 046fe3f5 Iustin Pop
                       "Custom node parameters",
217 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeNdparams), QffNormal)
218 046fe3f5 Iustin Pop
  -- FIXME: the below could be generalised a bit, like in Python
219 046fe3f5 Iustin Pop
  , (FieldDefinition "pinst_cnt" "Pinst" QFTNumber
220 046fe3f5 Iustin Pop
       "Number of instances with this node as primary",
221 96e3dfa7 Helga Velroyen
     FieldConfig (\cfg -> rsNormal . getNumInstances fst cfg), QffNormal)
222 046fe3f5 Iustin Pop
  , (FieldDefinition "sinst_cnt" "Sinst" QFTNumber
223 046fe3f5 Iustin Pop
       "Number of instances with this node as secondary",
224 96e3dfa7 Helga Velroyen
     FieldConfig (\cfg -> rsNormal . getNumInstances snd cfg), QffNormal)
225 b9bdc10e Iustin Pop
  , (FieldDefinition "pinst_list" "PriInstances" QFTOther
226 046fe3f5 Iustin Pop
       "List of instances with this node as primary",
227 c81b97f2 Iustin Pop
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . fst .
228 da4a52a3 Thomas Thrainer
                          getNodeInstances cfg . nodeUuid), QffNormal)
229 b9bdc10e Iustin Pop
  , (FieldDefinition "sinst_list" "SecInstances" QFTOther
230 046fe3f5 Iustin Pop
       "List of instances with this node as secondary",
231 c81b97f2 Iustin Pop
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . snd .
232 da4a52a3 Thomas Thrainer
                          getNodeInstances cfg . nodeUuid), QffNormal)
233 046fe3f5 Iustin Pop
  , (FieldDefinition "role" "Role" QFTText nodeRoleDoc,
234 f94a9680 Iustin Pop
     FieldConfig ((rsNormal .) . getNodeRole), QffNormal)
235 046fe3f5 Iustin Pop
  , (FieldDefinition "powered" "Powered" QFTBool
236 046fe3f5 Iustin Pop
       "Whether node is thought to be powered on",
237 f94a9680 Iustin Pop
     FieldConfig getNodePower, QffNormal)
238 046fe3f5 Iustin Pop
  -- FIXME: the two fields below are incomplete in Python, part of the
239 046fe3f5 Iustin Pop
  -- non-implemented node resource model; they are declared just for
240 046fe3f5 Iustin Pop
  -- parity, but are not functional
241 046fe3f5 Iustin Pop
  , (FieldDefinition "hv_state" "HypervisorState" QFTOther "Hypervisor state",
242 82953e9a Iustin Pop
     FieldSimple (const rsUnavail), QffNormal)
243 046fe3f5 Iustin Pop
  , (FieldDefinition "disk_state" "DiskState" QFTOther "Disk state",
244 82953e9a Iustin Pop
     FieldSimple (const rsUnavail), QffNormal)
245 046fe3f5 Iustin Pop
  ] ++
246 046fe3f5 Iustin Pop
  map nodeLiveFieldBuilder nodeLiveFieldsDefs ++
247 046fe3f5 Iustin Pop
  map buildNdParamField allNDParamFields ++
248 046fe3f5 Iustin Pop
  timeStampFields ++
249 046fe3f5 Iustin Pop
  uuidFields "Node" ++
250 046fe3f5 Iustin Pop
  serialFields "Node" ++
251 046fe3f5 Iustin Pop
  tagsFields
252 046fe3f5 Iustin Pop
253 96e3dfa7 Helga Velroyen
-- | Helper function to retrieve the number of (primary or secondary) instances
254 96e3dfa7 Helga Velroyen
getNumInstances :: (([Instance], [Instance]) -> [Instance])
255 96e3dfa7 Helga Velroyen
                -> ConfigData -> Node -> Int
256 96e3dfa7 Helga Velroyen
getNumInstances get_fn cfg = length . get_fn . getNodeInstances cfg . nodeUuid
257 96e3dfa7 Helga Velroyen
258 046fe3f5 Iustin Pop
-- | The node fields map.
259 36162faf Iustin Pop
fieldsMap :: FieldMap Node Runtime
260 c92b4671 Klaus Aehlig
fieldsMap = fieldListToFieldMap nodeFields
261 1ba01ff7 Iustin Pop
262 212b66c3 Helga Velroyen
-- | Create an RPC result for a broken node
263 212b66c3 Helga Velroyen
rpcResultNodeBroken :: Node -> (Node, Runtime)
264 212b66c3 Helga Velroyen
rpcResultNodeBroken node = (node, Left (RpcResultError "Broken configuration"))
265 212b66c3 Helga Velroyen
266 e86c9deb Helga Velroyen
-- | Storage-related query fields
267 e86c9deb Helga Velroyen
storageFields :: [String]
268 e86c9deb Helga Velroyen
storageFields = ["dtotal", "dfree", "spfree", "sptotal"]
269 e86c9deb Helga Velroyen
270 e86c9deb Helga Velroyen
-- | Hypervisor-related query fields
271 e86c9deb Helga Velroyen
hypervisorFields :: [String]
272 e86c9deb Helga Velroyen
hypervisorFields = ["mnode", "mfree", "mtotal",
273 e86c9deb Helga Velroyen
                    "cnodes", "csockets", "cnos", "ctotal"]
274 e86c9deb Helga Velroyen
275 e86c9deb Helga Velroyen
-- | Check if it is required to include domain-specific entities (for example
276 e86c9deb Helga Velroyen
-- storage units for storage info, hypervisor specs for hypervisor info)
277 e86c9deb Helga Velroyen
-- in the node_info call
278 e86c9deb Helga Velroyen
queryDomainRequired :: -- domain-specific fields to look for (storage, hv)
279 e86c9deb Helga Velroyen
                      [String]
280 e86c9deb Helga Velroyen
                      -- list of requested fields
281 e86c9deb Helga Velroyen
                   -> [String]
282 e86c9deb Helga Velroyen
                   -> Bool
283 e86c9deb Helga Velroyen
queryDomainRequired domain_fields fields = any (`elem` fields) domain_fields
284 e86c9deb Helga Velroyen
285 1ba01ff7 Iustin Pop
-- | Collect live data from RPC query if enabled.
286 e86c9deb Helga Velroyen
collectLiveData :: Bool
287 e86c9deb Helga Velroyen
                -> ConfigData
288 e86c9deb Helga Velroyen
                -> [String]
289 e86c9deb Helga Velroyen
                -> [Node]
290 e86c9deb Helga Velroyen
                -> IO [(Node, Runtime)]
291 e86c9deb Helga Velroyen
collectLiveData False _ _ nodes =
292 1ba01ff7 Iustin Pop
  return $ zip nodes (repeat $ Left (RpcResultError "Live data disabled"))
293 e86c9deb Helga Velroyen
collectLiveData True cfg fields nodes = do
294 e86c9deb Helga Velroyen
  let hvs = [getDefaultHypervisorSpec cfg |
295 e86c9deb Helga Velroyen
             queryDomainRequired hypervisorFields fields]
296 212b66c3 Helga Velroyen
      good_nodes = nodesWithValidConfig cfg nodes
297 e86c9deb Helga Velroyen
      storage_units = if queryDomainRequired storageFields fields
298 e86c9deb Helga Velroyen
                        then getStorageUnitsOfNodes cfg good_nodes
299 e86c9deb Helga Velroyen
                        else Map.fromList
300 e86c9deb Helga Velroyen
                          (map (\n -> (nodeUuid n, [])) good_nodes)
301 212b66c3 Helga Velroyen
  rpcres <- executeRpcCall good_nodes (RpcCallNodeInfo storage_units hvs)
302 212b66c3 Helga Velroyen
  return $ fillUpList (fillPairFromMaybe rpcResultNodeBroken pickPairUnique)
303 212b66c3 Helga Velroyen
      nodes rpcres