Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Instance.hs @ 46cc1ab4

History | View | Annotate | Download (33.1 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
  , getInstanceInfo
31
  , instanceFields
32
  , instanceAliases
33
  ) where
34

    
35
import Control.Applicative
36
import Data.Either
37
import Data.List
38
import Data.Maybe
39
import Data.Monoid
40
import qualified Data.Map as Map
41
import Data.Ord (comparing)
42
import qualified Text.JSON as J
43
import Text.Printf
44

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

    
61
-- | The LiveInfo consists of two entries whose presence is independent.
62
-- The 'InstanceInfo' is the live instance information, accompanied by a bool
63
-- signifying if it was found on its designated primary node or not.
64
-- The 'InstanceConsoleInfo' describes how to connect to an instance.
65
-- Any combination of these may or may not be present, depending on node and
66
-- instance availability.
67
type LiveInfo = (Maybe (InstanceInfo, Bool), Maybe InstanceConsoleInfo)
68

    
69
-- | Runtime containing the 'LiveInfo'. See the genericQuery function in
70
-- the Query.hs file for an explanation of the terms used.
71
type Runtime = Either RpcError LiveInfo
72

    
73
-- | The instance fields map.
74
fieldsMap :: FieldMap Instance Runtime
75
fieldsMap = Map.fromList [(fdefName f, v) | v@(f, _, _) <- aliasedFields]
76

    
77
-- | The instance aliases.
78
instanceAliases :: [(FieldName, FieldName)]
79
instanceAliases =
80
  [ ("vcpus", "be/vcpus")
81
  , ("be/memory", "be/maxmem")
82
  , ("sda_size", "disk.size/0")
83
  , ("sdb_size", "disk.size/1")
84
  , ("ip", "nic.ip/0")
85
  , ("mac", "nic.mac/0")
86
  , ("bridge", "nic.bridge/0")
87
  , ("nic_mode", "nic.mode/0")
88
  , ("nic_link", "nic.link/0")
89
  , ("nic_network", "nic.network/0")
90
  ]
91

    
92
-- | The aliased instance fields.
93
aliasedFields :: FieldList Instance Runtime
94
aliasedFields = aliasFields instanceAliases instanceFields
95

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

    
144
  -- Instance parameter fields, whole
145
  [ (FieldDefinition "hvparams" "HypervisorParameters" QFTOther
146
     "Hypervisor parameters (merged)",
147
     FieldConfig
148
       ((rsNormal .) . getFilledInstHvParams (C.toList C.hvcGlobals)),
149
     QffNormal),
150

    
151
    (FieldDefinition "beparams" "BackendParameters" QFTOther
152
     "Backend parameters (merged)",
153
     FieldConfig ((rsErrorNoData .) . getFilledInstBeParams), QffNormal)
154
  , (FieldDefinition "osparams" "OpSysParameters" QFTOther
155
     "Operating system parameters (merged)",
156
     FieldConfig ((rsNormal .) . getFilledInstOsParams), QffNormal)
157
  , (FieldDefinition "custom_hvparams" "CustomHypervisorParameters" QFTOther
158
     "Custom hypervisor parameters",
159
     FieldSimple (rsNormal . instHvparams), QffNormal)
160
  , (FieldDefinition "custom_beparams" "CustomBackendParameters" QFTOther
161
     "Custom backend parameters",
162
     FieldSimple (rsNormal . instBeparams), QffNormal)
163
  , (FieldDefinition "custom_osparams" "CustomOpSysParameters" QFTOther
164
     "Custom operating system parameters",
165
     FieldSimple (rsNormal . instOsparams), QffNormal)
166
  , (FieldDefinition "custom_nicparams" "CustomNicParameters" QFTOther
167
     "Custom network interface parameters",
168
     FieldSimple (rsNormal . map nicNicparams . instNics), QffNormal)
169
  ] ++
170

    
171
  -- Instance parameter fields, generated
172
  map (buildBeParamField beParamGetter) allBeParamFields ++
173
  map (buildHvParamField hvParamGetter) (C.toList C.hvsParameters) ++
174

    
175
  -- Aggregate disk parameter fields
176
  [ (FieldDefinition "disk_usage" "DiskUsage" QFTUnit
177
     "Total disk space used by instance on each of its nodes; this is not the\
178
     \ disk size visible to the instance, but the usage on the node",
179
     FieldSimple (rsNormal . getDiskSizeRequirements), QffNormal)
180
  , (FieldDefinition "disk.count" "Disks" QFTNumber
181
     "Number of disks",
182
     FieldSimple (rsNormal . length . instDisks), QffNormal)
183
  , (FieldDefinition "disk.sizes" "Disk_sizes" QFTOther
184
     "List of disk sizes",
185
     FieldSimple (rsNormal . map diskSize . instDisks), QffNormal)
186
  , (FieldDefinition "disk.spindles" "Disk_spindles" QFTOther
187
     "List of disk spindles",
188
     FieldSimple (rsNormal . map (MaybeForJSON . diskSpindles) .
189
                  instDisks),
190
     QffNormal)
191
  , (FieldDefinition "disk.names" "Disk_names" QFTOther
192
     "List of disk names",
193
     FieldSimple (rsNormal . map (MaybeForJSON . diskName) .
194
                  instDisks),
195
     QffNormal)
196
  , (FieldDefinition "disk.uuids" "Disk_UUIDs" QFTOther
197
     "List of disk UUIDs",
198
     FieldSimple (rsNormal . map diskUuid . instDisks), QffNormal)
199
  ] ++
200

    
201
  -- Per-disk parameter fields
202
  instantiateIndexedFields C.maxDisks
203
  [ (fieldDefinitionCompleter "disk.size/%d" "Disk/%d" QFTUnit
204
     "Disk size of %s disk",
205
     getIndexedField instDisks diskSize, QffNormal)
206
  , (fieldDefinitionCompleter "disk.spindles/%d" "DiskSpindles/%d" QFTNumber
207
     "Spindles of %s disk",
208
     getIndexedOptionalField instDisks diskSpindles, QffNormal)
209
  , (fieldDefinitionCompleter "disk.name/%d" "DiskName/%d" QFTText
210
     "Name of %s disk",
211
     getIndexedOptionalField instDisks diskName, QffNormal)
212
  , (fieldDefinitionCompleter "disk.uuid/%d" "DiskUUID/%d" QFTText
213
     "UUID of %s disk",
214
     getIndexedField instDisks diskUuid, QffNormal)
215
  ] ++
216

    
217
  -- Aggregate nic parameter fields
218
  [ (FieldDefinition "nic.count" "NICs" QFTNumber
219
     "Number of network interfaces",
220
     FieldSimple (rsNormal . length . instNics), QffNormal)
221
  , (FieldDefinition "nic.macs" "NIC_MACs" QFTOther
222
     (nicAggDescPrefix ++ "MAC address"),
223
     FieldSimple (rsNormal . map nicMac . instNics), QffNormal)
224
  , (FieldDefinition "nic.ips" "NIC_IPs" QFTOther
225
     (nicAggDescPrefix ++ "IP address"),
226
     FieldSimple (rsNormal . map (MaybeForJSON . nicIp) . instNics),
227
     QffNormal)
228
  , (FieldDefinition "nic.names" "NIC_Names" QFTOther
229
     (nicAggDescPrefix ++ "name"),
230
     FieldSimple (rsNormal . map (MaybeForJSON . nicName) . instNics),
231
     QffNormal)
232
  , (FieldDefinition "nic.uuids" "NIC_UUIDs" QFTOther
233
     (nicAggDescPrefix ++ "UUID"),
234
     FieldSimple (rsNormal . map nicUuid . instNics), QffNormal)
235
  , (FieldDefinition "nic.modes" "NIC_modes" QFTOther
236
     (nicAggDescPrefix ++ "mode"),
237
     FieldConfig (\cfg -> rsNormal . map
238
       (nicpMode . fillNicParamsFromConfig cfg . nicNicparams)
239
       . instNics),
240
     QffNormal)
241
  , (FieldDefinition "nic.bridges" "NIC_bridges" QFTOther
242
     (nicAggDescPrefix ++ "bridge"),
243
     FieldConfig (\cfg -> rsNormal . map (MaybeForJSON . getNicBridge .
244
       fillNicParamsFromConfig cfg . nicNicparams) . instNics),
245
     QffNormal)
246
  , (FieldDefinition "nic.links" "NIC_links" QFTOther
247
     (nicAggDescPrefix ++ "link"),
248
     FieldConfig (\cfg -> rsNormal . map
249
       (nicpLink . fillNicParamsFromConfig cfg . nicNicparams)
250
       . instNics),
251
     QffNormal)
252
  , (FieldDefinition "nic.networks" "NIC_networks" QFTOther
253
     "List containing each interface's network",
254
     FieldSimple (rsNormal . map (MaybeForJSON . nicNetwork) . instNics),
255
     QffNormal)
256
  , (FieldDefinition "nic.networks.names" "NIC_networks_names" QFTOther
257
     "List containing the name of each interface's network",
258
     FieldConfig (\cfg -> rsNormal . map
259
       (\x -> MaybeForJSON (getNetworkName cfg <$> nicNetwork x))
260
       . instNics),
261
     QffNormal)
262
  ] ++
263

    
264
  -- Per-nic parameter fields
265
  instantiateIndexedFields C.maxNics
266
  [ (fieldDefinitionCompleter "nic.ip/%d" "NicIP/%d" QFTText
267
     ("IP address" ++ nicDescSuffix),
268
     getIndexedOptionalField instNics nicIp, QffNormal)
269
  , (fieldDefinitionCompleter "nic.uuid/%d" "NicUUID/%d" QFTText
270
     ("UUID address" ++ nicDescSuffix),
271
     getIndexedField instNics nicUuid, QffNormal)
272
  , (fieldDefinitionCompleter "nic.mac/%d" "NicMAC/%d" QFTText
273
     ("MAC address" ++ nicDescSuffix),
274
     getIndexedField instNics nicMac, QffNormal)
275
  , (fieldDefinitionCompleter "nic.name/%d" "NicName/%d" QFTText
276
     ("Name address" ++ nicDescSuffix),
277
     getIndexedOptionalField instNics nicName, QffNormal)
278
  , (fieldDefinitionCompleter "nic.network/%d" "NicNetwork/%d" QFTText
279
     ("Network" ++ nicDescSuffix),
280
     getIndexedOptionalField instNics nicNetwork, QffNormal)
281
  , (fieldDefinitionCompleter "nic.mode/%d" "NicMode/%d" QFTText
282
     ("Mode" ++ nicDescSuffix),
283
     getIndexedNicField nicpMode, QffNormal)
284
  , (fieldDefinitionCompleter "nic.link/%d" "NicLink/%d" QFTText
285
     ("Link" ++ nicDescSuffix),
286
     getIndexedNicField nicpLink, QffNormal)
287
  , (fieldDefinitionCompleter "nic.network.name/%d" "NicNetworkName/%d" QFTText
288
     ("Network name" ++ nicDescSuffix),
289
     getIndexedNicNetworkNameField, QffNormal)
290
  , (fieldDefinitionCompleter "nic.bridge/%d" "NicBridge/%d" QFTText
291
     ("Bridge" ++ nicDescSuffix),
292
     getOptionalIndexedNicField getNicBridge, QffNormal)
293
  ] ++
294

    
295
  -- Live fields using special getters
296
  [ (FieldDefinition "status" "Status" QFTText
297
     statusDocText,
298
     FieldConfigRuntime statusExtract, QffNormal)
299
  , (FieldDefinition "oper_state" "Running" QFTBool
300
     "Actual state of instance",
301
     FieldRuntime operStatusExtract, QffNormal),
302

    
303
    (FieldDefinition "console" "Console" QFTOther
304
     "Instance console information",
305
     FieldRuntime consoleExtract, QffNormal)
306
  ] ++
307

    
308
  -- Simple live fields
309
  map instanceLiveFieldBuilder instanceLiveFieldsDefs ++
310

    
311
  -- Common fields
312
  timeStampFields ++
313
  serialFields "Instance" ++
314
  uuidFields "Instance" ++
315
  tagsFields
316

    
317
-- * Helper functions for node property retrieval
318

    
319
-- | Constant suffix of network interface field descriptions.
320
nicDescSuffix ::String
321
nicDescSuffix = " of %s network interface"
322

    
323
-- | Almost-constant suffix of aggregate network interface field descriptions.
324
nicAggDescPrefix ::String
325
nicAggDescPrefix = "List containing each network interface's "
326

    
327
-- | Given a network name id, returns the network's name.
328
getNetworkName :: ConfigData -> String -> NonEmptyString
329
getNetworkName cfg = networkName . (Map.!) (fromContainer $ configNetworks cfg)
330

    
331
-- | Gets the bridge of a NIC.
332
getNicBridge :: FilledNicParams -> Maybe String
333
getNicBridge nicParams
334
  | nicpMode nicParams == NMBridged = Just $ nicpLink nicParams
335
  | otherwise                       = Nothing
336

    
337
-- | Fill partial NIC params by using the defaults from the configuration.
338
fillNicParamsFromConfig :: ConfigData -> PartialNicParams -> FilledNicParams
339
fillNicParamsFromConfig cfg = fillNicParams (getDefaultNicParams cfg)
340

    
341
-- | Retrieves the default network interface parameters.
342
getDefaultNicParams :: ConfigData -> FilledNicParams
343
getDefaultNicParams cfg =
344
  (Map.!) (fromContainer . clusterNicparams . configCluster $ cfg) C.ppDefault
345

    
346
-- | Returns a field that retrieves a given NIC's network name.
347
getIndexedNicNetworkNameField :: Int -> FieldGetter Instance Runtime
348
getIndexedNicNetworkNameField index =
349
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
350
    nicObj <- maybeAt index $ instNics inst
351
    nicNetworkId <- nicNetwork nicObj
352
    return $ getNetworkName cfg nicNetworkId)
353

    
354
-- | Gets a fillable NIC field.
355
getIndexedNicField :: (J.JSON a)
356
                   => (FilledNicParams -> a)
357
                   -> Int
358
                   -> FieldGetter Instance Runtime
359
getIndexedNicField getter =
360
  getOptionalIndexedNicField (\x -> Just . getter $ x)
361

    
362
-- | Gets an optional fillable NIC field.
363
getOptionalIndexedNicField :: (J.JSON a)
364
                           => (FilledNicParams -> Maybe a)
365
                           -> Int
366
                           -> FieldGetter Instance Runtime
367
getOptionalIndexedNicField =
368
  getIndexedFieldWithDefault
369
    (map nicNicparams . instNics) (\x _ -> getDefaultNicParams x) fillNicParams
370

    
371
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
372
-- for fields that should be filled out through the use of a default.
373
getIndexedFieldWithDefault :: (J.JSON c)
374
  => (Instance -> [a])             -- ^ Extracts a list of incomplete objects
375
  -> (ConfigData -> Instance -> b) -- ^ Extracts the default object
376
  -> (b -> a -> b)                 -- ^ Fills the default object
377
  -> (b -> Maybe c)                -- ^ Extracts an obj property
378
  -> Int                           -- ^ Index in list to use
379
  -> FieldGetter Instance Runtime  -- ^ Result
380
getIndexedFieldWithDefault
381
  listGetter defaultGetter fillFn propertyGetter index =
382
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
383
                              incompleteObj <- maybeAt index $ listGetter inst
384
                              let defaultObj = defaultGetter cfg inst
385
                                  completeObj = fillFn defaultObj incompleteObj
386
                              propertyGetter completeObj)
387

    
388
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
389
-- for fields that may not return a value, expressed through the Maybe monad.
390
getIndexedOptionalField :: (J.JSON b)
391
                        => (Instance -> [a]) -- ^ Extracts a list of objects
392
                        -> (a -> Maybe b)    -- ^ Possibly gets a property
393
                                             -- from an object
394
                        -> Int               -- ^ Index in list to use
395
                        -> FieldGetter Instance Runtime -- ^ Result
396
getIndexedOptionalField extractor optPropertyGetter index =
397
  FieldSimple(\inst -> rsMaybeUnavail $ do
398
                         obj <- maybeAt index $ extractor inst
399
                         optPropertyGetter obj)
400

    
401
-- | Creates a function which produces a 'FieldGetter' when fed an index.
402
-- Works only for fields that surely return a value.
403
getIndexedField :: (J.JSON b)
404
                => (Instance -> [a]) -- ^ Extracts a list of objects
405
                -> (a -> b)          -- ^ Gets a property from an object
406
                -> Int               -- ^ Index in list to use
407
                -> FieldGetter Instance Runtime -- ^ Result
408
getIndexedField extractor propertyGetter index =
409
  let optPropertyGetter = Just . propertyGetter
410
  in getIndexedOptionalField extractor optPropertyGetter index
411

    
412
-- | Retrieves a value from an array at an index, using the Maybe monad to
413
-- indicate failure.
414
maybeAt :: Int -> [a] -> Maybe a
415
maybeAt index list
416
  | index >= length list = Nothing
417
  | otherwise            = Just $ list !! index
418

    
419
-- | Primed with format strings for everything but the type, it consumes two
420
-- values and uses them to complete the FieldDefinition.
421
-- Warning: a bit unsafe as it uses printf. Handle with care.
422
fieldDefinitionCompleter :: (PrintfArg t1) => (PrintfArg t2)
423
                         => FieldName
424
                         -> FieldTitle
425
                         -> FieldType
426
                         -> FieldDoc
427
                         -> t1
428
                         -> t2
429
                         -> FieldDefinition
430
fieldDefinitionCompleter fName fTitle fType fDoc firstVal secondVal =
431
  FieldDefinition (printf fName firstVal)
432
                  (printf fTitle firstVal)
433
                  fType
434
                  (printf fDoc secondVal)
435

    
436
-- | Given an incomplete field definition and values that can complete it,
437
-- return a fully functional FieldData. Cannot work for all cases, should be
438
-- extended as necessary.
439
fillIncompleteFields :: (t1 -> t2 -> FieldDefinition,
440
                         t1 -> FieldGetter a b,
441
                         QffMode)
442
                     -> t1
443
                     -> t2
444
                     -> FieldData a b
445
fillIncompleteFields (iDef, iGet, mode) firstVal secondVal =
446
  (iDef firstVal secondVal, iGet firstVal, mode)
447

    
448
-- | Given indexed fields that describe lists, complete / instantiate them for
449
-- a given list size.
450
instantiateIndexedFields :: (Show t1, Integral t1)
451
                         => Int            -- ^ The size of the list
452
                         -> [(t1 -> String -> FieldDefinition,
453
                              t1 -> FieldGetter a b,
454
                              QffMode)]    -- ^ The indexed fields
455
                         -> FieldList a b  -- ^ A list of complete fields
456
instantiateIndexedFields listSize fields = do
457
  index <- take listSize [0..]
458
  field <- fields
459
  return . fillIncompleteFields field index . formatOrdinal $ index + 1
460

    
461
-- * Various helper functions for property retrieval
462

    
463
-- | Helper function for primary node retrieval
464
getPrimaryNode :: ConfigData -> Instance -> ErrorResult Node
465
getPrimaryNode cfg = getInstPrimaryNode cfg . instName
466

    
467
-- | Get primary node hostname
468
getPrimaryNodeName :: ConfigData -> Instance -> ResultEntry
469
getPrimaryNodeName cfg inst =
470
  rsErrorNoData $ nodeName <$> getPrimaryNode cfg inst
471

    
472
-- | Get primary node group
473
getPrimaryNodeGroup :: ConfigData -> Instance -> ErrorResult NodeGroup
474
getPrimaryNodeGroup cfg inst = do
475
  pNode <- getPrimaryNode cfg inst
476
  maybeToError "Configuration missing" $ getGroupOfNode cfg pNode
477

    
478
-- | Get primary node group name
479
getPrimaryNodeGroupName :: ConfigData -> Instance -> ResultEntry
480
getPrimaryNodeGroupName cfg inst =
481
  rsErrorNoData $ groupName <$> getPrimaryNodeGroup cfg inst
482

    
483
-- | Get primary node group uuid
484
getPrimaryNodeGroupUuid :: ConfigData -> Instance -> ResultEntry
485
getPrimaryNodeGroupUuid cfg inst =
486
  rsErrorNoData $ groupUuid <$> getPrimaryNodeGroup cfg inst
487

    
488
-- | Get secondary nodes - the configuration objects themselves
489
getSecondaryNodes :: ConfigData -> Instance -> ErrorResult [Node]
490
getSecondaryNodes cfg inst = do
491
  pNode <- getPrimaryNode cfg inst
492
  allNodes <- getInstAllNodes cfg $ instName inst
493
  return $ delete pNode allNodes
494

    
495
-- | Get attributes of the secondary nodes
496
getSecondaryNodeAttribute :: (J.JSON a)
497
                          => (Node -> a)
498
                          -> ConfigData
499
                          -> Instance
500
                          -> ResultEntry
501
getSecondaryNodeAttribute getter cfg inst =
502
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodes cfg inst
503

    
504
-- | Get secondary node groups
505
getSecondaryNodeGroups :: ConfigData -> Instance -> ErrorResult [NodeGroup]
506
getSecondaryNodeGroups cfg inst = do
507
  sNodes <- getSecondaryNodes cfg inst
508
  return . catMaybes $ map (getGroupOfNode cfg) sNodes
509

    
510
-- | Get attributes of secondary node groups
511
getSecondaryNodeGroupAttribute :: (J.JSON a)
512
                               => (NodeGroup -> a)
513
                               -> ConfigData
514
                               -> Instance
515
                               -> ResultEntry
516
getSecondaryNodeGroupAttribute getter cfg inst =
517
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodeGroups cfg inst
518

    
519
-- | Beparam getter builder: given a field, it returns a FieldConfig
520
-- getter, that is a function that takes the config and the object and
521
-- returns the Beparam field specified when the getter was built.
522
beParamGetter :: String       -- ^ The field we are building the getter for
523
              -> ConfigData   -- ^ The configuration object
524
              -> Instance     -- ^ The instance configuration object
525
              -> ResultEntry  -- ^ The result
526
beParamGetter field config inst =
527
  case getFilledInstBeParams config inst of
528
    Ok beParams -> dictFieldGetter field $ Just beParams
529
    Bad       _ -> rsNoData
530

    
531
-- | Hvparam getter builder: given a field, it returns a FieldConfig
532
-- getter, that is a function that takes the config and the object and
533
-- returns the Hvparam field specified when the getter was built.
534
hvParamGetter :: String -- ^ The field we're building the getter for
535
              -> ConfigData -> Instance -> ResultEntry
536
hvParamGetter field cfg inst =
537
  rsMaybeUnavail . Map.lookup field . fromContainer $
538
    getFilledInstHvParams (C.toList C.hvcGlobals) cfg inst
539

    
540
-- * Live fields functionality
541

    
542
-- | List of node live fields.
543
instanceLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
544
instanceLiveFieldsDefs =
545
  [ ("oper_ram", "Memory", QFTUnit, "oper_ram",
546
     "Actual memory usage as seen by hypervisor")
547
  , ("oper_vcpus", "VCPUs", QFTNumber, "oper_vcpus",
548
     "Actual number of VCPUs as seen by hypervisor")
549
  ]
550

    
551
-- | Map each name to a function that extracts that value from the RPC result.
552
instanceLiveFieldExtract :: FieldName -> InstanceInfo -> Instance -> J.JSValue
553
instanceLiveFieldExtract "oper_ram"   info _ = J.showJSON $ instInfoMemory info
554
instanceLiveFieldExtract "oper_vcpus" info _ = J.showJSON $ instInfoVcpus info
555
instanceLiveFieldExtract n _ _ = J.showJSON $
556
  "The field " ++ n ++ " is not an expected or extractable live field!"
557

    
558
-- | Helper for extracting an instance live field from the RPC results.
559
instanceLiveRpcCall :: FieldName -> Runtime -> Instance -> ResultEntry
560
instanceLiveRpcCall fname (Right (Just (res, _), _)) inst =
561
  case instanceLiveFieldExtract fname res inst of
562
    J.JSNull -> rsNoData
563
    x        -> rsNormal x
564
instanceLiveRpcCall _ (Right (Nothing, _)) _ = rsUnavail
565
instanceLiveRpcCall _ (Left err) _ =
566
  ResultEntry (rpcErrorToStatus err) Nothing
567

    
568
-- | Builder for node live fields.
569
instanceLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
570
                         -> FieldData Instance Runtime
571
instanceLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
572
  ( FieldDefinition fname ftitle ftype fdoc
573
  , FieldRuntime $ instanceLiveRpcCall fname
574
  , QffNormal)
575

    
576
-- * Functionality related to status and operational status extraction
577

    
578
-- | The documentation text for the instance status field
579
statusDocText :: String
580
statusDocText =
581
  let si = show . instanceStatusToRaw :: InstanceStatus -> String
582
  in  "Instance status; " ++
583
      si Running ++
584
      " if instance is set to be running and actually is, " ++
585
      si StatusDown ++
586
      " if instance is stopped and is not running, " ++
587
      si WrongNode ++
588
      " if instance running, but not on its designated primary node, " ++
589
      si ErrorUp ++
590
      " if instance should be stopped, but is actually running, " ++
591
      si ErrorDown ++
592
      " if instance should run, but doesn't, " ++
593
      si NodeDown ++
594
      " if instance's primary node is down, " ++
595
      si NodeOffline ++
596
      " if instance's primary node is marked offline, " ++
597
      si StatusOffline ++
598
      " if instance is offline and does not use dynamic resources"
599

    
600
-- | Checks if the primary node of an instance is offline
601
isPrimaryOffline :: ConfigData -> Instance -> Bool
602
isPrimaryOffline cfg inst =
603
  let pNodeResult = getNode cfg $ instPrimaryNode inst
604
  in case pNodeResult of
605
     Ok pNode -> nodeOffline pNode
606
     Bad    _ -> error "Programmer error - result assumed to be OK is Bad!"
607

    
608
-- | Determines the status of a live instance
609
liveInstanceStatus :: (InstanceInfo, Bool) -> Instance -> InstanceStatus
610
liveInstanceStatus (_, foundOnPrimary) inst
611
  | not foundOnPrimary    = WrongNode
612
  | adminState == AdminUp = Running
613
  | otherwise             = ErrorUp
614
  where adminState = instAdminState inst
615

    
616
-- | Determines the status of a dead instance.
617
deadInstanceStatus :: Instance -> InstanceStatus
618
deadInstanceStatus inst =
619
  case instAdminState inst of
620
    AdminUp      -> ErrorDown
621
    AdminDown    -> StatusDown
622
    AdminOffline -> StatusOffline
623

    
624
-- | Determines the status of the instance, depending on whether it is possible
625
-- to communicate with its primary node, on which node it is, and its
626
-- configuration.
627
determineInstanceStatus :: ConfigData      -- ^ The configuration data
628
                        -> Runtime         -- ^ All the data from the live call
629
                        -> Instance        -- ^ Static instance configuration
630
                        -> InstanceStatus  -- ^ Result
631
determineInstanceStatus cfg res inst
632
  | isPrimaryOffline cfg inst = NodeOffline
633
  | otherwise = case res of
634
      Left _                   -> NodeDown
635
      Right (Just liveData, _) -> liveInstanceStatus liveData inst
636
      Right (Nothing, _)       -> deadInstanceStatus inst
637

    
638
-- | Extracts the instance status, retrieving it using the functions above and
639
-- transforming it into a 'ResultEntry'.
640
statusExtract :: ConfigData -> Runtime -> Instance -> ResultEntry
641
statusExtract cfg res inst =
642
  rsNormal . J.showJSON . instanceStatusToRaw $
643
    determineInstanceStatus cfg res inst
644

    
645
-- | Extracts the operational status of the instance.
646
operStatusExtract :: Runtime -> Instance -> ResultEntry
647
operStatusExtract res _ =
648
  rsMaybeNoData $ J.showJSON <$>
649
    case res of
650
      Left _       -> Nothing
651
      Right (x, _) -> Just $ isJust x
652

    
653
-- | Extracts the console connection information
654
consoleExtract :: Runtime -> Instance -> ResultEntry
655
consoleExtract (Left err) _ = ResultEntry (rpcErrorToStatus err) Nothing
656
consoleExtract (Right (_, val)) _ = rsMaybeNoData val
657

    
658
-- * Helper functions extracting information as necessary for the generic query
659
-- interfaces
660

    
661
-- | This function checks if a node with a given uuid has experienced an error
662
-- or not.
663
checkForNodeError :: [(String, ERpcError a)]
664
                  -> String
665
                  -> Maybe RpcError
666
checkForNodeError uuidList uuid =
667
  case snd <$> pickPairUnique uuid uuidList of
668
    Just (Left err) -> Just err
669
    Just (Right _)  -> Nothing
670
    Nothing         -> Just . RpcResultError $
671
                         "Node response not present"
672

    
673
-- | Finds information about the instance in the info delivered by a node
674
findInfoInNodeResult :: Instance
675
                     -> ERpcError RpcResultAllInstancesInfo
676
                     -> Maybe InstanceInfo
677
findInfoInNodeResult inst nodeResponse =
678
  case nodeResponse of
679
    Left  _err    -> Nothing
680
    Right allInfo ->
681
      let instances = rpcResAllInstInfoInstances allInfo
682
          maybeMatch = pickPairUnique (instName inst) instances
683
      in snd <$> maybeMatch
684

    
685
-- | Retrieves the instance information if it is present anywhere in the all
686
-- instances RPC result. Notes if it originates from the primary node.
687
-- An error is delivered if there is no result, and the primary node is down.
688
getInstanceInfo :: [(String, ERpcError RpcResultAllInstancesInfo)]
689
                -> Instance
690
                -> ERpcError (Maybe (InstanceInfo, Bool))
691
getInstanceInfo uuidList inst =
692
  let pNodeUuid = instPrimaryNode inst
693
      primarySearchResult =
694
        pickPairUnique pNodeUuid uuidList >>= findInfoInNodeResult inst . snd
695
  in case primarySearchResult of
696
       Just instInfo -> Right . Just $ (instInfo, True)
697
       Nothing       ->
698
         let allSearchResult =
699
               getFirst . mconcat $ map
700
               (First . findInfoInNodeResult inst . snd) uuidList
701
         in case allSearchResult of
702
              Just instInfo -> Right . Just $ (instInfo, False)
703
              Nothing       ->
704
                case checkForNodeError uuidList pNodeUuid of
705
                  Just err -> Left err
706
                  Nothing  -> Right Nothing
707

    
708
-- | Retrieves the console information if present anywhere in the given results
709
getConsoleInfo :: [(String, ERpcError RpcResultInstanceConsoleInfo)]
710
               -> Instance
711
               -> Maybe InstanceConsoleInfo
712
getConsoleInfo uuidList inst =
713
  let allValidResults = concatMap rpcResInstConsInfoInstancesInfo .
714
                        rights . map snd $ uuidList
715
  in snd <$> pickPairUnique (instName inst) allValidResults
716

    
717
-- | Extracts all the live information that can be extracted.
718
extractLiveInfo :: [(Node, ERpcError RpcResultAllInstancesInfo)]
719
                -> [(Node, ERpcError RpcResultInstanceConsoleInfo)]
720
                -> Instance
721
                -> Runtime
722
extractLiveInfo nodeResultList nodeConsoleList inst =
723
  let uuidConvert     = map (\(x, y) -> (nodeUuid x, y))
724
      uuidResultList  = uuidConvert nodeResultList
725
      uuidConsoleList = uuidConvert nodeConsoleList
726
  in case getInstanceInfo uuidResultList inst of
727
    -- If we can't get the instance info, we can't get the console info either.
728
    -- Best to propagate the error further.
729
    Left err  -> Left err
730
    Right res -> Right (res, getConsoleInfo uuidConsoleList inst)
731

    
732
-- | Retrieves all the parameters for the console calls.
733
getAllConsoleParams :: ConfigData
734
                    -> [Instance]
735
                    -> ErrorResult [InstanceConsoleInfoParams]
736
getAllConsoleParams cfg = mapM $ \i ->
737
  InstanceConsoleInfoParams i
738
    <$> getPrimaryNode cfg i
739
    <*> pure (getFilledInstHvParams [] cfg i)
740
    <*> getFilledInstBeParams cfg i
741

    
742
-- | Compares two params according to their node, needed for grouping.
743
compareParamsByNode :: InstanceConsoleInfoParams
744
                    -> InstanceConsoleInfoParams
745
                    -> Bool
746
compareParamsByNode x y = instConsInfoParamsNode x == instConsInfoParamsNode y
747

    
748
-- | Groups instance information calls heading out to the same nodes.
749
consoleParamsToCalls :: [InstanceConsoleInfoParams]
750
                     -> [(Node, RpcCallInstanceConsoleInfo)]
751
consoleParamsToCalls params =
752
  let sortedParams = sortBy
753
        (comparing (instPrimaryNode . instConsInfoParamsInstance)) params
754
      groupedParams = groupBy compareParamsByNode sortedParams
755
  in map (\x -> case x of
756
            [] -> error "Programmer error: group must have one or more members"
757
            paramGroup@(y:_) ->
758
              let node = instConsInfoParamsNode y
759
                  packer z = (instName $ instConsInfoParamsInstance z, z)
760
              in (node, RpcCallInstanceConsoleInfo . map packer $ paramGroup)
761
         ) groupedParams
762

    
763
-- | Retrieves a list of all the hypervisors and params used by the given
764
-- instances.
765
getHypervisorSpecs :: ConfigData -> [Instance] -> [(Hypervisor, HvParams)]
766
getHypervisorSpecs cfg instances =
767
  let hvs = nub . map instHypervisor $ instances
768
      hvParamMap = (fromContainer . clusterHvparams . configCluster $ cfg)
769
  in zip hvs . map ((Map.!) hvParamMap . hypervisorToRaw) $ hvs
770

    
771
-- | Collect live data from RPC query if enabled.
772
collectLiveData :: Bool        -- ^ Live queries allowed
773
                -> ConfigData  -- ^ The cluster config
774
                -> [String]    -- ^ The requested fields
775
                -> [Instance]  -- ^ The instance objects
776
                -> IO [(Instance, Runtime)]
777
collectLiveData liveDataEnabled cfg fields instances
778
  | not liveDataEnabled = return . zip instances . repeat . Left .
779
                            RpcResultError $ "Live data disabled"
780
  | otherwise = do
781
      let hvSpecs = getHypervisorSpecs cfg instances
782
          instanceNodes = nub . justOk $
783
                            map (getNode cfg . instPrimaryNode) instances
784
          goodNodes = nodesWithValidConfig cfg instanceNodes
785
      instInfoRes <- executeRpcCall goodNodes (RpcCallAllInstancesInfo hvSpecs)
786
      consInfoRes <-
787
        if "console" `elem` fields
788
          then case getAllConsoleParams cfg instances of
789
            Ok  p -> executeRpcCalls $ consoleParamsToCalls p
790
            Bad _ -> return . zip goodNodes . repeat . Left $
791
              RpcResultError "Cannot construct parameters for console info call"
792
          else return [] -- The information is not necessary
793
      return . zip instances .
794
        map (extractLiveInfo instInfoRes consInfoRes) $ instances