Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ 32389d91

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 qualified Ganeti.Types as T
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
  , ("csockets", "CSockets", QFTNumber, "cpu_sockets",
61
     "Number of physical CPU sockets (if exported by hypervisor)")
62
  , ("ctotal", "CTotal", QFTNumber, "cpu_total",
63
     "Number of logical processors")
64
  , ("dfree", "DFree", QFTUnit, "storage_free",
65
     "Available storage space on storage unit")
66
  , ("dtotal", "DTotal", QFTUnit, "storage_size",
67
     "Total storage space on storage unit for instance disk allocation")
68
  , ("spfree", "SpFree", QFTNumber, "spindles_free",
69
     "Available spindles in volume group (exclusive storage only)")
70
  , ("sptotal", "SpTotal", QFTNumber, "spindles_total",
71
     "Total spindles in volume group (exclusive storage only)")
72
  , ("mfree", "MFree", QFTUnit, "memory_free",
73
     "Memory available for instance allocations")
74
  , ("mnode", "MNode", QFTUnit, "memory_dom0",
75
     "Amount of memory used by node (dom0 for Xen)")
76
  , ("mtotal", "MTotal", QFTUnit, "memory_total",
77
     "Total amount of memory of physical machine")
78
  ]
79

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

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

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

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

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

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

    
222
-- | The node fields map.
223
fieldsMap :: FieldMap Node Runtime
224
fieldsMap =
225
  Map.fromList $ map (\v@(f, _, _) -> (fdefName f, v)) nodeFields
226

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

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

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