Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 2af78b97

History | View | Annotate | Download (20.5 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
  , allNicParamFields
39
  , PartialNic(..)
40
  , DiskMode(..)
41
  , DiskType(..)
42
  , DiskLogicalId(..)
43
  , Disk(..)
44
  , DiskTemplate(..)
45
  , PartialBeParams(..)
46
  , FilledBeParams(..)
47
  , fillBeParams
48
  , allBeParamFields
49
  , Hypervisor(..)
50
  , AdminState(..)
51
  , adminStateFromRaw
52
  , Instance(..)
53
  , toDictInstance
54
  , PartialNDParams(..)
55
  , FilledNDParams(..)
56
  , fillNDParams
57
  , allNDParamFields
58
  , Node(..)
59
  , NodeRole(..)
60
  , nodeRoleToRaw
61
  , roleDescription
62
  , AllocPolicy(..)
63
  , FilledISpecParams(..)
64
  , PartialISpecParams(..)
65
  , fillISpecParams
66
  , allISpecParamFields
67
  , FilledIPolicy(..)
68
  , PartialIPolicy(..)
69
  , fillIPolicy
70
  , DiskParams
71
  , NodeGroup(..)
72
  , IpFamily(..)
73
  , ipFamilyToVersion
74
  , fillDict
75
  , ClusterHvParams
76
  , OsHvParams
77
  , ClusterBeParams
78
  , ClusterOsParams
79
  , ClusterNicParams
80
  , Cluster(..)
81
  , ConfigData(..)
82
  , TimeStampObject(..)
83
  , UuidObject(..)
84
  , SerialNoObject(..)
85
  , TagsObject(..)
86
  , DictObject(..) -- re-exported from THH
87
  ) where
88

    
89
import Data.List (foldl')
90
import Data.Maybe
91
import qualified Data.Map as Map
92
import qualified Data.Set as Set
93
import Text.JSON (makeObj, showJSON, readJSON, JSON, JSValue(..))
94
import qualified Text.JSON as J
95

    
96
import qualified Ganeti.Constants as C
97
import Ganeti.HTools.JSON
98

    
99
import Ganeti.THH
100

    
101
-- * Generic definitions
102

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

    
110
-- | The hypervisor parameter type. This is currently a simple map,
111
-- without type checking on key/value pairs.
112
type HvParams = Container JSValue
113

    
114
-- | The OS parameters type. This is, and will remain, a string
115
-- container, since the keys are dynamically declared by the OSes, and
116
-- the values are always strings.
117
type OsParams = Container String
118

    
119
-- | Class of objects that have timestamps.
120
class TimeStampObject a where
121
  cTimeOf :: a -> Double
122
  mTimeOf :: a -> Double
123

    
124
-- | Class of objects that have an UUID.
125
class UuidObject a where
126
  uuidOf :: a -> String
127

    
128
-- | Class of object that have a serial number.
129
class SerialNoObject a where
130
  serialOf :: a -> Int
131

    
132
-- | Class of objects that have tags.
133
class TagsObject a where
134
  tagsOf :: a -> Set.Set String
135

    
136
-- * Node role object
137

    
138
$(declareSADT "NodeRole"
139
  [ ("NROffline",   'C.nrOffline)
140
  , ("NRDrained",   'C.nrDrained)
141
  , ("NRRegular",   'C.nrRegular)
142
  , ("NRCandidate", 'C.nrMcandidate)
143
  , ("NRMaster",    'C.nrMaster)
144
  ])
145
$(makeJSONInstance ''NodeRole)
146

    
147
-- | The description of the node role.
148
roleDescription :: NodeRole -> String
149
roleDescription NROffline   = "offline"
150
roleDescription NRDrained   = "drained"
151
roleDescription NRRegular   = "regular"
152
roleDescription NRCandidate = "master candidate"
153
roleDescription NRMaster    = "master"
154

    
155
-- * NIC definitions
156

    
157
$(declareSADT "NICMode"
158
  [ ("NMBridged", 'C.nicModeBridged)
159
  , ("NMRouted",  'C.nicModeRouted)
160
  ])
161
$(makeJSONInstance ''NICMode)
162

    
163
$(buildParam "Nic" "nicp"
164
  [ simpleField "mode" [t| NICMode |]
165
  , simpleField "link" [t| String  |]
166
  ])
167

    
168
$(buildObject "PartialNic" "nic"
169
  [ simpleField "mac" [t| String |]
170
  , optionalField $ simpleField "ip" [t| String |]
171
  , simpleField "nicparams" [t| PartialNicParams |]
172
  ])
173

    
174
-- * Disk definitions
175

    
176
$(declareSADT "DiskMode"
177
  [ ("DiskRdOnly", 'C.diskRdonly)
178
  , ("DiskRdWr",   'C.diskRdwr)
179
  ])
180
$(makeJSONInstance ''DiskMode)
181

    
182
$(declareSADT "DiskType"
183
  [ ("LD_LV",       'C.ldLv)
184
  , ("LD_DRBD8",    'C.ldDrbd8)
185
  , ("LD_FILE",     'C.ldFile)
186
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
187
  , ("LD_RADOS",    'C.ldRbd)
188
  ])
189
$(makeJSONInstance ''DiskType)
190

    
191
-- | The file driver type.
192
$(declareSADT "FileDriver"
193
  [ ("FileLoop",   'C.fdLoop)
194
  , ("FileBlktap", 'C.fdBlktap)
195
  ])
196
$(makeJSONInstance ''FileDriver)
197

    
198
-- | The persistent block driver type. Currently only one type is allowed.
199
$(declareSADT "BlockDriver"
200
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
201
  ])
202
$(makeJSONInstance ''BlockDriver)
203

    
204
-- | Constant for the dev_type key entry in the disk config.
205
devType :: String
206
devType = "dev_type"
207

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

    
221
-- | Mapping from a logical id to a disk type.
222
lidDiskType :: DiskLogicalId -> DiskType
223
lidDiskType (LIDPlain {}) = LD_LV
224
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
225
lidDiskType (LIDFile  {}) = LD_FILE
226
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
227
lidDiskType (LIDRados {}) = LD_RADOS
228

    
229
-- | Builds the extra disk_type field for a given logical id.
230
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
231
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
232

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

    
243
-- | Custom encoder for DiskLogicalId, composing both the logical id
244
-- and the extra disk_type field.
245
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
246
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
247

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

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

    
307
$(buildObjectSerialisation "Disk"
308
  [ customField 'decodeDLId 'encodeFullDLId $
309
      simpleField "logical_id"    [t| DiskLogicalId   |]
310
--  , simpleField "physical_id" [t| String   |]
311
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
312
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
313
  , simpleField "size" [t| Int |]
314
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
315
  ])
316

    
317
-- * Hypervisor definitions
318

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

    
330
-- * Instance definitions
331

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

    
344
$(declareSADT "AdminState"
345
  [ ("AdminOffline", 'C.adminstOffline)
346
  , ("AdminDown",    'C.adminstDown)
347
  , ("AdminUp",      'C.adminstUp)
348
  ])
349
$(makeJSONInstance ''AdminState)
350

    
351
$(buildParam "Be" "bep" $
352
  [ simpleField "minmem"       [t| Int  |]
353
  , simpleField "maxmem"       [t| Int  |]
354
  , simpleField "vcpus"        [t| Int  |]
355
  , simpleField "auto_balance" [t| Bool |]
356
  ])
357

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

    
377
instance TimeStampObject Instance where
378
  cTimeOf = instCtime
379
  mTimeOf = instMtime
380

    
381
instance UuidObject Instance where
382
  uuidOf = instUuid
383

    
384
instance SerialNoObject Instance where
385
  serialOf = instSerial
386

    
387
instance TagsObject Instance where
388
  tagsOf = instTags
389

    
390
-- * IPolicy definitions
391

    
392
$(buildParam "ISpec" "ispec" $
393
  [ simpleField C.ispecMemSize     [t| Int |]
394
  , simpleField C.ispecDiskSize    [t| Int |]
395
  , simpleField C.ispecDiskCount   [t| Int |]
396
  , simpleField C.ispecCpuCount    [t| Int |]
397
  , simpleField C.ispecSpindleUse  [t| Int |]
398
  ])
399

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

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

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

    
449
$(buildParam "ND" "ndp" $
450
  [ simpleField "oob_program"   [t| String |]
451
  , simpleField "spindle_count" [t| Int    |]
452
  ])
453

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

    
472
instance TimeStampObject Node where
473
  cTimeOf = nodeCtime
474
  mTimeOf = nodeMtime
475

    
476
instance UuidObject Node where
477
  uuidOf = nodeUuid
478

    
479
instance SerialNoObject Node where
480
  serialOf = nodeSerial
481

    
482
instance TagsObject Node where
483
  tagsOf = nodeTags
484

    
485
-- * NodeGroup definitions
486

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

    
502
-- | The disk parameters type.
503
type DiskParams = Container (Container JSValue)
504

    
505
$(buildObject "NodeGroup" "group" $
506
  [ simpleField "name"         [t| String |]
507
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
508
  , simpleField "ndparams"     [t| PartialNDParams |]
509
  , simpleField "alloc_policy" [t| AllocPolicy     |]
510
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
511
  , simpleField "diskparams"   [t| DiskParams      |]
512
  ]
513
  ++ timeStampFields
514
  ++ uuidFields
515
  ++ serialFields
516
  ++ tagsFields)
517

    
518
instance TimeStampObject NodeGroup where
519
  cTimeOf = groupCtime
520
  mTimeOf = groupMtime
521

    
522
instance UuidObject NodeGroup where
523
  uuidOf = groupUuid
524

    
525
instance SerialNoObject NodeGroup where
526
  serialOf = groupSerial
527

    
528
instance TagsObject NodeGroup where
529
  tagsOf = groupTags
530

    
531
-- | IP family type
532
$(declareIADT "IpFamily"
533
  [ ("IpFamilyV4", 'C.ip4Family)
534
  , ("IpFamilyV6", 'C.ip6Family)
535
  ])
536
$(makeJSONInstance ''IpFamily)
537

    
538
-- | Conversion from IP family to IP version. This is needed because
539
-- Python uses both, depending on context.
540
ipFamilyToVersion :: IpFamily -> Int
541
ipFamilyToVersion IpFamilyV4 = C.ip4Version
542
ipFamilyToVersion IpFamilyV6 = C.ip6Version
543

    
544
-- | Cluster HvParams (hvtype to hvparams mapping).
545
type ClusterHvParams = Container HvParams
546

    
547
-- | Cluster Os-HvParams (os to hvparams mapping).
548
type OsHvParams = Container ClusterHvParams
549

    
550
-- | Cluser BeParams.
551
type ClusterBeParams = Container FilledBeParams
552

    
553
-- | Cluster OsParams.
554
type ClusterOsParams = Container OsParams
555

    
556
-- | Cluster NicParams.
557
type ClusterNicParams = Container FilledNicParams
558

    
559
-- | Cluster UID Pool, list (low, high) UID ranges.
560
type UidPool = [(Int, Int)]
561

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

    
605
instance TimeStampObject Cluster where
606
  cTimeOf = clusterCtime
607
  mTimeOf = clusterMtime
608

    
609
instance UuidObject Cluster where
610
  uuidOf = clusterUuid
611

    
612
instance SerialNoObject Cluster where
613
  serialOf = clusterSerial
614

    
615
instance TagsObject Cluster where
616
  tagsOf = clusterTags
617

    
618
-- * ConfigData definitions
619

    
620
$(buildObject "ConfigData" "config" $
621
--  timeStampFields ++
622
  [ simpleField "version"    [t| Int                 |]
623
  , simpleField "cluster"    [t| Cluster             |]
624
  , simpleField "nodes"      [t| Container Node      |]
625
  , simpleField "nodegroups" [t| Container NodeGroup |]
626
  , simpleField "instances"  [t| Container Instance  |]
627
  ]
628
  ++ serialFields)
629

    
630
instance SerialNoObject ConfigData where
631
  serialOf = configSerial