Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Instance.hs @ 32933325

History | View | Annotate | Download (34 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.vlans" "NIC_VLANs" QFTOther
242
     (nicAggDescPrefix ++ "VLAN"),
243
     FieldConfig (\cfg -> rsNormal . map (MaybeForJSON . getNicVlan .
244
       fillNicParamsFromConfig cfg . nicNicparams) . instNics),
245
     QffNormal)
246
  , (FieldDefinition "nic.bridges" "NIC_bridges" QFTOther
247
     (nicAggDescPrefix ++ "bridge"),
248
     FieldConfig (\cfg -> rsNormal . map (MaybeForJSON . getNicBridge .
249
       fillNicParamsFromConfig cfg . nicNicparams) . instNics),
250
     QffNormal)
251
  , (FieldDefinition "nic.links" "NIC_links" QFTOther
252
     (nicAggDescPrefix ++ "link"),
253
     FieldConfig (\cfg -> rsNormal . map
254
       (nicpLink . fillNicParamsFromConfig cfg . nicNicparams)
255
       . instNics),
256
     QffNormal)
257
  , (FieldDefinition "nic.networks" "NIC_networks" QFTOther
258
     "List containing each interface's network",
259
     FieldSimple (rsNormal . map (MaybeForJSON . nicNetwork) . instNics),
260
     QffNormal)
261
  , (FieldDefinition "nic.networks.names" "NIC_networks_names" QFTOther
262
     "List containing the name of each interface's network",
263
     FieldConfig (\cfg -> rsNormal . map
264
       (\x -> MaybeForJSON (getNetworkName cfg <$> nicNetwork x))
265
       . instNics),
266
     QffNormal)
267
  ] ++
268

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

    
303
  -- Live fields using special getters
304
  [ (FieldDefinition "status" "Status" QFTText
305
     statusDocText,
306
     FieldConfigRuntime statusExtract, QffNormal)
307
  , (FieldDefinition "oper_state" "Running" QFTBool
308
     "Actual state of instance",
309
     FieldRuntime operStatusExtract, QffNormal),
310

    
311
    (FieldDefinition "console" "Console" QFTOther
312
     "Instance console information",
313
     FieldRuntime consoleExtract, QffNormal)
314
  ] ++
315

    
316
  -- Simple live fields
317
  map instanceLiveFieldBuilder instanceLiveFieldsDefs ++
318

    
319
  -- Common fields
320
  timeStampFields ++
321
  serialFields "Instance" ++
322
  uuidFields "Instance" ++
323
  tagsFields
324

    
325
-- * Helper functions for node property retrieval
326

    
327
-- | Constant suffix of network interface field descriptions.
328
nicDescSuffix ::String
329
nicDescSuffix = " of %s network interface"
330

    
331
-- | Almost-constant suffix of aggregate network interface field descriptions.
332
nicAggDescPrefix ::String
333
nicAggDescPrefix = "List containing each network interface's "
334

    
335
-- | Given a network name id, returns the network's name.
336
getNetworkName :: ConfigData -> String -> NonEmptyString
337
getNetworkName cfg = networkName . (Map.!) (fromContainer $ configNetworks cfg)
338

    
339
-- | Gets the bridge of a NIC.
340
getNicBridge :: FilledNicParams -> Maybe String
341
getNicBridge nicParams
342
  | nicpMode nicParams == NMBridged = Just $ nicpLink nicParams
343
  | otherwise                       = Nothing
344

    
345
-- | Gets the VLAN of a NIC.
346
getNicVlan :: FilledNicParams -> Maybe String
347
getNicVlan params
348
  | nicpMode params == NMOvs = Just $ nicpVlan params
349
  | otherwise                = Nothing
350

    
351
-- | Fill partial NIC params by using the defaults from the configuration.
352
fillNicParamsFromConfig :: ConfigData -> PartialNicParams -> FilledNicParams
353
fillNicParamsFromConfig cfg = fillNicParams (getDefaultNicParams cfg)
354

    
355
-- | Retrieves the default network interface parameters.
356
getDefaultNicParams :: ConfigData -> FilledNicParams
357
getDefaultNicParams cfg =
358
  (Map.!) (fromContainer . clusterNicparams . configCluster $ cfg) C.ppDefault
359

    
360
-- | Returns a field that retrieves a given NIC's network name.
361
getIndexedNicNetworkNameField :: Int -> FieldGetter Instance Runtime
362
getIndexedNicNetworkNameField index =
363
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
364
    nicObj <- maybeAt index $ instNics inst
365
    nicNetworkId <- nicNetwork nicObj
366
    return $ getNetworkName cfg nicNetworkId)
367

    
368
-- | Gets a fillable NIC field.
369
getIndexedNicField :: (J.JSON a)
370
                   => (FilledNicParams -> a)
371
                   -> Int
372
                   -> FieldGetter Instance Runtime
373
getIndexedNicField getter =
374
  getOptionalIndexedNicField (\x -> Just . getter $ x)
375

    
376
-- | Gets an optional fillable NIC field.
377
getOptionalIndexedNicField :: (J.JSON a)
378
                           => (FilledNicParams -> Maybe a)
379
                           -> Int
380
                           -> FieldGetter Instance Runtime
381
getOptionalIndexedNicField =
382
  getIndexedFieldWithDefault
383
    (map nicNicparams . instNics) (\x _ -> getDefaultNicParams x) fillNicParams
384

    
385
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
386
-- for fields that should be filled out through the use of a default.
387
getIndexedFieldWithDefault :: (J.JSON c)
388
  => (Instance -> [a])             -- ^ Extracts a list of incomplete objects
389
  -> (ConfigData -> Instance -> b) -- ^ Extracts the default object
390
  -> (b -> a -> b)                 -- ^ Fills the default object
391
  -> (b -> Maybe c)                -- ^ Extracts an obj property
392
  -> Int                           -- ^ Index in list to use
393
  -> FieldGetter Instance Runtime  -- ^ Result
394
getIndexedFieldWithDefault
395
  listGetter defaultGetter fillFn propertyGetter index =
396
  FieldConfig (\cfg inst -> rsMaybeUnavail $ do
397
                              incompleteObj <- maybeAt index $ listGetter inst
398
                              let defaultObj = defaultGetter cfg inst
399
                                  completeObj = fillFn defaultObj incompleteObj
400
                              propertyGetter completeObj)
401

    
402
-- | Creates a function which produces a 'FieldGetter' when fed an index. Works
403
-- for fields that may not return a value, expressed through the Maybe monad.
404
getIndexedOptionalField :: (J.JSON b)
405
                        => (Instance -> [a]) -- ^ Extracts a list of objects
406
                        -> (a -> Maybe b)    -- ^ Possibly gets a property
407
                                             -- from an object
408
                        -> Int               -- ^ Index in list to use
409
                        -> FieldGetter Instance Runtime -- ^ Result
410
getIndexedOptionalField extractor optPropertyGetter index =
411
  FieldSimple(\inst -> rsMaybeUnavail $ do
412
                         obj <- maybeAt index $ extractor inst
413
                         optPropertyGetter obj)
414

    
415
-- | Creates a function which produces a 'FieldGetter' when fed an index.
416
-- Works only for fields that surely return a value.
417
getIndexedField :: (J.JSON b)
418
                => (Instance -> [a]) -- ^ Extracts a list of objects
419
                -> (a -> b)          -- ^ Gets a property from an object
420
                -> Int               -- ^ Index in list to use
421
                -> FieldGetter Instance Runtime -- ^ Result
422
getIndexedField extractor propertyGetter index =
423
  let optPropertyGetter = Just . propertyGetter
424
  in getIndexedOptionalField extractor optPropertyGetter index
425

    
426
-- | Retrieves a value from an array at an index, using the Maybe monad to
427
-- indicate failure.
428
maybeAt :: Int -> [a] -> Maybe a
429
maybeAt index list
430
  | index >= length list = Nothing
431
  | otherwise            = Just $ list !! index
432

    
433
-- | Primed with format strings for everything but the type, it consumes two
434
-- values and uses them to complete the FieldDefinition.
435
-- Warning: a bit unsafe as it uses printf. Handle with care.
436
fieldDefinitionCompleter :: (PrintfArg t1) => (PrintfArg t2)
437
                         => FieldName
438
                         -> FieldTitle
439
                         -> FieldType
440
                         -> FieldDoc
441
                         -> t1
442
                         -> t2
443
                         -> FieldDefinition
444
fieldDefinitionCompleter fName fTitle fType fDoc firstVal secondVal =
445
  FieldDefinition (printf fName firstVal)
446
                  (printf fTitle firstVal)
447
                  fType
448
                  (printf fDoc secondVal)
449

    
450
-- | Given an incomplete field definition and values that can complete it,
451
-- return a fully functional FieldData. Cannot work for all cases, should be
452
-- extended as necessary.
453
fillIncompleteFields :: (t1 -> t2 -> FieldDefinition,
454
                         t1 -> FieldGetter a b,
455
                         QffMode)
456
                     -> t1
457
                     -> t2
458
                     -> FieldData a b
459
fillIncompleteFields (iDef, iGet, mode) firstVal secondVal =
460
  (iDef firstVal secondVal, iGet firstVal, mode)
461

    
462
-- | Given indexed fields that describe lists, complete / instantiate them for
463
-- a given list size.
464
instantiateIndexedFields :: (Show t1, Integral t1)
465
                         => Int            -- ^ The size of the list
466
                         -> [(t1 -> String -> FieldDefinition,
467
                              t1 -> FieldGetter a b,
468
                              QffMode)]    -- ^ The indexed fields
469
                         -> FieldList a b  -- ^ A list of complete fields
470
instantiateIndexedFields listSize fields = do
471
  index <- take listSize [0..]
472
  field <- fields
473
  return . fillIncompleteFields field index . formatOrdinal $ index + 1
474

    
475
-- * Various helper functions for property retrieval
476

    
477
-- | Helper function for primary node retrieval
478
getPrimaryNode :: ConfigData -> Instance -> ErrorResult Node
479
getPrimaryNode cfg = getInstPrimaryNode cfg . instName
480

    
481
-- | Get primary node hostname
482
getPrimaryNodeName :: ConfigData -> Instance -> ResultEntry
483
getPrimaryNodeName cfg inst =
484
  rsErrorNoData $ nodeName <$> getPrimaryNode cfg inst
485

    
486
-- | Get primary node group
487
getPrimaryNodeGroup :: ConfigData -> Instance -> ErrorResult NodeGroup
488
getPrimaryNodeGroup cfg inst = do
489
  pNode <- getPrimaryNode cfg inst
490
  maybeToError "Configuration missing" $ getGroupOfNode cfg pNode
491

    
492
-- | Get primary node group name
493
getPrimaryNodeGroupName :: ConfigData -> Instance -> ResultEntry
494
getPrimaryNodeGroupName cfg inst =
495
  rsErrorNoData $ groupName <$> getPrimaryNodeGroup cfg inst
496

    
497
-- | Get primary node group uuid
498
getPrimaryNodeGroupUuid :: ConfigData -> Instance -> ResultEntry
499
getPrimaryNodeGroupUuid cfg inst =
500
  rsErrorNoData $ groupUuid <$> getPrimaryNodeGroup cfg inst
501

    
502
-- | Get secondary nodes - the configuration objects themselves
503
getSecondaryNodes :: ConfigData -> Instance -> ErrorResult [Node]
504
getSecondaryNodes cfg inst = do
505
  pNode <- getPrimaryNode cfg inst
506
  allNodes <- getInstAllNodes cfg $ instName inst
507
  return $ delete pNode allNodes
508

    
509
-- | Get attributes of the secondary nodes
510
getSecondaryNodeAttribute :: (J.JSON a)
511
                          => (Node -> a)
512
                          -> ConfigData
513
                          -> Instance
514
                          -> ResultEntry
515
getSecondaryNodeAttribute getter cfg inst =
516
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodes cfg inst
517

    
518
-- | Get secondary node groups
519
getSecondaryNodeGroups :: ConfigData -> Instance -> ErrorResult [NodeGroup]
520
getSecondaryNodeGroups cfg inst = do
521
  sNodes <- getSecondaryNodes cfg inst
522
  return . catMaybes $ map (getGroupOfNode cfg) sNodes
523

    
524
-- | Get attributes of secondary node groups
525
getSecondaryNodeGroupAttribute :: (J.JSON a)
526
                               => (NodeGroup -> a)
527
                               -> ConfigData
528
                               -> Instance
529
                               -> ResultEntry
530
getSecondaryNodeGroupAttribute getter cfg inst =
531
  rsErrorNoData $ map (J.showJSON . getter) <$> getSecondaryNodeGroups cfg inst
532

    
533
-- | Beparam getter builder: given a field, it returns a FieldConfig
534
-- getter, that is a function that takes the config and the object and
535
-- returns the Beparam field specified when the getter was built.
536
beParamGetter :: String       -- ^ The field we are building the getter for
537
              -> ConfigData   -- ^ The configuration object
538
              -> Instance     -- ^ The instance configuration object
539
              -> ResultEntry  -- ^ The result
540
beParamGetter field config inst =
541
  case getFilledInstBeParams config inst of
542
    Ok beParams -> dictFieldGetter field $ Just beParams
543
    Bad       _ -> rsNoData
544

    
545
-- | Hvparam getter builder: given a field, it returns a FieldConfig
546
-- getter, that is a function that takes the config and the object and
547
-- returns the Hvparam field specified when the getter was built.
548
hvParamGetter :: String -- ^ The field we're building the getter for
549
              -> ConfigData -> Instance -> ResultEntry
550
hvParamGetter field cfg inst =
551
  rsMaybeUnavail . Map.lookup field . fromContainer $
552
    getFilledInstHvParams (C.toList C.hvcGlobals) cfg inst
553

    
554
-- * Live fields functionality
555

    
556
-- | List of node live fields.
557
instanceLiveFieldsDefs :: [(FieldName, FieldTitle, FieldType, String, FieldDoc)]
558
instanceLiveFieldsDefs =
559
  [ ("oper_ram", "Memory", QFTUnit, "oper_ram",
560
     "Actual memory usage as seen by hypervisor")
561
  , ("oper_vcpus", "VCPUs", QFTNumber, "oper_vcpus",
562
     "Actual number of VCPUs as seen by hypervisor")
563
  ]
564

    
565
-- | Map each name to a function that extracts that value from the RPC result.
566
instanceLiveFieldExtract :: FieldName -> InstanceInfo -> Instance -> J.JSValue
567
instanceLiveFieldExtract "oper_ram"   info _ = J.showJSON $ instInfoMemory info
568
instanceLiveFieldExtract "oper_vcpus" info _ = J.showJSON $ instInfoVcpus info
569
instanceLiveFieldExtract n _ _ = J.showJSON $
570
  "The field " ++ n ++ " is not an expected or extractable live field!"
571

    
572
-- | Helper for extracting an instance live field from the RPC results.
573
instanceLiveRpcCall :: FieldName -> Runtime -> Instance -> ResultEntry
574
instanceLiveRpcCall fname (Right (Just (res, _), _)) inst =
575
  case instanceLiveFieldExtract fname res inst of
576
    J.JSNull -> rsNoData
577
    x        -> rsNormal x
578
instanceLiveRpcCall _ (Right (Nothing, _)) _ = rsUnavail
579
instanceLiveRpcCall _ (Left err) _ =
580
  ResultEntry (rpcErrorToStatus err) Nothing
581

    
582
-- | Builder for node live fields.
583
instanceLiveFieldBuilder :: (FieldName, FieldTitle, FieldType, String, FieldDoc)
584
                         -> FieldData Instance Runtime
585
instanceLiveFieldBuilder (fname, ftitle, ftype, _, fdoc) =
586
  ( FieldDefinition fname ftitle ftype fdoc
587
  , FieldRuntime $ instanceLiveRpcCall fname
588
  , QffNormal)
589

    
590
-- * Functionality related to status and operational status extraction
591

    
592
-- | The documentation text for the instance status field
593
statusDocText :: String
594
statusDocText =
595
  let si = show . instanceStatusToRaw :: InstanceStatus -> String
596
  in  "Instance status; " ++
597
      si Running ++
598
      " if instance is set to be running and actually is, " ++
599
      si StatusDown ++
600
      " if instance is stopped and is not running, " ++
601
      si WrongNode ++
602
      " if instance running, but not on its designated primary node, " ++
603
      si ErrorUp ++
604
      " if instance should be stopped, but is actually running, " ++
605
      si ErrorDown ++
606
      " if instance should run, but doesn't, " ++
607
      si NodeDown ++
608
      " if instance's primary node is down, " ++
609
      si NodeOffline ++
610
      " if instance's primary node is marked offline, " ++
611
      si StatusOffline ++
612
      " if instance is offline and does not use dynamic resources"
613

    
614
-- | Checks if the primary node of an instance is offline
615
isPrimaryOffline :: ConfigData -> Instance -> Bool
616
isPrimaryOffline cfg inst =
617
  let pNodeResult = getNode cfg $ instPrimaryNode inst
618
  in case pNodeResult of
619
     Ok pNode -> nodeOffline pNode
620
     Bad    _ -> error "Programmer error - result assumed to be OK is Bad!"
621

    
622
-- | Determines the status of a live instance
623
liveInstanceStatus :: (InstanceInfo, Bool) -> Instance -> InstanceStatus
624
liveInstanceStatus (instInfo, foundOnPrimary) inst
625
  | not foundOnPrimary = WrongNode
626
  | otherwise =
627
    case instanceState of
628
      InstanceStateRunning | adminState == AdminUp -> Running
629
                           | otherwise -> ErrorUp
630
      InstanceStateShutdown | adminState == AdminUp -> UserDown
631
                            | otherwise -> StatusDown
632
  where adminState = instAdminState inst
633
        instanceState = instInfoState instInfo
634

    
635
-- | Determines the status of a dead instance.
636
deadInstanceStatus :: Instance -> InstanceStatus
637
deadInstanceStatus inst =
638
  case instAdminState inst of
639
    AdminUp      -> ErrorDown
640
    AdminDown    -> StatusDown
641
    AdminOffline -> StatusOffline
642

    
643
-- | Determines the status of the instance, depending on whether it is possible
644
-- to communicate with its primary node, on which node it is, and its
645
-- configuration.
646
determineInstanceStatus :: ConfigData      -- ^ The configuration data
647
                        -> Runtime         -- ^ All the data from the live call
648
                        -> Instance        -- ^ Static instance configuration
649
                        -> InstanceStatus  -- ^ Result
650
determineInstanceStatus cfg res inst
651
  | isPrimaryOffline cfg inst = NodeOffline
652
  | otherwise = case res of
653
      Left _                   -> NodeDown
654
      Right (Just liveData, _) -> liveInstanceStatus liveData inst
655
      Right (Nothing, _)       -> deadInstanceStatus inst
656

    
657
-- | Extracts the instance status, retrieving it using the functions above and
658
-- transforming it into a 'ResultEntry'.
659
statusExtract :: ConfigData -> Runtime -> Instance -> ResultEntry
660
statusExtract cfg res inst =
661
  rsNormal . J.showJSON . instanceStatusToRaw $
662
    determineInstanceStatus cfg res inst
663

    
664
-- | Extracts the operational status of the instance.
665
operStatusExtract :: Runtime -> Instance -> ResultEntry
666
operStatusExtract res _ =
667
  rsMaybeNoData $ J.showJSON <$>
668
    case res of
669
      Left _       -> Nothing
670
      Right (x, _) -> Just $ isJust x
671

    
672
-- | Extracts the console connection information
673
consoleExtract :: Runtime -> Instance -> ResultEntry
674
consoleExtract (Left err) _ = ResultEntry (rpcErrorToStatus err) Nothing
675
consoleExtract (Right (_, val)) _ = rsMaybeNoData val
676

    
677
-- * Helper functions extracting information as necessary for the generic query
678
-- interfaces
679

    
680
-- | This function checks if a node with a given uuid has experienced an error
681
-- or not.
682
checkForNodeError :: [(String, ERpcError a)]
683
                  -> String
684
                  -> Maybe RpcError
685
checkForNodeError uuidList uuid =
686
  case snd <$> pickPairUnique uuid uuidList of
687
    Just (Left err) -> Just err
688
    Just (Right _)  -> Nothing
689
    Nothing         -> Just . RpcResultError $
690
                         "Node response not present"
691

    
692
-- | Finds information about the instance in the info delivered by a node
693
findInfoInNodeResult :: Instance
694
                     -> ERpcError RpcResultAllInstancesInfo
695
                     -> Maybe InstanceInfo
696
findInfoInNodeResult inst nodeResponse =
697
  case nodeResponse of
698
    Left  _err    -> Nothing
699
    Right allInfo ->
700
      let instances = rpcResAllInstInfoInstances allInfo
701
          maybeMatch = pickPairUnique (instName inst) instances
702
      in snd <$> maybeMatch
703

    
704
-- | Retrieves the instance information if it is present anywhere in the all
705
-- instances RPC result. Notes if it originates from the primary node.
706
-- An error is delivered if there is no result, and the primary node is down.
707
getInstanceInfo :: [(String, ERpcError RpcResultAllInstancesInfo)]
708
                -> Instance
709
                -> ERpcError (Maybe (InstanceInfo, Bool))
710
getInstanceInfo uuidList inst =
711
  let pNodeUuid = instPrimaryNode inst
712
      primarySearchResult =
713
        pickPairUnique pNodeUuid uuidList >>= findInfoInNodeResult inst . snd
714
  in case primarySearchResult of
715
       Just instInfo -> Right . Just $ (instInfo, True)
716
       Nothing       ->
717
         let allSearchResult =
718
               getFirst . mconcat $ map
719
               (First . findInfoInNodeResult inst . snd) uuidList
720
         in case allSearchResult of
721
              Just instInfo -> Right . Just $ (instInfo, False)
722
              Nothing       ->
723
                case checkForNodeError uuidList pNodeUuid of
724
                  Just err -> Left err
725
                  Nothing  -> Right Nothing
726

    
727
-- | Retrieves the console information if present anywhere in the given results
728
getConsoleInfo :: [(String, ERpcError RpcResultInstanceConsoleInfo)]
729
               -> Instance
730
               -> Maybe InstanceConsoleInfo
731
getConsoleInfo uuidList inst =
732
  let allValidResults = concatMap rpcResInstConsInfoInstancesInfo .
733
                        rights . map snd $ uuidList
734
  in snd <$> pickPairUnique (instName inst) allValidResults
735

    
736
-- | Extracts all the live information that can be extracted.
737
extractLiveInfo :: [(Node, ERpcError RpcResultAllInstancesInfo)]
738
                -> [(Node, ERpcError RpcResultInstanceConsoleInfo)]
739
                -> Instance
740
                -> Runtime
741
extractLiveInfo nodeResultList nodeConsoleList inst =
742
  let uuidConvert     = map (\(x, y) -> (nodeUuid x, y))
743
      uuidResultList  = uuidConvert nodeResultList
744
      uuidConsoleList = uuidConvert nodeConsoleList
745
  in case getInstanceInfo uuidResultList inst of
746
    -- If we can't get the instance info, we can't get the console info either.
747
    -- Best to propagate the error further.
748
    Left err  -> Left err
749
    Right res -> Right (res, getConsoleInfo uuidConsoleList inst)
750

    
751
-- | Retrieves all the parameters for the console calls.
752
getAllConsoleParams :: ConfigData
753
                    -> [Instance]
754
                    -> ErrorResult [InstanceConsoleInfoParams]
755
getAllConsoleParams cfg = mapM $ \i ->
756
  InstanceConsoleInfoParams i
757
    <$> getPrimaryNode cfg i
758
    <*> getPrimaryNodeGroup cfg i
759
    <*> pure (getFilledInstHvParams [] cfg i)
760
    <*> getFilledInstBeParams cfg i
761

    
762
-- | Compares two params according to their node, needed for grouping.
763
compareParamsByNode :: InstanceConsoleInfoParams
764
                    -> InstanceConsoleInfoParams
765
                    -> Bool
766
compareParamsByNode x y = instConsInfoParamsNode x == instConsInfoParamsNode y
767

    
768
-- | Groups instance information calls heading out to the same nodes.
769
consoleParamsToCalls :: [InstanceConsoleInfoParams]
770
                     -> [(Node, RpcCallInstanceConsoleInfo)]
771
consoleParamsToCalls params =
772
  let sortedParams = sortBy
773
        (comparing (instPrimaryNode . instConsInfoParamsInstance)) params
774
      groupedParams = groupBy compareParamsByNode sortedParams
775
  in map (\x -> case x of
776
            [] -> error "Programmer error: group must have one or more members"
777
            paramGroup@(y:_) ->
778
              let node = instConsInfoParamsNode y
779
                  packer z = (instName $ instConsInfoParamsInstance z, z)
780
              in (node, RpcCallInstanceConsoleInfo . map packer $ paramGroup)
781
         ) groupedParams
782

    
783
-- | Retrieves a list of all the hypervisors and params used by the given
784
-- instances.
785
getHypervisorSpecs :: ConfigData -> [Instance] -> [(Hypervisor, HvParams)]
786
getHypervisorSpecs cfg instances =
787
  let hvs = nub . map instHypervisor $ instances
788
      hvParamMap = (fromContainer . clusterHvparams . configCluster $ cfg)
789
  in zip hvs . map ((Map.!) hvParamMap . hypervisorToRaw) $ hvs
790

    
791
-- | Collect live data from RPC query if enabled.
792
collectLiveData :: Bool        -- ^ Live queries allowed
793
                -> ConfigData  -- ^ The cluster config
794
                -> [String]    -- ^ The requested fields
795
                -> [Instance]  -- ^ The instance objects
796
                -> IO [(Instance, Runtime)]
797
collectLiveData liveDataEnabled cfg fields instances
798
  | not liveDataEnabled = return . zip instances . repeat . Left .
799
                            RpcResultError $ "Live data disabled"
800
  | otherwise = do
801
      let hvSpecs = getHypervisorSpecs cfg instances
802
          instanceNodes = nub . justOk $
803
                            map (getNode cfg . instPrimaryNode) instances
804
          goodNodes = nodesWithValidConfig cfg instanceNodes
805
      instInfoRes <- executeRpcCall goodNodes (RpcCallAllInstancesInfo hvSpecs)
806
      consInfoRes <-
807
        if "console" `elem` fields
808
          then case getAllConsoleParams cfg instances of
809
            Ok  p -> executeRpcCalls $ consoleParamsToCalls p
810
            Bad _ -> return . zip goodNodes . repeat . Left $
811
              RpcResultError "Cannot construct parameters for console info call"
812
          else return [] -- The information is not necessary
813
      return . zip instances .
814
        map (extractLiveInfo instInfoRes consInfoRes) $ instances