Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Node.hs @ 36162faf

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