Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ f43c898d

History | View | Annotate | Download (10.9 kB)

1
{-| Implementation of the Ganeti Query2 node queries.
2

    
3
 -}
4

    
5
{-
6

    
7
Copyright (C) 2012, 2013 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.Query.Node
27
  ( Runtime
28
  , fieldsMap
29
  , collectLiveData
30
  ) where
31

    
32
import Control.Applicative
33
import Data.List
34
import Data.Maybe
35
import qualified Data.Map as Map
36
import qualified Text.JSON as J
37

    
38
import Ganeti.Config
39
import Ganeti.Objects
40
import Ganeti.JSON
41
import Ganeti.Rpc
42
import Ganeti.Types
43
import Ganeti.Query.Language
44
import Ganeti.Query.Common
45
import Ganeti.Query.Types
46
import Ganeti.Storage.Utils
47
import Ganeti.Utils (niceSort)
48

    
49
-- | Runtime is the resulting type for NodeInfo call.
50
type Runtime = Either RpcError RpcResultNodeInfo
51

    
52
-- | List of node live fields.
53
nodeLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
54
nodeLiveFieldsDefs =
55
  [ ("bootid", "BootID", QFTText, "bootid",
56
     "Random UUID renewed for each system reboot, can be used\
57
     \ for detecting reboots by tracking changes")
58
  , ("cnodes", "CNodes", QFTNumber, "cpu_nodes",
59
     "Number of NUMA domains on node (if exported by hypervisor)")
60
  , ("cnos", "CNOs", QFTNumber, "cpu_dom0",
61
     "Number of logical processors used by the node OS (dom0 for Xen)")
62
  , ("csockets", "CSockets", QFTNumber, "cpu_sockets",
63
     "Number of physical CPU sockets (if exported by hypervisor)")
64
  , ("ctotal", "CTotal", QFTNumber, "cpu_total",
65
     "Number of logical processors")
66
  , ("dfree", "DFree", QFTUnit, "storage_free",
67
     "Available storage space on storage unit")
68
  , ("dtotal", "DTotal", QFTUnit, "storage_size",
69
     "Total storage space on storage unit for instance disk allocation")
70
  , ("spfree", "SpFree", QFTNumber, "spindles_free",
71
     "Available spindles in volume group (exclusive storage only)")
72
  , ("sptotal", "SpTotal", QFTNumber, "spindles_total",
73
     "Total spindles in volume group (exclusive storage only)")
74
  , ("mfree", "MFree", QFTUnit, "memory_free",
75
     "Memory available for instance allocations")
76
  , ("mnode", "MNode", QFTUnit, "memory_dom0",
77
     "Amount of memory used by node (dom0 for Xen)")
78
  , ("mtotal", "MTotal", QFTUnit, "memory_total",
79
     "Total amount of memory of physical machine")
80
  ]
81

    
82
-- | Map each name to a function that extracts that value from
83
-- the RPC result.
84
nodeLiveFieldExtract :: FieldName -> RpcResultNodeInfo -> J.JSValue
85
nodeLiveFieldExtract "bootid" res =
86
  J.showJSON $ rpcResNodeInfoBootId res
87
nodeLiveFieldExtract "cnodes" res =
88
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuNodes
89
nodeLiveFieldExtract "cnos" res =
90
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuDom0
91
nodeLiveFieldExtract "csockets" res =
92
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuSockets
93
nodeLiveFieldExtract "ctotal" res =
94
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuTotal
95
nodeLiveFieldExtract "dfree" res =
96
  getMaybeJsonHead (rpcResNodeInfoStorageInfo res) storageInfoStorageFree
97
nodeLiveFieldExtract "dtotal" res =
98
  getMaybeJsonHead (rpcResNodeInfoStorageInfo res) storageInfoStorageSize
99
nodeLiveFieldExtract "spfree" res =
100
  getMaybeJsonElem (rpcResNodeInfoStorageInfo res) 1 storageInfoStorageFree
101
nodeLiveFieldExtract "sptotal" res =
102
  getMaybeJsonElem (rpcResNodeInfoStorageInfo res) 1 storageInfoStorageSize
103
nodeLiveFieldExtract "mfree" res =
104
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryFree
105
nodeLiveFieldExtract "mnode" res =
106
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryDom0
107
nodeLiveFieldExtract "mtotal" res =
108
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryTotal
109
nodeLiveFieldExtract _ _ = J.JSNull
110

    
111
-- | Helper for extracting field from RPC result.
112
nodeLiveRpcCall :: FieldName -> Runtime -> Node -> ResultEntry
113
nodeLiveRpcCall fname (Right res) _ =
114
  case nodeLiveFieldExtract fname res of
115
    J.JSNull -> rsNoData
116
    x -> rsNormal x
117
nodeLiveRpcCall _ (Left err) _ =
118
    ResultEntry (rpcErrorToStatus err) Nothing
119

    
120
-- | Builder for node live fields.
121
nodeLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
122
                     -> FieldData Node Runtime
123
nodeLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
124
  ( FieldDefinition fname ftitle ftype fdoc
125
  , FieldRuntime $ nodeLiveRpcCall fname
126
  , QffNormal)
127

    
128
-- | The docstring for the node role. Note that we use 'reverse' in
129
-- order to keep the same order as Python.
130
nodeRoleDoc :: String
131
nodeRoleDoc =
132
  "Node role; " ++
133
  intercalate ", "
134
   (map (\role ->
135
          "\"" ++ nodeRoleToRaw role ++ "\" for " ++ roleDescription role)
136
   (reverse [minBound..maxBound]))
137

    
138
-- | Get node powered status.
139
getNodePower :: ConfigData -> Node -> ResultEntry
140
getNodePower cfg node =
141
  case getNodeNdParams cfg node of
142
    Nothing -> rsNoData
143
    Just ndp -> if null (ndpOobProgram ndp)
144
                  then rsUnavail
145
                  else rsNormal (nodePowered node)
146

    
147
-- | List of all node fields.
148
nodeFields :: FieldList Node Runtime
149
nodeFields =
150
  [ (FieldDefinition "drained" "Drained" QFTBool "Whether node is drained",
151
     FieldSimple (rsNormal . nodeDrained), QffNormal)
152
  , (FieldDefinition "master_candidate" "MasterC" QFTBool
153
       "Whether node is a master candidate",
154
     FieldSimple (rsNormal . nodeMasterCandidate), QffNormal)
155
  , (FieldDefinition "master_capable" "MasterCapable" QFTBool
156
       "Whether node can become a master candidate",
157
     FieldSimple (rsNormal . nodeMasterCapable), QffNormal)
158
  , (FieldDefinition "name" "Node" QFTText "Node name",
159
     FieldSimple (rsNormal . nodeName), QffHostname)
160
  , (FieldDefinition "offline" "Offline" QFTBool
161
       "Whether node is marked offline",
162
     FieldSimple (rsNormal . nodeOffline), QffNormal)
163
  , (FieldDefinition "vm_capable" "VMCapable" QFTBool
164
       "Whether node can host instances",
165
     FieldSimple (rsNormal . nodeVmCapable), QffNormal)
166
  , (FieldDefinition "pip" "PrimaryIP" QFTText "Primary IP address",
167
     FieldSimple (rsNormal . nodePrimaryIp), QffNormal)
168
  , (FieldDefinition "sip" "SecondaryIP" QFTText "Secondary IP address",
169
     FieldSimple (rsNormal . nodeSecondaryIp), QffNormal)
170
  , (FieldDefinition "master" "IsMaster" QFTBool "Whether node is master",
171
     FieldConfig (\cfg node ->
172
                    rsNormal (nodeName node ==
173
                              clusterMasterNode (configCluster cfg))),
174
     QffNormal)
175
  , (FieldDefinition "group" "Group" QFTText "Node group",
176
     FieldConfig (\cfg node ->
177
                    rsMaybeNoData (groupName <$> getGroupOfNode cfg node)),
178
     QffNormal)
179
  , (FieldDefinition "group.uuid" "GroupUUID" QFTText "UUID of node group",
180
     FieldSimple (rsNormal . nodeGroup), QffNormal)
181
  ,  (FieldDefinition "ndparams" "NodeParameters" QFTOther
182
        "Merged node parameters",
183
      FieldConfig ((rsMaybeNoData .) . getNodeNdParams), QffNormal)
184
  , (FieldDefinition "custom_ndparams" "CustomNodeParameters" QFTOther
185
                       "Custom node parameters",
186
     FieldSimple (rsNormal . nodeNdparams), QffNormal)
187
  -- FIXME: the below could be generalised a bit, like in Python
188
  , (FieldDefinition "pinst_cnt" "Pinst" QFTNumber
189
       "Number of instances with this node as primary",
190
     FieldConfig (\cfg ->
191
                    rsNormal . length . fst . getNodeInstances cfg . nodeUuid),
192
     QffNormal)
193
  , (FieldDefinition "sinst_cnt" "Sinst" QFTNumber
194
       "Number of instances with this node as secondary",
195
     FieldConfig (\cfg ->
196
                    rsNormal . length . snd . getNodeInstances cfg . nodeUuid),
197
     QffNormal)
198
  , (FieldDefinition "pinst_list" "PriInstances" QFTOther
199
       "List of instances with this node as primary",
200
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . fst .
201
                          getNodeInstances cfg . nodeUuid), QffNormal)
202
  , (FieldDefinition "sinst_list" "SecInstances" QFTOther
203
       "List of instances with this node as secondary",
204
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . snd .
205
                          getNodeInstances cfg . nodeUuid), QffNormal)
206
  , (FieldDefinition "role" "Role" QFTText nodeRoleDoc,
207
     FieldConfig ((rsNormal .) . getNodeRole), QffNormal)
208
  , (FieldDefinition "powered" "Powered" QFTBool
209
       "Whether node is thought to be powered on",
210
     FieldConfig getNodePower, QffNormal)
211
  -- FIXME: the two fields below are incomplete in Python, part of the
212
  -- non-implemented node resource model; they are declared just for
213
  -- parity, but are not functional
214
  , (FieldDefinition "hv_state" "HypervisorState" QFTOther "Hypervisor state",
215
     FieldSimple (const rsUnavail), QffNormal)
216
  , (FieldDefinition "disk_state" "DiskState" QFTOther "Disk state",
217
     FieldSimple (const rsUnavail), QffNormal)
218
  ] ++
219
  map nodeLiveFieldBuilder nodeLiveFieldsDefs ++
220
  map buildNdParamField allNDParamFields ++
221
  timeStampFields ++
222
  uuidFields "Node" ++
223
  serialFields "Node" ++
224
  tagsFields
225

    
226
-- | The node fields map.
227
fieldsMap :: FieldMap Node Runtime
228
fieldsMap =
229
  Map.fromList $ map (\v@(f, _, _) -> (fdefName f, v)) nodeFields
230

    
231
-- | Collect live data from RPC query if enabled.
232
--
233
-- FIXME: Check which fields we actually need and possibly send empty
234
-- hvs\/vgs if no info from hypervisor\/volume group respectively is
235
-- required
236
collectLiveData:: Bool -> ConfigData -> [Node] -> IO [(Node, Runtime)]
237
collectLiveData False _ nodes =
238
  return $ zip nodes (repeat $ Left (RpcResultError "Live data disabled"))
239
collectLiveData True cfg nodes = do
240
  let storage_units = getClusterStorageUnits cfg
241
      hvs = [getDefaultHypervisorSpec cfg]
242
      step n (bn, gn, em) =
243
        let ndp' = getNodeNdParams cfg n
244
        in case ndp' of
245
             Just ndp -> (bn, n : gn,
246
                          (nodeName n, ndpExclusiveStorage ndp) : em)
247
             Nothing -> (n : bn, gn, em)
248
      (bnodes, gnodes, emap) = foldr step ([], [], []) nodes
249
  rpcres <- executeRpcCall gnodes (RpcCallNodeInfo storage_units hvs
250
    (Map.fromList emap))
251
  -- FIXME: The order of nodes in the result could be different from the input
252
  return $ zip bnodes (repeat $ Left (RpcResultError "Broken configuration"))
253
           ++ rpcres
254

    
255
-- | Looks up the default hypervisor and it's hvparams
256
getDefaultHypervisorSpec :: ConfigData -> (Hypervisor, HvParams)
257
getDefaultHypervisorSpec cfg = (hv, getHvParamsFromCluster cfg hv)
258
  where hv = getDefaultHypervisor cfg
259

    
260
-- | Looks up the cluster's hvparams of the given hypervisor
261
getHvParamsFromCluster :: ConfigData -> Hypervisor -> HvParams
262
getHvParamsFromCluster cfg hv =
263
  fromMaybe (GenericContainer (Map.fromList []))
264
    (Map.lookup (hypervisorToRaw hv)
265
       (fromContainer (clusterHvparams (configCluster cfg))))