Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ 3e02cd3c

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