Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Instance.hs @ 3fd38382

History | View | Annotate | Download (28.7 kB)

1
{-| Implementation of the Ganeti Query2 instance queries.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 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.Instance
27
  ( Runtime
28
  , fieldsMap
29
  , collectLiveData
30
  , instanceFields
31
  , instanceAliases
32
  ) where
33

    
34
import Control.Applicative
35
import Data.List
36
import Data.Maybe
37
import Data.Monoid
38
import qualified Data.Map as Map
39
import qualified Text.JSON as J
40
import Text.Printf
41

    
42
import Ganeti.BasicTypes
43
import Ganeti.Common
44
import Ganeti.Config
45
import qualified Ganeti.Constants as C
46
import qualified Ganeti.ConstantUtils as C
47
import Ganeti.Errors
48
import Ganeti.JSON
49
import Ganeti.Objects
50
import Ganeti.Query.Common
51
import Ganeti.Query.Language
52
import Ganeti.Query.Types
53
import Ganeti.Rpc
54
import Ganeti.Storage.Utils
55
import Ganeti.Types
56
import Ganeti.Utils (formatOrdinal)
57

    
58
-- | The LiveInfo structure packs additional information beside the
59
-- 'InstanceInfo'. We also need to know whether the instance information was
60
-- found on the primary node, and encode this as a Bool.
61
type LiveInfo = (InstanceInfo, Bool)
62

    
63
-- | Runtime possibly containing the 'LiveInfo'. See the genericQuery function
64
-- in the Query.hs file for an explanation of the terms used.
65
type Runtime = Either RpcError (Maybe LiveInfo)
66

    
67
-- | The instance fields map.
68
fieldsMap :: FieldMap Instance Runtime
69
fieldsMap = Map.fromList [(fdefName f, v) | v@(f, _, _) <- aliasedFields]
70

    
71
-- | The instance aliases.
72
instanceAliases :: [(FieldName, FieldName)]
73
instanceAliases =
74
  [ ("vcpus", "be/vcpus")
75
  , ("be/memory", "be/maxmem")
76
  , ("sda_size", "disk.size/0")
77
  , ("sdb_size", "disk.size/1")
78
  , ("ip", "nic.ip/0")
79
  , ("mac", "nic.mac/0")
80
  , ("bridge", "nic.bridge/0")
81
  , ("nic_mode", "nic.mode/0")
82
  , ("nic_link", "nic.link/0")
83
  , ("nic_network", "nic.network/0")
84
  ]
85

    
86
-- | The aliased instance fields.
87
aliasedFields :: FieldList Instance Runtime
88
aliasedFields = aliasFields instanceAliases instanceFields
89

    
90
-- | The instance fields.
91
instanceFields :: FieldList Instance Runtime
92
instanceFields =
93
  -- Simple fields
94
  [ (FieldDefinition "admin_state" "InstanceState" QFTText
95
     "Desired state of instance",
96
     FieldSimple (rsNormal . adminStateToRaw . instAdminState), QffNormal)
97
  , (FieldDefinition "admin_up" "Autostart" QFTBool
98
     "Desired state of instance",
99
     FieldSimple (rsNormal . (== AdminUp) . instAdminState), QffNormal)
100
  , (FieldDefinition "disk_template" "Disk_template" QFTText
101
     "Instance disk template",
102
     FieldSimple (rsNormal . instDiskTemplate), QffNormal)
103
  , (FieldDefinition "disks_active" "DisksActive" QFTBool
104
     "Desired state of instance disks",
105
     FieldSimple (rsNormal . instDisksActive), QffNormal)
106
  , (FieldDefinition "name" "Instance" QFTText
107
     "Instance name",
108
     FieldSimple (rsNormal . instName), QffHostname)
109
  , (FieldDefinition "hypervisor" "Hypervisor" QFTText
110
     "Hypervisor name",
111
     FieldSimple (rsNormal . instHypervisor), QffNormal)
112
  , (FieldDefinition "network_port" "Network_port" QFTOther
113
     "Instance network port if available (e.g. for VNC console)",
114
     FieldSimple (rsMaybeUnavail . instNetworkPort), QffNormal)
115
  , (FieldDefinition "os" "OS" QFTText
116
     "Operating system",
117
     FieldSimple (rsNormal . instOs), QffNormal)
118
  , (FieldDefinition "pnode" "Primary_node" QFTText
119
     "Primary node",
120
     FieldConfig getPrimaryNodeName, QffHostname)
121
  , (FieldDefinition "pnode.group" "PrimaryNodeGroup" QFTText
122
     "Primary node's group",
123
     FieldConfig getPrimaryNodeGroup, QffNormal)
124
  , (FieldDefinition "snodes" "Secondary_Nodes" QFTOther
125
     "Secondary nodes; usually this will just be one node",
126
     FieldConfig (getSecondaryNodeAttribute nodeName), QffNormal)
127
  , (FieldDefinition "snodes.group" "SecondaryNodesGroups" QFTOther
128
     "Node groups of secondary nodes",
129
     FieldConfig (getSecondaryNodeGroupAttribute groupName), QffNormal)
130
  , (FieldDefinition "snodes.group.uuid" "SecondaryNodesGroupsUUID" QFTOther
131
     "Node group UUIDs of secondary nodes",
132
     FieldConfig (getSecondaryNodeGroupAttribute groupUuid), QffNormal)
133
  ] ++
134

    
135
  -- Instance parameter fields, whole
136
  [ (FieldDefinition "hvparams" "HypervisorParameters" QFTOther
137
     "Hypervisor parameters (merged)",
138
     FieldConfig ((rsNormal .) . getFilledInstHvParams), QffNormal)
139
  , (FieldDefinition "beparams" "BackendParameters" QFTOther
140
     "Backend parameters (merged)",
141
     FieldConfig ((rsErrorNoData .) . getFilledInstBeParams), QffNormal)
142
  , (FieldDefinition "osparams" "OpSysParameters" QFTOther
143
     "Operating system parameters (merged)",
144
     FieldConfig ((rsNormal .) . getFilledInstOsParams), QffNormal)
145
  , (FieldDefinition "custom_hvparams" "CustomHypervisorParameters" QFTOther
146
     "Custom hypervisor parameters",
147
     FieldSimple (rsNormal . instHvparams), QffNormal)
148
  , (FieldDefinition "custom_beparams" "CustomBackendParameters" QFTOther
149
     "Custom backend parameters",
150
     FieldSimple (rsNormal . instBeparams), QffNormal)
151
  , (FieldDefinition "custom_osparams" "CustomOpSysParameters" QFTOther
152
     "Custom operating system parameters",
153
     FieldSimple (rsNormal . instOsparams), QffNormal)
154
  ] ++
155

    
156
  -- Instance parameter fields, generated
157
  map (buildBeParamField beParamGetter) allBeParamFields ++
158
  map (buildHvParamField hvParamGetter) (C.toList C.hvsParameters) ++
159

    
160
  -- Aggregate disk parameter fields
161
  [ (FieldDefinition "disk_usage" "DiskUsage" QFTUnit
162
     "Total disk space used by instance on each of its nodes; this is not the\
163
     \ disk size visible to the instance, but the usage on the node",
164
     FieldSimple (rsNormal . getDiskSizeRequirements), QffNormal)
165
  , (FieldDefinition "disk.count" "Disks" QFTNumber
166
     "Number of disks",
167
     FieldSimple (rsNormal . length . instDisks), QffNormal)
168
  , (FieldDefinition "disk.sizes" "Disk_sizes" QFTOther
169
     "List of disk sizes",
170
     FieldSimple (rsNormal . map diskSize . instDisks), QffNormal)
171
  , (FieldDefinition "disk.spindles" "Disk_spindles" QFTOther
172
     "List of disk spindles",
173
     FieldSimple (rsNormal . map (MaybeForJSON . diskSpindles) .
174
                  instDisks),
175
     QffNormal)
176
  , (FieldDefinition "disk.names" "Disk_names" QFTOther
177
     "List of disk names",
178
     FieldSimple (rsNormal . map (MaybeForJSON . diskName) .
179
                  instDisks),
180
     QffNormal)
181
  , (FieldDefinition "disk.uuids" "Disk_UUIDs" QFTOther
182
     "List of disk UUIDs",
183
     FieldSimple (rsNormal . map diskUuid . instDisks), QffNormal)
184
  ] ++
185

    
186
  -- Per-disk parameter fields
187
  instantiateIndexedFields C.maxDisks
188
  [ (fieldDefinitionCompleter "disk.size/%d" "Disk/%d" QFTUnit
189
     "Disk size of %s disk",
190
     getIndexedField instDisks diskSize, QffNormal)
191
  , (fieldDefinitionCompleter "disk.spindles/%d" "DiskSpindles/%d" QFTNumber
192
     "Spindles of %s disk",
193
     getIndexedOptionalField instDisks diskSpindles, QffNormal)
194
  , (fieldDefinitionCompleter "disk.name/%d" "DiskName/%d" QFTText
195
     "Name of %s disk",
196
     getIndexedOptionalField instDisks diskName, QffNormal)
197
  , (fieldDefinitionCompleter "disk.uuid/%d" "DiskUUID/%d" QFTText
198
     "UUID of %s disk",
199
     getIndexedField instDisks diskUuid, QffNormal)
200
  ] ++
201

    
202
  -- Aggregate nic parameter fields
203
  [ (FieldDefinition "nic.count" "NICs" QFTNumber
204
     "Number of network interfaces",
205
     FieldSimple (rsNormal . length . instNics), QffNormal)
206
  , (FieldDefinition "nic.macs" "NIC_MACs" QFTOther
207
     (nicAggDescPrefix ++ "MAC address"),
208
     FieldSimple (rsNormal . map nicMac . instNics), QffNormal)
209
  , (FieldDefinition "nic.ips" "NIC_IPs" QFTOther
210
     (nicAggDescPrefix ++ "IP address"),
211
     FieldSimple (rsNormal . map (MaybeForJSON . nicIp) . instNics),
212
     QffNormal)
213
  , (FieldDefinition "nic.names" "NIC_Names" QFTOther
214
     (nicAggDescPrefix ++ "name"),
215
     FieldSimple (rsNormal . map (MaybeForJSON . nicName) . instNics),
216
     QffNormal)
217
  , (FieldDefinition "nic.uuids" "NIC_UUIDs" QFTOther
218
     (nicAggDescPrefix ++ "UUID"),
219
     FieldSimple (rsNormal . map nicUuid . instNics), QffNormal)
220
  , (FieldDefinition "nic.modes" "NIC_modes" QFTOther
221
     (nicAggDescPrefix ++ "mode"),
222
     FieldConfig (\cfg -> rsNormal . map
223
       (nicpMode . fillNicParamsFromConfig cfg . nicNicparams)
224
       . instNics),
225
     QffNormal)
226
  , (FieldDefinition "nic.bridges" "NIC_bridges" QFTOther
227
     (nicAggDescPrefix ++ "bridge"),
228
     FieldConfig (\cfg -> rsNormal . map (MaybeForJSON . getNicBridge .
229
       fillNicParamsFromConfig cfg . nicNicparams) . instNics),
230
     QffNormal)
231
  , (FieldDefinition "nic.links" "NIC_links" QFTOther
232
     (nicAggDescPrefix ++ "link"),
233
     FieldConfig (\cfg -> rsNormal . map
234
       (nicpLink . fillNicParamsFromConfig cfg . nicNicparams)
235
       . instNics),
236
     QffNormal)
237
  , (FieldDefinition "nic.networks" "NIC_networks" QFTOther
238
     "List containing each interface's network",
239
     FieldSimple (rsNormal . map (MaybeForJSON . nicNetwork) . instNics),
240
     QffNormal)
241
  , (FieldDefinition "nic.networks.names" "NIC_networks_names" QFTOther
242
     "List containing the name of each interface's network",
243
     FieldConfig (\cfg -> rsNormal . map
244
       (\x -> MaybeForJSON (getNetworkName cfg <$> nicNetwork x))
245
       . instNics),
246
     QffNormal)
247
  ] ++
248

    
249
  -- Per-nic parameter fields
250
  instantiateIndexedFields C.maxNics
251
  [ (fieldDefinitionCompleter "nic.ip/%d" "NicIP/%d" QFTText
252
     ("IP address" ++ nicDescSuffix),
253
     getIndexedOptionalField instNics nicIp, QffNormal)
254
  , (fieldDefinitionCompleter "nic.uuid/%d" "NicUUID/%d" QFTText
255
     ("UUID address" ++ nicDescSuffix),
256
     getIndexedField instNics nicUuid, QffNormal)
257
  , (fieldDefinitionCompleter "nic.mac/%d" "NicMAC/%d" QFTText
258
     ("MAC address" ++ nicDescSuffix),
259
     getIndexedField instNics nicMac, QffNormal)
260
  , (fieldDefinitionCompleter "nic.name/%d" "NicName/%d" QFTText
261
     ("Name address" ++ nicDescSuffix),
262
     getIndexedOptionalField instNics nicName, QffNormal)
263
  , (fieldDefinitionCompleter "nic.network/%d" "NicNetwork/%d" QFTText
264
     ("Network" ++ nicDescSuffix),
265
     getIndexedOptionalField instNics nicNetwork, QffNormal)
266
  , (fieldDefinitionCompleter "nic.mode/%d" "NicMode/%d" QFTText
267
     ("Mode" ++ nicDescSuffix),
268
     getIndexedNicField nicpMode, QffNormal)
269
  , (fieldDefinitionCompleter "nic.link/%d" "NicLink/%d" QFTText
270
     ("Link" ++ nicDescSuffix),
271
     getIndexedNicField nicpLink, QffNormal)
272
  , (fieldDefinitionCompleter "nic.network.name/%d" "NicNetworkName/%d" QFTText
273
     ("Network name" ++ nicDescSuffix),
274
     getIndexedNicNetworkNameField, QffNormal)
275
  , (fieldDefinitionCompleter "nic.bridge/%d" "NicBridge/%d" QFTText
276
     ("Bridge" ++ nicDescSuffix),
277
     getOptionalIndexedNicField getNicBridge, QffNormal)
278
  ] ++
279

    
280
  -- Live fields using special getters
281
  [ (FieldDefinition "status" "Status" QFTText
282
     statusDocText,
283
     FieldConfigRuntime statusExtract, QffNormal)
284
  , (FieldDefinition "oper_state" "Running" QFTBool
285
     "Actual state of instance",
286
     FieldRuntime operStatusExtract, QffNormal)
287
  ] ++
288

    
289
  -- Simple live fields
290
  map instanceLiveFieldBuilder instanceLiveFieldsDefs ++
291

    
292
  -- Generated fields
293
  serialFields "Instance" ++
294
  uuidFields "Instance" ++
295
  tagsFields
296

    
297
-- * Helper functions for node property retrieval
298

    
299
-- | Constant suffix of network interface field descriptions.
300
nicDescSuffix ::String
301
nicDescSuffix = " of %s network interface"
302

    
303
-- | Almost-constant suffix of aggregate network interface field descriptions.
304
nicAggDescPrefix ::String
305
nicAggDescPrefix = "List containing each network interface's "
306

    
307
-- | Given a network name id, returns the network's name.
308
getNetworkName :: ConfigData -> String -> NonEmptyString
309
getNetworkName cfg = networkName . (Map.!) (fromContainer $ configNetworks cfg)
310

    
311
-- | Gets the bridge of a NIC.
312
getNicBridge :: FilledNicParams -> Maybe String
313
getNicBridge nicParams
314
  | nicpMode nicParams == NMBridged = Just $ nicpLink nicParams
315
  | otherwise                       = Nothing
316

    
317
-- | Fill partial NIC params by using the defaults from the configuration.
318
fillNicParamsFromConfig :: ConfigData -> PartialNicParams -> FilledNicParams
319
fillNicParamsFromConfig cfg = fillNicParams (getDefaultNicParams cfg)
320

    
321
-- | Retrieves the default network interface parameters.
322
getDefaultNicParams :: ConfigData -> FilledNicParams
323
getDefaultNicParams cfg =
324
  (Map.!) (fromContainer . clusterNicparams . configCluster $ cfg) C.ppDefault
325

    
326
-- | Returns a field that retrieves a given NIC's network name.
327
getIndexedNicNetworkNameField :: Int -> FieldGetter Instance Runtime
328
getIndexedNicNetworkNameField index =
329
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
330
    nicObj <- maybeAt index $ instNics inst
331
    nicNetworkId <- nicNetwork nicObj
332
    return $ getNetworkName cfg nicNetworkId)
333

    
334
-- | Gets a fillable NIC field.
335
getIndexedNicField :: (J.JSON a)
336
                   => (FilledNicParams -> a)
337
                   -> Int
338
                   -> FieldGetter Instance Runtime
339
getIndexedNicField getter =
340
  getOptionalIndexedNicField (\x -> Just . getter $ x)
341

    
342
-- | Gets an optional fillable NIC field.
343
getOptionalIndexedNicField :: (J.JSON a)
344
                           => (FilledNicParams -> Maybe a)
345
                           -> Int
346
                           -> FieldGetter Instance Runtime
347
getOptionalIndexedNicField =
348
  getIndexedFieldWithDefault
349
    (map nicNicparams . instNics) (\x _ -> getDefaultNicParams x) fillNicParams
350

    
351
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
352
-- for fields that should be filled out through the use of a default.
353
getIndexedFieldWithDefault :: (J.JSON c)
354
  => (Instance -> [a])             -- ^ Extracts a list of incomplete objects
355
  -> (ConfigData -> Instance -> b) -- ^ Extracts the default object
356
  -> (b -> a -> b)                 -- ^ Fills the default object
357
  -> (b -> Maybe c)                -- ^ Extracts an obj property
358
  -> Int                           -- ^ Index in list to use
359
  -> FieldGetter Instance Runtime  -- ^ Result
360
getIndexedFieldWithDefault
361
  listGetter defaultGetter fillFn propertyGetter index =
362
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
363
                              incompleteObj <- maybeAt index $ listGetter inst
364
                              let defaultObj = defaultGetter cfg inst
365
                                  completeObj = fillFn defaultObj incompleteObj
366
                              propertyGetter completeObj)
367

    
368
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
369
-- for fields that may not return a value, expressed through the Maybe monad.
370
getIndexedOptionalField :: (J.JSON b)
371
                        => (Instance -> [a]) -- ^ Extracts a list of objects
372
                        -> (a -> Maybe b)    -- ^ Possibly gets a property
373
                                             -- from an object
374
                        -> Int               -- ^ Index in list to use
375
                        -> FieldGetter Instance Runtime -- ^ Result
376
getIndexedOptionalField extractor optPropertyGetter index =
377
  FieldSimple(\inst -> rsMaybeUnavail $ do
378
                         obj <- maybeAt index $ extractor inst
379
                         optPropertyGetter obj)
380

    
381
-- | Creates a function which produces a 'FieldGetter' when fed an index.
382
-- Works only for fields that surely return a value.
383
getIndexedField :: (J.JSON b)
384
                => (Instance -> [a]) -- ^ Extracts a list of objects
385
                -> (a -> b)          -- ^ Gets a property from an object
386
                -> Int               -- ^ Index in list to use
387
                -> FieldGetter Instance Runtime -- ^ Result
388
getIndexedField extractor propertyGetter index =
389
  let optPropertyGetter = Just . propertyGetter
390
  in getIndexedOptionalField extractor optPropertyGetter index
391

    
392
-- | Retrieves a value from an array at an index, using the Maybe monad to
393
-- indicate failure.
394
maybeAt :: Int -> [a] -> Maybe a
395
maybeAt index list
396
  | index >= length list = Nothing
397
  | otherwise            = Just $ list !! index
398

    
399
-- | Primed with format strings for everything but the type, it consumes two
400
-- values and uses them to complete the FieldDefinition.
401
-- Warning: a bit unsafe as it uses printf. Handle with care.
402
fieldDefinitionCompleter :: (PrintfArg t1) => (PrintfArg t2)
403
                         => FieldName
404
                         -> FieldTitle
405
                         -> FieldType
406
                         -> FieldDoc
407
                         -> t1
408
                         -> t2
409
                         -> FieldDefinition
410
fieldDefinitionCompleter fName fTitle fType fDoc firstVal secondVal =
411
  FieldDefinition (printf fName firstVal)
412
                  (printf fTitle firstVal)
413
                  fType
414
                  (printf fDoc secondVal)
415

    
416
-- | Given an incomplete field definition and values that can complete it,
417
-- return a fully functional FieldData. Cannot work for all cases, should be
418
-- extended as necessary.
419
fillIncompleteFields :: (t1 -> t2 -> FieldDefinition,
420
                         t1 -> FieldGetter a b,
421
                         QffMode)
422
                     -> t1
423
                     -> t2
424
                     -> FieldData a b
425
fillIncompleteFields (iDef, iGet, mode) firstVal secondVal =
426
  (iDef firstVal secondVal, iGet firstVal, mode)
427

    
428
-- | Given indexed fields that describe lists, complete / instantiate them for
429
-- a given list size.
430
instantiateIndexedFields :: (Show t1, Integral t1)
431
                         => Int            -- ^ The size of the list
432
                         -> [(t1 -> String -> FieldDefinition,
433
                              t1 -> FieldGetter a b,
434
                              QffMode)]    -- ^ The indexed fields
435
                         -> FieldList a b  -- ^ A list of complete fields
436
instantiateIndexedFields listSize fields = do
437
  index <- take listSize [0..]
438
  field <- fields
439
  return . fillIncompleteFields field index . formatOrdinal $ index + 1
440

    
441
-- * Various helper functions for property retrieval
442

    
443
-- | Helper function for primary node retrieval
444
getPrimaryNode :: ConfigData -> Instance -> ErrorResult Node
445
getPrimaryNode cfg = getInstPrimaryNode cfg . instName
446

    
447
-- | Get primary node hostname
448
getPrimaryNodeName :: ConfigData -> Instance -> ResultEntry
449
getPrimaryNodeName cfg inst =
450
  rsErrorNoData $ nodeName <$> getPrimaryNode cfg inst
451

    
452
-- | Get primary node hostname
453
getPrimaryNodeGroup :: ConfigData -> Instance -> ResultEntry
454
getPrimaryNodeGroup cfg inst =
455
  rsErrorNoData $ (J.showJSON . groupName) <$>
456
    (getPrimaryNode cfg inst >>=
457
    maybeToError "Configuration missing" . getGroupOfNode cfg)
458

    
459
-- | Get secondary nodes - the configuration objects themselves
460
getSecondaryNodes :: ConfigData -> Instance -> ErrorResult [Node]
461
getSecondaryNodes cfg inst = do
462
  pNode <- getPrimaryNode cfg inst
463
  allNodes <- getInstAllNodes cfg $ instName inst
464
  return $ delete pNode allNodes
465

    
466
-- | Get attributes of the secondary nodes
467
getSecondaryNodeAttribute :: (J.JSON a)
468
                          => (Node -> a)
469
                          -> ConfigData
470
                          -> Instance
471
                          -> ResultEntry
472
getSecondaryNodeAttribute getter cfg inst =
473
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodes cfg inst
474

    
475
-- | Get secondary node groups
476
getSecondaryNodeGroups :: ConfigData -> Instance -> ErrorResult [NodeGroup]
477
getSecondaryNodeGroups cfg inst = do
478
  sNodes <- getSecondaryNodes cfg inst
479
  return . catMaybes $ map (getGroupOfNode cfg) sNodes
480

    
481
-- | Get attributes of secondary node groups
482
getSecondaryNodeGroupAttribute :: (J.JSON a)
483
                               => (NodeGroup -> a)
484
                               -> ConfigData
485
                               -> Instance
486
                               -> ResultEntry
487
getSecondaryNodeGroupAttribute getter cfg inst =
488
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodeGroups cfg inst
489

    
490
-- | Beparam getter builder: given a field, it returns a FieldConfig
491
-- getter, that is a function that takes the config and the object and
492
-- returns the Beparam field specified when the getter was built.
493
beParamGetter :: String       -- ^ The field we are building the getter for
494
              -> ConfigData   -- ^ The configuration object
495
              -> Instance     -- ^ The instance configuration object
496
              -> ResultEntry  -- ^ The result
497
beParamGetter field config inst =
498
  case getFilledInstBeParams config inst of
499
    Ok beParams -> dictFieldGetter field $ Just beParams
500
    Bad       _ -> rsNoData
501

    
502
-- | Hvparam getter builder: given a field, it returns a FieldConfig
503
-- getter, that is a function that takes the config and the object and
504
-- returns the Hvparam field specified when the getter was built.
505
hvParamGetter :: String -- ^ The field we're building the getter for
506
              -> ConfigData -> Instance -> ResultEntry
507
hvParamGetter field cfg inst =
508
  rsMaybeUnavail . Map.lookup field . fromContainer $
509
                                        getFilledInstHvParams cfg inst
510

    
511
-- * Live fields functionality
512

    
513
-- | List of node live fields.
514
instanceLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
515
instanceLiveFieldsDefs =
516
  [ ("oper_ram", "Memory", QFTUnit, "oper_ram",
517
     "Actual memory usage as seen by hypervisor")
518
  , ("oper_vcpus", "VCPUs", QFTNumber, "oper_vcpus",
519
     "Actual number of VCPUs as seen by hypervisor")
520
  ]
521

    
522
-- | Map each name to a function that extracts that value from the RPC result.
523
instanceLiveFieldExtract :: FieldName -> InstanceInfo -> Instance -> J.JSValue
524
instanceLiveFieldExtract "oper_ram"   info _ = J.showJSON $ instInfoMemory info
525
instanceLiveFieldExtract "oper_vcpus" info _ = J.showJSON $ instInfoVcpus info
526
instanceLiveFieldExtract n _ _ = J.showJSON $
527
  "The field " ++ n ++ " is not an expected or extractable live field!"
528

    
529
-- | Helper for extracting field from RPC result.
530
instanceLiveRpcCall :: FieldName -> Runtime -> Instance -> ResultEntry
531
instanceLiveRpcCall fname (Right (Just (res, _))) inst =
532
  case instanceLiveFieldExtract fname res inst of
533
    J.JSNull -> rsNoData
534
    x        -> rsNormal x
535
instanceLiveRpcCall _ (Right Nothing) _ = rsUnavail
536
instanceLiveRpcCall _ (Left err) _ =
537
  ResultEntry (rpcErrorToStatus err) Nothing
538

    
539
-- | Builder for node live fields.
540
instanceLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
541
                         -> FieldData Instance Runtime
542
instanceLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
543
  ( FieldDefinition fname ftitle ftype fdoc
544
  , FieldRuntime $ instanceLiveRpcCall fname
545
  , QffNormal)
546

    
547
-- * Functionality related to status and operational status extraction
548

    
549
-- | The documentation text for the instance status field
550
statusDocText :: String
551
statusDocText =
552
  let si = show . instanceStatusToRaw :: InstanceStatus -> String
553
  in  "Instance status; " ++
554
      si Running ++
555
      " if instance is set to be running and actually is, " ++
556
      si StatusDown ++
557
      " if instance is stopped and is not running, " ++
558
      si WrongNode ++
559
      " if instance running, but not on its designated primary node, " ++
560
      si ErrorUp ++
561
      " if instance should be stopped, but is actually running, " ++
562
      si ErrorDown ++
563
      " if instance should run, but doesn't, " ++
564
      si NodeDown ++
565
      " if instance's primary node is down, " ++
566
      si NodeOffline ++
567
      " if instance's primary node is marked offline, " ++
568
      si StatusOffline ++
569
      " if instance is offline and does not use dynamic resources"
570

    
571
-- | Checks if the primary node of an instance is offline
572
isPrimaryOffline :: ConfigData -> Instance -> Bool
573
isPrimaryOffline cfg inst =
574
  let pNodeResult = getNode cfg $ instPrimaryNode inst
575
  in case pNodeResult of
576
     Ok pNode -> nodeOffline pNode
577
     Bad    _ -> error "Programmer error - result assumed to be OK is Bad!"
578

    
579
-- | Determines the status of a live instance
580
liveInstanceStatus :: LiveInfo -> Instance -> InstanceStatus
581
liveInstanceStatus (_, foundOnPrimary) inst
582
  | not foundOnPrimary    = WrongNode
583
  | adminState == AdminUp = Running
584
  | otherwise             = ErrorUp
585
  where adminState = instAdminState inst
586

    
587
-- | Determines the status of a dead instance.
588
deadInstanceStatus :: Instance -> InstanceStatus
589
deadInstanceStatus inst =
590
  case instAdminState inst of
591
    AdminUp      -> ErrorDown
592
    AdminDown    -> StatusDown
593
    AdminOffline -> StatusOffline
594

    
595
-- | Determines the status of the instance, depending on whether it is possible
596
-- to communicate with its primary node, on which node it is, and its
597
-- configuration.
598
determineInstanceStatus :: ConfigData      -- ^ The configuration data
599
                        -> Runtime         -- ^ All the data from the live call
600
                        -> Instance        -- ^ Static instance configuration
601
                        -> InstanceStatus  -- ^ Result
602
determineInstanceStatus cfg res inst
603
  | isPrimaryOffline cfg inst = NodeOffline
604
  | otherwise = case res of
605
                  Left _                -> NodeDown
606
                  Right (Just liveData) -> liveInstanceStatus liveData inst
607
                  Right Nothing         -> deadInstanceStatus inst
608

    
609
-- | Extracts the instance status, retrieving it using the functions above and
610
-- transforming it into a 'ResultEntry'.
611
statusExtract :: ConfigData -> Runtime -> Instance -> ResultEntry
612
statusExtract cfg res inst =
613
  rsNormal . J.showJSON . instanceStatusToRaw $
614
    determineInstanceStatus cfg res inst
615

    
616
-- | Extracts the operational status of the instance.
617
operStatusExtract :: Runtime -> Instance -> ResultEntry
618
operStatusExtract res _ =
619
  rsMaybeNoData $ J.showJSON <$>
620
    case res of
621
      Left  _ -> Nothing
622
      Right x -> Just $ isJust x
623

    
624
-- * Helper functions extracting information as necessary for the generic query
625
-- interfaces
626

    
627
-- | Finds information about the instance in the info delivered by a node
628
findInstanceInfo :: Instance
629
                 -> ERpcError RpcResultAllInstancesInfo
630
                 -> Maybe InstanceInfo
631
findInstanceInfo inst nodeResponse =
632
  case nodeResponse of
633
    Left  _err    -> Nothing
634
    Right allInfo ->
635
      let instances = rpcResAllInstInfoInstances allInfo
636
          maybeMatch = pickPairUnique (instName inst) instances
637
      in snd <$> maybeMatch
638

    
639
-- | Finds the node information ('RPCResultError') or the instance information
640
-- (Maybe 'LiveInfo').
641
extractLiveInfo :: [(Node, ERpcError RpcResultAllInstancesInfo)]
642
                -> Instance
643
                -> Runtime
644
extractLiveInfo nodeResultList inst =
645
  let uuidResultList = [(nodeUuid x, y) | (x, y) <- nodeResultList]
646
      pNodeUuid = instPrimaryNode inst
647
      maybeRPCError = getNodeStatus uuidResultList pNodeUuid
648
  in case maybeRPCError of
649
       Just err -> Left err
650
       Nothing  -> Right $ getInstanceStatus uuidResultList pNodeUuid inst
651

    
652
-- | Tries to find out if the node given by the uuid is bad - unreachable or
653
-- returning errors, does not mather for the purpose of this call.
654
getNodeStatus :: [(String, ERpcError RpcResultAllInstancesInfo)]
655
              -> String
656
              -> Maybe RpcError
657
getNodeStatus uuidList uuid =
658
  case snd <$> pickPairUnique uuid uuidList of
659
    Just (Left err) -> Just err
660
    Just (Right _)  -> Nothing
661
    Nothing         -> Just . RpcResultError $
662
                         "Primary node response not present"
663

    
664
-- | Retrieves the instance information if it is present anywhere in the all
665
-- instances RPC result. Notes if it originates from the primary node.
666
-- All nodes are represented as UUID's for ease of use.
667
getInstanceStatus :: [(String, ERpcError RpcResultAllInstancesInfo)]
668
                  -> String
669
                  -> Instance
670
                  -> Maybe LiveInfo
671
getInstanceStatus uuidList pNodeUuid inst =
672
  let primarySearchResult =
673
        snd <$> pickPairUnique pNodeUuid uuidList >>= findInstanceInfo inst
674
  in case primarySearchResult of
675
       Just instInfo -> Just (instInfo, True)
676
       Nothing       ->
677
         let allSearchResult =
678
               getFirst . mconcat $ map
679
               (First . findInstanceInfo inst . snd) uuidList
680
         in case allSearchResult of
681
              Just liveInfo -> Just (liveInfo, False)
682
              Nothing       -> Nothing
683

    
684
-- | Collect live data from RPC query if enabled.
685
collectLiveData :: Bool -> ConfigData -> [Instance] -> IO [(Instance, Runtime)]
686
collectLiveData liveDataEnabled cfg instances
687
  | not liveDataEnabled = return . zip instances . repeat . Left .
688
                            RpcResultError $ "Live data disabled"
689
  | otherwise = do
690
      let hvSpec = getDefaultHypervisorSpec cfg
691
          instance_nodes = nub . justOk $
692
                             map (getNode cfg . instPrimaryNode) instances
693
          good_nodes = nodesWithValidConfig cfg instance_nodes
694
      rpcres <- executeRpcCall good_nodes $ RpcCallAllInstancesInfo [hvSpec]
695
      return . zip instances . map (extractLiveInfo rpcres) $ instances