Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ da45c352

History | View | Annotate | Download (20.4 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti config objects.
4

    
5
Some object fields are not implemented yet, and as such they are
6
commented out below.
7

    
8
-}
9

    
10
{-
11

    
12
Copyright (C) 2011, 2012 Google Inc.
13

    
14
This program is free software; you can redistribute it and/or modify
15
it under the terms of the GNU General Public License as published by
16
the Free Software Foundation; either version 2 of the License, or
17
(at your option) any later version.
18

    
19
This program is distributed in the hope that it will be useful, but
20
WITHOUT ANY WARRANTY; without even the implied warranty of
21
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22
General Public License for more details.
23

    
24
You should have received a copy of the GNU General Public License
25
along with this program; if not, write to the Free Software
26
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
27
02110-1301, USA.
28

    
29
-}
30

    
31
module Ganeti.Objects
32
  ( HvParams
33
  , OsParams
34
  , NICMode(..)
35
  , PartialNicParams(..)
36
  , FilledNicParams(..)
37
  , fillNicParams
38
  , PartialNic(..)
39
  , DiskMode(..)
40
  , DiskType(..)
41
  , DiskLogicalId(..)
42
  , Disk(..)
43
  , DiskTemplate(..)
44
  , PartialBeParams(..)
45
  , FilledBeParams(..)
46
  , fillBeParams
47
  , Hypervisor(..)
48
  , AdminState(..)
49
  , adminStateFromRaw
50
  , Instance(..)
51
  , toDictInstance
52
  , PartialNDParams(..)
53
  , FilledNDParams(..)
54
  , fillNDParams
55
  , Node(..)
56
  , NodeRole(..)
57
  , nodeRoleToRaw
58
  , roleDescription
59
  , AllocPolicy(..)
60
  , FilledISpecParams(..)
61
  , PartialISpecParams(..)
62
  , fillISpecParams
63
  , FilledIPolicy(..)
64
  , PartialIPolicy(..)
65
  , fillIPolicy
66
  , DiskParams
67
  , NodeGroup(..)
68
  , IpFamily(..)
69
  , ipFamilyToVersion
70
  , fillDict
71
  , ClusterHvParams
72
  , OsHvParams
73
  , ClusterBeParams
74
  , ClusterOsParams
75
  , ClusterNicParams
76
  , Cluster(..)
77
  , ConfigData(..)
78
  , TimeStampObject(..)
79
  , UuidObject(..)
80
  , SerialNoObject(..)
81
  , TagsObject(..)
82
  ) where
83

    
84
import Data.List (foldl')
85
import Data.Maybe
86
import qualified Data.Map as Map
87
import qualified Data.Set as Set
88
import Text.JSON (makeObj, showJSON, readJSON, JSON, JSValue(..))
89
import qualified Text.JSON as J
90

    
91
import qualified Ganeti.Constants as C
92
import Ganeti.HTools.JSON
93

    
94
import Ganeti.THH
95

    
96
-- * Generic definitions
97

    
98
-- | Fills one map with keys from the other map, if not already
99
-- existing. Mirrors objects.py:FillDict.
100
fillDict :: (Ord k) => Map.Map k v -> Map.Map k v -> [k] -> Map.Map k v
101
fillDict defaults custom skip_keys =
102
  let updated = Map.union custom defaults
103
  in foldl' (flip Map.delete) updated skip_keys
104

    
105
-- | The hypervisor parameter type. This is currently a simple map,
106
-- without type checking on key/value pairs.
107
type HvParams = Container JSValue
108

    
109
-- | The OS parameters type. This is, and will remain, a string
110
-- container, since the keys are dynamically declared by the OSes, and
111
-- the values are always strings.
112
type OsParams = Container String
113

    
114
-- | Class of objects that have timestamps.
115
class TimeStampObject a where
116
  cTimeOf :: a -> Double
117
  mTimeOf :: a -> Double
118

    
119
-- | Class of objects that have an UUID.
120
class UuidObject a where
121
  uuidOf :: a -> String
122

    
123
-- | Class of object that have a serial number.
124
class SerialNoObject a where
125
  serialOf :: a -> Int
126

    
127
-- | Class of objects that have tags.
128
class TagsObject a where
129
  tagsOf :: a -> Set.Set String
130

    
131
-- * Node role object
132

    
133
$(declareSADT "NodeRole"
134
  [ ("NROffline",   'C.nrOffline)
135
  , ("NRDrained",   'C.nrDrained)
136
  , ("NRRegular",   'C.nrRegular)
137
  , ("NRCandidate", 'C.nrMcandidate)
138
  , ("NRMaster",    'C.nrMaster)
139
  ])
140
$(makeJSONInstance ''NodeRole)
141

    
142
-- | The description of the node role.
143
roleDescription :: NodeRole -> String
144
roleDescription NROffline   = "offline"
145
roleDescription NRDrained   = "drained"
146
roleDescription NRRegular   = "regular"
147
roleDescription NRCandidate = "master candidate"
148
roleDescription NRMaster    = "master"
149

    
150
-- * NIC definitions
151

    
152
$(declareSADT "NICMode"
153
  [ ("NMBridged", 'C.nicModeBridged)
154
  , ("NMRouted",  'C.nicModeRouted)
155
  ])
156
$(makeJSONInstance ''NICMode)
157

    
158
$(buildParam "Nic" "nicp"
159
  [ simpleField "mode" [t| NICMode |]
160
  , simpleField "link" [t| String  |]
161
  ])
162

    
163
$(buildObject "PartialNic" "nic"
164
  [ simpleField "mac" [t| String |]
165
  , optionalField $ simpleField "ip" [t| String |]
166
  , simpleField "nicparams" [t| PartialNicParams |]
167
  ])
168

    
169
-- * Disk definitions
170

    
171
$(declareSADT "DiskMode"
172
  [ ("DiskRdOnly", 'C.diskRdonly)
173
  , ("DiskRdWr",   'C.diskRdwr)
174
  ])
175
$(makeJSONInstance ''DiskMode)
176

    
177
$(declareSADT "DiskType"
178
  [ ("LD_LV",       'C.ldLv)
179
  , ("LD_DRBD8",    'C.ldDrbd8)
180
  , ("LD_FILE",     'C.ldFile)
181
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
182
  , ("LD_RADOS",    'C.ldRbd)
183
  ])
184
$(makeJSONInstance ''DiskType)
185

    
186
-- | The file driver type.
187
$(declareSADT "FileDriver"
188
  [ ("FileLoop",   'C.fdLoop)
189
  , ("FileBlktap", 'C.fdBlktap)
190
  ])
191
$(makeJSONInstance ''FileDriver)
192

    
193
-- | The persistent block driver type. Currently only one type is allowed.
194
$(declareSADT "BlockDriver"
195
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
196
  ])
197
$(makeJSONInstance ''BlockDriver)
198

    
199
-- | Constant for the dev_type key entry in the disk config.
200
devType :: String
201
devType = "dev_type"
202

    
203
-- | The disk configuration type. This includes the disk type itself,
204
-- for a more complete consistency. Note that since in the Python
205
-- code-base there's no authoritative place where we document the
206
-- logical id, this is probably a good reference point.
207
data DiskLogicalId
208
  = LIDPlain String String  -- ^ Volume group, logical volume
209
  | LIDDrbd8 String String Int Int Int String
210
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
211
  | LIDFile FileDriver String -- ^ Driver, path
212
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
213
  | LIDRados String String -- ^ Unused, path
214
    deriving (Read, Show, Eq)
215

    
216
-- | Mapping from a logical id to a disk type.
217
lidDiskType :: DiskLogicalId -> DiskType
218
lidDiskType (LIDPlain {}) = LD_LV
219
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
220
lidDiskType (LIDFile  {}) = LD_FILE
221
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
222
lidDiskType (LIDRados {}) = LD_RADOS
223

    
224
-- | Builds the extra disk_type field for a given logical id.
225
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
226
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
227

    
228
-- | Custom encoder for DiskLogicalId (logical id only).
229
encodeDLId :: DiskLogicalId -> JSValue
230
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
231
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
232
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
233
          , showJSON minorA, showJSON minorB, showJSON key ]
234
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
235
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
236
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
237

    
238
-- | Custom encoder for DiskLogicalId, composing both the logical id
239
-- and the extra disk_type field.
240
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
241
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
242

    
243
-- | Custom decoder for DiskLogicalId. This is manual for now, since
244
-- we don't have yet automation for separate-key style fields.
245
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
246
decodeDLId obj lid = do
247
  dtype <- fromObj obj devType
248
  case dtype of
249
    LD_DRBD8 ->
250
      case lid of
251
        JSArray [nA, nB, p, mA, mB, k] -> do
252
          nA' <- readJSON nA
253
          nB' <- readJSON nB
254
          p'  <- readJSON p
255
          mA' <- readJSON mA
256
          mB' <- readJSON mB
257
          k'  <- readJSON k
258
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
259
        _ -> fail $ "Can't read logical_id for DRBD8 type"
260
    LD_LV ->
261
      case lid of
262
        JSArray [vg, lv] -> do
263
          vg' <- readJSON vg
264
          lv' <- readJSON lv
265
          return $ LIDPlain vg' lv'
266
        _ -> fail $ "Can't read logical_id for plain type"
267
    LD_FILE ->
268
      case lid of
269
        JSArray [driver, path] -> do
270
          driver' <- readJSON driver
271
          path'   <- readJSON path
272
          return $ LIDFile driver' path'
273
        _ -> fail $ "Can't read logical_id for file type"
274
    LD_BLOCKDEV ->
275
      case lid of
276
        JSArray [driver, path] -> do
277
          driver' <- readJSON driver
278
          path'   <- readJSON path
279
          return $ LIDBlockDev driver' path'
280
        _ -> fail $ "Can't read logical_id for blockdev type"
281
    LD_RADOS ->
282
      case lid of
283
        JSArray [driver, path] -> do
284
          driver' <- readJSON driver
285
          path'   <- readJSON path
286
          return $ LIDRados driver' path'
287
        _ -> fail $ "Can't read logical_id for rdb type"
288

    
289
-- | Disk data structure.
290
--
291
-- This is declared manually as it's a recursive structure, and our TH
292
-- code currently can't build it.
293
data Disk = Disk
294
  { diskLogicalId  :: DiskLogicalId
295
--  , diskPhysicalId :: String
296
  , diskChildren   :: [Disk]
297
  , diskIvName     :: String
298
  , diskSize       :: Int
299
  , diskMode       :: DiskMode
300
  } deriving (Read, Show, Eq)
301

    
302
$(buildObjectSerialisation "Disk"
303
  [ customField 'decodeDLId 'encodeFullDLId $
304
      simpleField "logical_id"    [t| DiskLogicalId   |]
305
--  , simpleField "physical_id" [t| String   |]
306
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
307
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
308
  , simpleField "size" [t| Int |]
309
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
310
  ])
311

    
312
-- * Hypervisor definitions
313

    
314
-- | This may be due to change when we add hypervisor parameters.
315
$(declareSADT "Hypervisor"
316
  [ ( "Kvm",    'C.htKvm )
317
  , ( "XenPvm", 'C.htXenPvm )
318
  , ( "Chroot", 'C.htChroot )
319
  , ( "XenHvm", 'C.htXenHvm )
320
  , ( "Lxc",    'C.htLxc )
321
  , ( "Fake",   'C.htFake )
322
  ])
323
$(makeJSONInstance ''Hypervisor)
324

    
325
-- * Instance definitions
326

    
327
-- | Instance disk template type. **Copied from HTools/Types.hs**
328
$(declareSADT "DiskTemplate"
329
  [ ("DTDiskless",   'C.dtDiskless)
330
  , ("DTFile",       'C.dtFile)
331
  , ("DTSharedFile", 'C.dtSharedFile)
332
  , ("DTPlain",      'C.dtPlain)
333
  , ("DTBlock",      'C.dtBlock)
334
  , ("DTDrbd8",      'C.dtDrbd8)
335
  , ("DTRados",      'C.dtRbd)
336
  ])
337
$(makeJSONInstance ''DiskTemplate)
338

    
339
$(declareSADT "AdminState"
340
  [ ("AdminOffline", 'C.adminstOffline)
341
  , ("AdminDown",    'C.adminstDown)
342
  , ("AdminUp",      'C.adminstUp)
343
  ])
344
$(makeJSONInstance ''AdminState)
345

    
346
$(buildParam "Be" "bep" $
347
  [ simpleField "minmem"       [t| Int  |]
348
  , simpleField "maxmem"       [t| Int  |]
349
  , simpleField "vcpus"        [t| Int  |]
350
  , simpleField "auto_balance" [t| Bool |]
351
  ])
352

    
353
$(buildObject "Instance" "inst" $
354
  [ simpleField "name"           [t| String             |]
355
  , simpleField "primary_node"   [t| String             |]
356
  , simpleField "os"             [t| String             |]
357
  , simpleField "hypervisor"     [t| Hypervisor         |]
358
  , simpleField "hvparams"       [t| HvParams           |]
359
  , simpleField "beparams"       [t| PartialBeParams    |]
360
  , simpleField "osparams"       [t| OsParams           |]
361
  , simpleField "admin_state"    [t| AdminState         |]
362
  , simpleField "nics"           [t| [PartialNic]       |]
363
  , simpleField "disks"          [t| [Disk]             |]
364
  , simpleField "disk_template"  [t| DiskTemplate       |]
365
  , optionalField $ simpleField "network_port" [t| Int  |]
366
  ]
367
  ++ timeStampFields
368
  ++ uuidFields
369
  ++ serialFields
370
  ++ tagsFields)
371

    
372
instance TimeStampObject Instance where
373
  cTimeOf = instCtime
374
  mTimeOf = instMtime
375

    
376
instance UuidObject Instance where
377
  uuidOf = instUuid
378

    
379
instance SerialNoObject Instance where
380
  serialOf = instSerial
381

    
382
instance TagsObject Instance where
383
  tagsOf = instTags
384

    
385
-- * IPolicy definitions
386

    
387
$(buildParam "ISpec" "ispec" $
388
  [ simpleField C.ispecMemSize     [t| Int |]
389
  , simpleField C.ispecDiskSize    [t| Int |]
390
  , simpleField C.ispecDiskCount   [t| Int |]
391
  , simpleField C.ispecCpuCount    [t| Int |]
392
  , simpleField C.ispecSpindleUse  [t| Int |]
393
  ])
394

    
395
-- | Custom partial ipolicy. This is not built via buildParam since it
396
-- has a special 2-level inheritance mode.
397
$(buildObject "PartialIPolicy" "ipolicy" $
398
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
399
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
400
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
401
  , optionalField . renameField "SpindleRatioP"
402
                    $ simpleField "spindle-ratio"  [t| Double |]
403
  , optionalField . renameField "VcpuRatioP"
404
                    $ simpleField "vcpu-ratio"     [t| Double |]
405
  , optionalField . renameField "DiskTemplatesP"
406
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
407
  ])
408

    
409
-- | Custom filled ipolicy. This is not built via buildParam since it
410
-- has a special 2-level inheritance mode.
411
$(buildObject "FilledIPolicy" "ipolicy" $
412
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
413
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
414
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
415
  , simpleField "spindle-ratio"  [t| Double |]
416
  , simpleField "vcpu-ratio"     [t| Double |]
417
  , simpleField "disk-templates" [t| [DiskTemplate] |]
418
  ])
419

    
420
-- | Custom filler for the ipolicy types.
421
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
422
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
423
                           , ipolicyMaxSpec       = fmax
424
                           , ipolicyStdSpec       = fstd
425
                           , ipolicySpindleRatio  = fspindleRatio
426
                           , ipolicyVcpuRatio     = fvcpuRatio
427
                           , ipolicyDiskTemplates = fdiskTemplates})
428
            (PartialIPolicy { ipolicyMinSpecP       = pmin
429
                            , ipolicyMaxSpecP       = pmax
430
                            , ipolicyStdSpecP       = pstd
431
                            , ipolicySpindleRatioP  = pspindleRatio
432
                            , ipolicyVcpuRatioP     = pvcpuRatio
433
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
434
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
435
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
436
                , ipolicyStdSpec       = fillISpecParams fstd pstd
437
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
438
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
439
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
440
                                         pdiskTemplates
441
                }
442
-- * Node definitions
443

    
444
$(buildParam "ND" "ndp" $
445
  [ simpleField "oob_program"   [t| String |]
446
  , simpleField "spindle_count" [t| Int    |]
447
  ])
448

    
449
$(buildObject "Node" "node" $
450
  [ simpleField "name"             [t| String |]
451
  , simpleField "primary_ip"       [t| String |]
452
  , simpleField "secondary_ip"     [t| String |]
453
  , simpleField "master_candidate" [t| Bool   |]
454
  , simpleField "offline"          [t| Bool   |]
455
  , simpleField "drained"          [t| Bool   |]
456
  , simpleField "group"            [t| String |]
457
  , simpleField "master_capable"   [t| Bool   |]
458
  , simpleField "vm_capable"       [t| Bool   |]
459
  , simpleField "ndparams"         [t| PartialNDParams |]
460
  , simpleField "powered"          [t| Bool   |]
461
  ]
462
  ++ timeStampFields
463
  ++ uuidFields
464
  ++ serialFields
465
  ++ tagsFields)
466

    
467
instance TimeStampObject Node where
468
  cTimeOf = nodeCtime
469
  mTimeOf = nodeMtime
470

    
471
instance UuidObject Node where
472
  uuidOf = nodeUuid
473

    
474
instance SerialNoObject Node where
475
  serialOf = nodeSerial
476

    
477
instance TagsObject Node where
478
  tagsOf = nodeTags
479

    
480
-- * NodeGroup definitions
481

    
482
-- | The Group allocation policy type.
483
--
484
-- Note that the order of constructors is important as the automatic
485
-- Ord instance will order them in the order they are defined, so when
486
-- changing this data type be careful about the interaction with the
487
-- desired sorting order.
488
--
489
-- FIXME: COPIED from Types.hs; we need to eliminate this duplication later
490
$(declareSADT "AllocPolicy"
491
  [ ("AllocPreferred",   'C.allocPolicyPreferred)
492
  , ("AllocLastResort",  'C.allocPolicyLastResort)
493
  , ("AllocUnallocable", 'C.allocPolicyUnallocable)
494
  ])
495
$(makeJSONInstance ''AllocPolicy)
496

    
497
-- | The disk parameters type.
498
type DiskParams = Container (Container JSValue)
499

    
500
$(buildObject "NodeGroup" "group" $
501
  [ simpleField "name"         [t| String |]
502
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
503
  , simpleField "ndparams"     [t| PartialNDParams |]
504
  , simpleField "alloc_policy" [t| AllocPolicy     |]
505
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
506
  , simpleField "diskparams"   [t| DiskParams      |]
507
  ]
508
  ++ timeStampFields
509
  ++ uuidFields
510
  ++ serialFields
511
  ++ tagsFields)
512

    
513
instance TimeStampObject NodeGroup where
514
  cTimeOf = groupCtime
515
  mTimeOf = groupMtime
516

    
517
instance UuidObject NodeGroup where
518
  uuidOf = groupUuid
519

    
520
instance SerialNoObject NodeGroup where
521
  serialOf = groupSerial
522

    
523
instance TagsObject NodeGroup where
524
  tagsOf = groupTags
525

    
526
-- | IP family type
527
$(declareIADT "IpFamily"
528
  [ ("IpFamilyV4", 'C.ip4Family)
529
  , ("IpFamilyV6", 'C.ip6Family)
530
  ])
531
$(makeJSONInstance ''IpFamily)
532

    
533
-- | Conversion from IP family to IP version. This is needed because
534
-- Python uses both, depending on context.
535
ipFamilyToVersion :: IpFamily -> Int
536
ipFamilyToVersion IpFamilyV4 = C.ip4Version
537
ipFamilyToVersion IpFamilyV6 = C.ip6Version
538

    
539
-- | Cluster HvParams (hvtype to hvparams mapping).
540
type ClusterHvParams = Container HvParams
541

    
542
-- | Cluster Os-HvParams (os to hvparams mapping).
543
type OsHvParams = Container ClusterHvParams
544

    
545
-- | Cluser BeParams.
546
type ClusterBeParams = Container FilledBeParams
547

    
548
-- | Cluster OsParams.
549
type ClusterOsParams = Container OsParams
550

    
551
-- | Cluster NicParams.
552
type ClusterNicParams = Container FilledNicParams
553

    
554
-- | Cluster UID Pool, list (low, high) UID ranges.
555
type UidPool = [(Int, Int)]
556

    
557
-- * Cluster definitions
558
$(buildObject "Cluster" "cluster" $
559
  [ simpleField "rsahostkeypub"           [t| String           |]
560
  , simpleField "highest_used_port"       [t| Int              |]
561
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
562
  , simpleField "mac_prefix"              [t| String           |]
563
  , simpleField "volume_group_name"       [t| String           |]
564
  , simpleField "reserved_lvs"            [t| [String]         |]
565
  , optionalField $
566
    simpleField "drbd_usermode_helper"    [t| String           |]
567
  , simpleField "master_node"             [t| String           |]
568
  , simpleField "master_ip"               [t| String           |]
569
  , simpleField "master_netdev"           [t| String           |]
570
  , simpleField "master_netmask"          [t| Int              |]
571
  , simpleField "use_external_mip_script" [t| Bool             |]
572
  , simpleField "cluster_name"            [t| String           |]
573
  , simpleField "file_storage_dir"        [t| String           |]
574
  , simpleField "shared_file_storage_dir" [t| String           |]
575
  , simpleField "enabled_hypervisors"     [t| [String]         |]
576
  , simpleField "hvparams"                [t| ClusterHvParams  |]
577
  , simpleField "os_hvp"                  [t| OsHvParams       |]
578
  , simpleField "beparams"                [t| ClusterBeParams  |]
579
  , simpleField "osparams"                [t| ClusterOsParams  |]
580
  , simpleField "nicparams"               [t| ClusterNicParams |]
581
  , simpleField "ndparams"                [t| FilledNDParams   |]
582
  , simpleField "diskparams"              [t| DiskParams       |]
583
  , simpleField "candidate_pool_size"     [t| Int              |]
584
  , simpleField "modify_etc_hosts"        [t| Bool             |]
585
  , simpleField "modify_ssh_setup"        [t| Bool             |]
586
  , simpleField "maintain_node_health"    [t| Bool             |]
587
  , simpleField "uid_pool"                [t| UidPool          |]
588
  , simpleField "default_iallocator"      [t| String           |]
589
  , simpleField "hidden_os"               [t| [String]         |]
590
  , simpleField "blacklisted_os"          [t| [String]         |]
591
  , simpleField "primary_ip_family"       [t| IpFamily         |]
592
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
593
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
594
 ]
595
 ++ timeStampFields
596
 ++ uuidFields
597
 ++ serialFields
598
 ++ tagsFields)
599

    
600
instance TimeStampObject Cluster where
601
  cTimeOf = clusterCtime
602
  mTimeOf = clusterMtime
603

    
604
instance UuidObject Cluster where
605
  uuidOf = clusterUuid
606

    
607
instance SerialNoObject Cluster where
608
  serialOf = clusterSerial
609

    
610
instance TagsObject Cluster where
611
  tagsOf = clusterTags
612

    
613
-- * ConfigData definitions
614

    
615
$(buildObject "ConfigData" "config" $
616
--  timeStampFields ++
617
  [ simpleField "version"    [t| Int                 |]
618
  , simpleField "cluster"    [t| Cluster             |]
619
  , simpleField "nodes"      [t| Container Node      |]
620
  , simpleField "nodegroups" [t| Container NodeGroup |]
621
  , simpleField "instances"  [t| Container Instance  |]
622
  ]
623
  ++ serialFields)
624

    
625
instance SerialNoObject ConfigData where
626
  serialOf = configSerial