Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ 68af861c

History | View | Annotate | Download (10.8 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 046fe3f5 Iustin Pop
import Ganeti.Objects
40 cca4e6fe Agata Murawska
import Ganeti.JSON
41 7f0fd838 Agata Murawska
import Ganeti.Rpc
42 030ab01a Helga Velroyen
import Ganeti.Types
43 4cab6703 Iustin Pop
import Ganeti.Query.Language
44 046fe3f5 Iustin Pop
import Ganeti.Query.Common
45 046fe3f5 Iustin Pop
import Ganeti.Query.Types
46 4b92e992 Helga Velroyen
import qualified Ganeti.Types as T
47 c81b97f2 Iustin Pop
import Ganeti.Utils (niceSort)
48 046fe3f5 Iustin Pop
49 36162faf Iustin Pop
-- | Runtime is the resulting type for NodeInfo call.
50 36162faf Iustin Pop
type Runtime = Either RpcError RpcResultNodeInfo
51 046fe3f5 Iustin Pop
52 cca4e6fe Agata Murawska
-- | List of node live fields.
53 046fe3f5 Iustin Pop
nodeLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
54 046fe3f5 Iustin Pop
nodeLiveFieldsDefs =
55 046fe3f5 Iustin Pop
  [ ("bootid", "BootID", QFTText, "bootid",
56 046fe3f5 Iustin Pop
     "Random UUID renewed for each system reboot, can be used\
57 046fe3f5 Iustin Pop
     \ for detecting reboots by tracking changes")
58 046fe3f5 Iustin Pop
  , ("cnodes", "CNodes", QFTNumber, "cpu_nodes",
59 046fe3f5 Iustin Pop
     "Number of NUMA domains on node (if exported by hypervisor)")
60 046fe3f5 Iustin Pop
  , ("csockets", "CSockets", QFTNumber, "cpu_sockets",
61 046fe3f5 Iustin Pop
     "Number of physical CPU sockets (if exported by hypervisor)")
62 046fe3f5 Iustin Pop
  , ("ctotal", "CTotal", QFTNumber, "cpu_total",
63 046fe3f5 Iustin Pop
     "Number of logical processors")
64 046fe3f5 Iustin Pop
  , ("dfree", "DFree", QFTUnit, "vg_free",
65 046fe3f5 Iustin Pop
     "Available disk space in volume group")
66 046fe3f5 Iustin Pop
  , ("dtotal", "DTotal", QFTUnit, "vg_size",
67 046fe3f5 Iustin Pop
     "Total disk space in volume group used for instance disk allocation")
68 06fb92cf Bernardo Dal Seno
  , ("spfree", "SpFree", QFTNumber, "spindles_free",
69 06fb92cf Bernardo Dal Seno
     "Available spindles in volume group (exclusive storage only)")
70 06fb92cf Bernardo Dal Seno
  , ("sptotal", "SpTotal", QFTNumber, "spindles_total",
71 06fb92cf Bernardo Dal Seno
     "Total spindles in volume group (exclusive storage only)")
72 046fe3f5 Iustin Pop
  , ("mfree", "MFree", QFTUnit, "memory_free",
73 046fe3f5 Iustin Pop
     "Memory available for instance allocations")
74 046fe3f5 Iustin Pop
  , ("mnode", "MNode", QFTUnit, "memory_dom0",
75 046fe3f5 Iustin Pop
     "Amount of memory used by node (dom0 for Xen)")
76 046fe3f5 Iustin Pop
  , ("mtotal", "MTotal", QFTUnit, "memory_total",
77 046fe3f5 Iustin Pop
     "Total amount of memory of physical machine")
78 046fe3f5 Iustin Pop
  ]
79 046fe3f5 Iustin Pop
80 cca4e6fe Agata Murawska
-- | Map each name to a function that extracts that value from
81 cca4e6fe Agata Murawska
-- the RPC result.
82 edb3f937 Iustin Pop
nodeLiveFieldExtract :: FieldName -> RpcResultNodeInfo -> J.JSValue
83 cca4e6fe Agata Murawska
nodeLiveFieldExtract "bootid" res =
84 edb3f937 Iustin Pop
  J.showJSON $ rpcResNodeInfoBootId res
85 edb3f937 Iustin Pop
nodeLiveFieldExtract "cnodes" res =
86 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuNodes
87 edb3f937 Iustin Pop
nodeLiveFieldExtract "csockets" res =
88 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuSockets
89 edb3f937 Iustin Pop
nodeLiveFieldExtract "ctotal" res =
90 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoCpuTotal
91 edb3f937 Iustin Pop
nodeLiveFieldExtract "dfree" res =
92 318853ab Iustin Pop
  getMaybeJsonHead (rpcResNodeInfoVgInfo res) vgInfoVgFree
93 edb3f937 Iustin Pop
nodeLiveFieldExtract "dtotal" res =
94 318853ab Iustin Pop
  getMaybeJsonHead (rpcResNodeInfoVgInfo res) vgInfoVgSize
95 06fb92cf Bernardo Dal Seno
nodeLiveFieldExtract "spfree" res =
96 06fb92cf Bernardo Dal Seno
  getMaybeJsonElem (rpcResNodeInfoVgInfo res) 1 vgInfoVgFree
97 06fb92cf Bernardo Dal Seno
nodeLiveFieldExtract "sptotal" res =
98 06fb92cf Bernardo Dal Seno
  getMaybeJsonElem (rpcResNodeInfoVgInfo res) 1 vgInfoVgSize
99 edb3f937 Iustin Pop
nodeLiveFieldExtract "mfree" res =
100 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryFree
101 edb3f937 Iustin Pop
nodeLiveFieldExtract "mnode" res =
102 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryDom0
103 edb3f937 Iustin Pop
nodeLiveFieldExtract "mtotal" res =
104 edb3f937 Iustin Pop
  jsonHead (rpcResNodeInfoHvInfo res) hvInfoMemoryTotal
105 cca4e6fe Agata Murawska
nodeLiveFieldExtract _ _ = J.JSNull
106 cca4e6fe Agata Murawska
107 cca4e6fe Agata Murawska
-- | Helper for extracting field from RPC result.
108 36162faf Iustin Pop
nodeLiveRpcCall :: FieldName -> Runtime -> Node -> ResultEntry
109 cca4e6fe Agata Murawska
nodeLiveRpcCall fname (Right res) _ =
110 edb3f937 Iustin Pop
  case nodeLiveFieldExtract fname res of
111 edb3f937 Iustin Pop
    J.JSNull -> rsNoData
112 edb3f937 Iustin Pop
    x -> rsNormal x
113 cca4e6fe Agata Murawska
nodeLiveRpcCall _ (Left err) _ =
114 cca4e6fe Agata Murawska
    ResultEntry (rpcErrorToStatus err) Nothing
115 cca4e6fe Agata Murawska
116 046fe3f5 Iustin Pop
-- | Builder for node live fields.
117 046fe3f5 Iustin Pop
nodeLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
118 36162faf Iustin Pop
                     -> FieldData Node Runtime
119 046fe3f5 Iustin Pop
nodeLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
120 cca4e6fe Agata Murawska
  ( FieldDefinition fname ftitle ftype fdoc
121 f94a9680 Iustin Pop
  , FieldRuntime $ nodeLiveRpcCall fname
122 f94a9680 Iustin Pop
  , QffNormal)
123 046fe3f5 Iustin Pop
124 2412bdea Iustin Pop
-- | The docstring for the node role. Note that we use 'reverse' in
125 046fe3f5 Iustin Pop
-- order to keep the same order as Python.
126 046fe3f5 Iustin Pop
nodeRoleDoc :: String
127 046fe3f5 Iustin Pop
nodeRoleDoc =
128 046fe3f5 Iustin Pop
  "Node role; " ++
129 5b11f8db Iustin Pop
  intercalate ", "
130 5b11f8db Iustin Pop
   (map (\role ->
131 046fe3f5 Iustin Pop
          "\"" ++ nodeRoleToRaw role ++ "\" for " ++ roleDescription role)
132 046fe3f5 Iustin Pop
   (reverse [minBound..maxBound]))
133 046fe3f5 Iustin Pop
134 5227de56 Iustin Pop
-- | Get node powered status.
135 5227de56 Iustin Pop
getNodePower :: ConfigData -> Node -> ResultEntry
136 5227de56 Iustin Pop
getNodePower cfg node =
137 5227de56 Iustin Pop
  case getNodeNdParams cfg node of
138 5227de56 Iustin Pop
    Nothing -> rsNoData
139 5227de56 Iustin Pop
    Just ndp -> if null (ndpOobProgram ndp)
140 5227de56 Iustin Pop
                  then rsUnavail
141 5227de56 Iustin Pop
                  else rsNormal (nodePowered node)
142 5227de56 Iustin Pop
143 046fe3f5 Iustin Pop
-- | List of all node fields.
144 36162faf Iustin Pop
nodeFields :: FieldList Node Runtime
145 046fe3f5 Iustin Pop
nodeFields =
146 046fe3f5 Iustin Pop
  [ (FieldDefinition "drained" "Drained" QFTBool "Whether node is drained",
147 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeDrained), QffNormal)
148 046fe3f5 Iustin Pop
  , (FieldDefinition "master_candidate" "MasterC" QFTBool
149 046fe3f5 Iustin Pop
       "Whether node is a master candidate",
150 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeMasterCandidate), QffNormal)
151 046fe3f5 Iustin Pop
  , (FieldDefinition "master_capable" "MasterCapable" QFTBool
152 046fe3f5 Iustin Pop
       "Whether node can become a master candidate",
153 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeMasterCapable), QffNormal)
154 046fe3f5 Iustin Pop
  , (FieldDefinition "name" "Node" QFTText "Node name",
155 91c1a265 Iustin Pop
     FieldSimple (rsNormal . nodeName), QffHostname)
156 046fe3f5 Iustin Pop
  , (FieldDefinition "offline" "Offline" QFTBool
157 046fe3f5 Iustin Pop
       "Whether node is marked offline",
158 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeOffline), QffNormal)
159 046fe3f5 Iustin Pop
  , (FieldDefinition "vm_capable" "VMCapable" QFTBool
160 046fe3f5 Iustin Pop
       "Whether node can host instances",
161 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeVmCapable), QffNormal)
162 046fe3f5 Iustin Pop
  , (FieldDefinition "pip" "PrimaryIP" QFTText "Primary IP address",
163 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodePrimaryIp), QffNormal)
164 046fe3f5 Iustin Pop
  , (FieldDefinition "sip" "SecondaryIP" QFTText "Secondary IP address",
165 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeSecondaryIp), QffNormal)
166 046fe3f5 Iustin Pop
  , (FieldDefinition "master" "IsMaster" QFTBool "Whether node is master",
167 046fe3f5 Iustin Pop
     FieldConfig (\cfg node ->
168 046fe3f5 Iustin Pop
                    rsNormal (nodeName node ==
169 f94a9680 Iustin Pop
                              clusterMasterNode (configCluster cfg))),
170 f94a9680 Iustin Pop
     QffNormal)
171 046fe3f5 Iustin Pop
  , (FieldDefinition "group" "Group" QFTText "Node group",
172 046fe3f5 Iustin Pop
     FieldConfig (\cfg node ->
173 a64cc96b Helga Velroyen
                    rsMaybeNoData (groupName <$> getGroupOfNode cfg node)),
174 f94a9680 Iustin Pop
     QffNormal)
175 046fe3f5 Iustin Pop
  , (FieldDefinition "group.uuid" "GroupUUID" QFTText "UUID of node group",
176 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeGroup), QffNormal)
177 046fe3f5 Iustin Pop
  ,  (FieldDefinition "ndparams" "NodeParameters" QFTOther
178 046fe3f5 Iustin Pop
        "Merged node parameters",
179 a64cc96b Helga Velroyen
      FieldConfig ((rsMaybeNoData .) . getNodeNdParams), QffNormal)
180 046fe3f5 Iustin Pop
  , (FieldDefinition "custom_ndparams" "CustomNodeParameters" QFTOther
181 046fe3f5 Iustin Pop
                       "Custom node parameters",
182 f94a9680 Iustin Pop
     FieldSimple (rsNormal . nodeNdparams), QffNormal)
183 046fe3f5 Iustin Pop
  -- FIXME: the below could be generalised a bit, like in Python
184 046fe3f5 Iustin Pop
  , (FieldDefinition "pinst_cnt" "Pinst" QFTNumber
185 046fe3f5 Iustin Pop
       "Number of instances with this node as primary",
186 046fe3f5 Iustin Pop
     FieldConfig (\cfg ->
187 f94a9680 Iustin Pop
                    rsNormal . length . fst . getNodeInstances cfg . nodeName),
188 f94a9680 Iustin Pop
     QffNormal)
189 046fe3f5 Iustin Pop
  , (FieldDefinition "sinst_cnt" "Sinst" QFTNumber
190 046fe3f5 Iustin Pop
       "Number of instances with this node as secondary",
191 046fe3f5 Iustin Pop
     FieldConfig (\cfg ->
192 f94a9680 Iustin Pop
                    rsNormal . length . snd . getNodeInstances cfg . nodeName),
193 f94a9680 Iustin Pop
     QffNormal)
194 b9bdc10e Iustin Pop
  , (FieldDefinition "pinst_list" "PriInstances" QFTOther
195 046fe3f5 Iustin Pop
       "List of instances with this node as primary",
196 c81b97f2 Iustin Pop
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . fst .
197 f94a9680 Iustin Pop
                          getNodeInstances cfg . nodeName), QffNormal)
198 b9bdc10e Iustin Pop
  , (FieldDefinition "sinst_list" "SecInstances" QFTOther
199 046fe3f5 Iustin Pop
       "List of instances with this node as secondary",
200 c81b97f2 Iustin Pop
     FieldConfig (\cfg -> rsNormal . niceSort . map instName . snd .
201 f94a9680 Iustin Pop
                          getNodeInstances cfg . nodeName), QffNormal)
202 046fe3f5 Iustin Pop
  , (FieldDefinition "role" "Role" QFTText nodeRoleDoc,
203 f94a9680 Iustin Pop
     FieldConfig ((rsNormal .) . getNodeRole), QffNormal)
204 046fe3f5 Iustin Pop
  , (FieldDefinition "powered" "Powered" QFTBool
205 046fe3f5 Iustin Pop
       "Whether node is thought to be powered on",
206 f94a9680 Iustin Pop
     FieldConfig getNodePower, QffNormal)
207 046fe3f5 Iustin Pop
  -- FIXME: the two fields below are incomplete in Python, part of the
208 046fe3f5 Iustin Pop
  -- non-implemented node resource model; they are declared just for
209 046fe3f5 Iustin Pop
  -- parity, but are not functional
210 046fe3f5 Iustin Pop
  , (FieldDefinition "hv_state" "HypervisorState" QFTOther "Hypervisor state",
211 82953e9a Iustin Pop
     FieldSimple (const rsUnavail), QffNormal)
212 046fe3f5 Iustin Pop
  , (FieldDefinition "disk_state" "DiskState" QFTOther "Disk state",
213 82953e9a Iustin Pop
     FieldSimple (const rsUnavail), QffNormal)
214 046fe3f5 Iustin Pop
  ] ++
215 046fe3f5 Iustin Pop
  map nodeLiveFieldBuilder nodeLiveFieldsDefs ++
216 046fe3f5 Iustin Pop
  map buildNdParamField allNDParamFields ++
217 046fe3f5 Iustin Pop
  timeStampFields ++
218 046fe3f5 Iustin Pop
  uuidFields "Node" ++
219 046fe3f5 Iustin Pop
  serialFields "Node" ++
220 046fe3f5 Iustin Pop
  tagsFields
221 046fe3f5 Iustin Pop
222 046fe3f5 Iustin Pop
-- | The node fields map.
223 36162faf Iustin Pop
fieldsMap :: FieldMap Node Runtime
224 36162faf Iustin Pop
fieldsMap =
225 f94a9680 Iustin Pop
  Map.fromList $ map (\v@(f, _, _) -> (fdefName f, v)) nodeFields
226 1ba01ff7 Iustin Pop
227 1ba01ff7 Iustin Pop
-- | Collect live data from RPC query if enabled.
228 1ba01ff7 Iustin Pop
--
229 1ba01ff7 Iustin Pop
-- FIXME: Check which fields we actually need and possibly send empty
230 36162faf Iustin Pop
-- hvs\/vgs if no info from hypervisor\/volume group respectively is
231 1ba01ff7 Iustin Pop
-- required
232 36162faf Iustin Pop
collectLiveData:: Bool -> ConfigData -> [Node] -> IO [(Node, Runtime)]
233 36162faf Iustin Pop
collectLiveData False _ nodes =
234 1ba01ff7 Iustin Pop
  return $ zip nodes (repeat $ Left (RpcResultError "Live data disabled"))
235 36162faf Iustin Pop
collectLiveData True cfg nodes = do
236 64b0309a Dimitris Aragiorgis
  let vgs = maybeToList . clusterVolumeGroupName $ configCluster cfg
237 4b92e992 Helga Velroyen
      -- FIXME: This currently sets every storage unit to LVM
238 06fb92cf Bernardo Dal Seno
      storage_units = zip (repeat T.StorageLvmVg) vgs ++
239 06fb92cf Bernardo Dal Seno
                      zip (repeat T.StorageLvmPv) vgs
240 030ab01a Helga Velroyen
      hvs = [getDefaultHypervisorSpec cfg]
241 319322a7 Bernardo Dal Seno
      step n (bn, gn, em) =
242 319322a7 Bernardo Dal Seno
        let ndp' = getNodeNdParams cfg n
243 319322a7 Bernardo Dal Seno
        in case ndp' of
244 319322a7 Bernardo Dal Seno
             Just ndp -> (bn, n : gn,
245 319322a7 Bernardo Dal Seno
                          (nodeName n, ndpExclusiveStorage ndp) : em)
246 319322a7 Bernardo Dal Seno
             Nothing -> (n : bn, gn, em)
247 319322a7 Bernardo Dal Seno
      (bnodes, gnodes, emap) = foldr step ([], [], []) nodes
248 4b92e992 Helga Velroyen
  rpcres <- executeRpcCall gnodes (RpcCallNodeInfo storage_units hvs
249 4b92e992 Helga Velroyen
    (Map.fromList emap))
250 319322a7 Bernardo Dal Seno
  -- FIXME: The order of nodes in the result could be different from the input
251 319322a7 Bernardo Dal Seno
  return $ zip bnodes (repeat $ Left (RpcResultError "Broken configuration"))
252 319322a7 Bernardo Dal Seno
           ++ rpcres
253 030ab01a Helga Velroyen
254 030ab01a Helga Velroyen
-- | Looks up the default hypervisor and it's hvparams
255 030ab01a Helga Velroyen
getDefaultHypervisorSpec :: ConfigData -> (Hypervisor, HvParams)
256 030ab01a Helga Velroyen
getDefaultHypervisorSpec cfg = (hv, getHvParamsFromCluster cfg hv)
257 030ab01a Helga Velroyen
  where hv = getDefaultHypervisor cfg
258 030ab01a Helga Velroyen
259 030ab01a Helga Velroyen
-- | Looks up the cluster's hvparams of the given hypervisor
260 030ab01a Helga Velroyen
getHvParamsFromCluster :: ConfigData -> Hypervisor -> HvParams
261 030ab01a Helga Velroyen
getHvParamsFromCluster cfg hv =
262 030ab01a Helga Velroyen
  fromMaybe (GenericContainer (Map.fromList []))
263 68af861c Helga Velroyen
    (Map.lookup (hypervisorToRaw hv)
264 030ab01a Helga Velroyen
       (fromContainer (clusterHvparams (configCluster cfg))))