Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Node.hs @ 37904802

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