Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ da1dcce1

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

    
93
import Data.List (foldl')
94
import Data.Maybe
95
import qualified Data.Map as Map
96
import qualified Data.Set as Set
97
import Text.JSON (showJSON, readJSON, JSON, JSValue(..))
98
import qualified Text.JSON as J
99

    
100
import qualified Ganeti.Constants as C
101
import Ganeti.JSON
102
import Ganeti.Types
103
import Ganeti.THH
104

    
105
-- * Generic definitions
106

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

    
114
-- | The VTYPES, a mini-type system in Python.
115
$(declareSADT "VType"
116
  [ ("VTypeString",      'C.vtypeString)
117
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
118
  , ("VTypeBool",        'C.vtypeBool)
119
  , ("VTypeSize",        'C.vtypeSize)
120
  , ("VTypeInt",         'C.vtypeInt)
121
  ])
122
$(makeJSONInstance ''VType)
123

    
124
-- | The hypervisor parameter type. This is currently a simple map,
125
-- without type checking on key/value pairs.
126
type HvParams = Container JSValue
127

    
128
-- | The OS parameters type. This is, and will remain, a string
129
-- container, since the keys are dynamically declared by the OSes, and
130
-- the values are always strings.
131
type OsParams = Container String
132

    
133
-- | Class of objects that have timestamps.
134
class TimeStampObject a where
135
  cTimeOf :: a -> Double
136
  mTimeOf :: a -> Double
137

    
138
-- | Class of objects that have an UUID.
139
class UuidObject a where
140
  uuidOf :: a -> String
141

    
142
-- | Class of object that have a serial number.
143
class SerialNoObject a where
144
  serialOf :: a -> Int
145

    
146
-- | Class of objects that have tags.
147
class TagsObject a where
148
  tagsOf :: a -> Set.Set String
149

    
150
-- * Node role object
151

    
152
$(declareSADT "NodeRole"
153
  [ ("NROffline",   'C.nrOffline)
154
  , ("NRDrained",   'C.nrDrained)
155
  , ("NRRegular",   'C.nrRegular)
156
  , ("NRCandidate", 'C.nrMcandidate)
157
  , ("NRMaster",    'C.nrMaster)
158
  ])
159
$(makeJSONInstance ''NodeRole)
160

    
161
-- | The description of the node role.
162
roleDescription :: NodeRole -> String
163
roleDescription NROffline   = "offline"
164
roleDescription NRDrained   = "drained"
165
roleDescription NRRegular   = "regular"
166
roleDescription NRCandidate = "master candidate"
167
roleDescription NRMaster    = "master"
168

    
169
-- * Network definitions
170

    
171
-- FIXME: Not all types might be correct here, since they
172
-- haven't been exhaustively deduced from the python code yet.
173
$(buildObject "Network" "network" $
174
  [ simpleField "name"             [t| NonEmptyString |]
175
  , optionalField $
176
    simpleField "network_type"     [t| NetworkType |]
177
  , optionalField $
178
    simpleField "mac_prefix"       [t| String |]
179
  , optionalField $
180
    simpleField "family"           [t| Int |]
181
  , simpleField "network"          [t| NonEmptyString |]
182
  , optionalField $
183
    simpleField "network6"         [t| String |]
184
  , optionalField $
185
    simpleField "gateway"          [t| String |]
186
  , optionalField $
187
    simpleField "gateway6"         [t| String |]
188
  , optionalField $
189
    simpleField "size"             [t| J.JSValue |]
190
  , optionalField $
191
    simpleField "reservations"     [t| String |]
192
  , optionalField $
193
    simpleField "ext_reservations" [t| String |]
194
  ]
195
  ++ serialFields
196
  ++ tagsFields)
197

    
198
instance SerialNoObject Network where
199
  serialOf = networkSerial
200

    
201
instance TagsObject Network where
202
  tagsOf = networkTags
203

    
204
-- * NIC definitions
205

    
206
$(buildParam "Nic" "nicp"
207
  [ simpleField "mode" [t| NICMode |]
208
  , simpleField "link" [t| String  |]
209
  ])
210

    
211
$(buildObject "PartialNic" "nic"
212
  [ simpleField "mac" [t| String |]
213
  , optionalField $ simpleField "ip" [t| String |]
214
  , simpleField "nicparams" [t| PartialNicParams |]
215
  , optionalField $ simpleField "network" [t| Network |]
216
  ])
217

    
218
-- * Disk definitions
219

    
220
$(declareSADT "DiskMode"
221
  [ ("DiskRdOnly", 'C.diskRdonly)
222
  , ("DiskRdWr",   'C.diskRdwr)
223
  ])
224
$(makeJSONInstance ''DiskMode)
225

    
226
$(declareSADT "DiskType"
227
  [ ("LD_LV",       'C.ldLv)
228
  , ("LD_DRBD8",    'C.ldDrbd8)
229
  , ("LD_FILE",     'C.ldFile)
230
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
231
  , ("LD_RADOS",    'C.ldRbd)
232
  ])
233
$(makeJSONInstance ''DiskType)
234

    
235
-- | The persistent block driver type. Currently only one type is allowed.
236
$(declareSADT "BlockDriver"
237
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
238
  ])
239
$(makeJSONInstance ''BlockDriver)
240

    
241
-- | Constant for the dev_type key entry in the disk config.
242
devType :: String
243
devType = "dev_type"
244

    
245
-- | The disk configuration type. This includes the disk type itself,
246
-- for a more complete consistency. Note that since in the Python
247
-- code-base there's no authoritative place where we document the
248
-- logical id, this is probably a good reference point.
249
data DiskLogicalId
250
  = LIDPlain String String  -- ^ Volume group, logical volume
251
  | LIDDrbd8 String String Int Int Int String
252
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
253
  | LIDFile FileDriver String -- ^ Driver, path
254
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
255
  | LIDRados String String -- ^ Unused, path
256
    deriving (Show, Eq)
257

    
258
-- | Mapping from a logical id to a disk type.
259
lidDiskType :: DiskLogicalId -> DiskType
260
lidDiskType (LIDPlain {}) = LD_LV
261
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
262
lidDiskType (LIDFile  {}) = LD_FILE
263
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
264
lidDiskType (LIDRados {}) = LD_RADOS
265

    
266
-- | Builds the extra disk_type field for a given logical id.
267
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
268
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
269

    
270
-- | Custom encoder for DiskLogicalId (logical id only).
271
encodeDLId :: DiskLogicalId -> JSValue
272
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
273
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
274
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
275
          , showJSON minorA, showJSON minorB, showJSON key ]
276
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
277
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
278
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
279

    
280
-- | Custom encoder for DiskLogicalId, composing both the logical id
281
-- and the extra disk_type field.
282
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
283
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
284

    
285
-- | Custom decoder for DiskLogicalId. This is manual for now, since
286
-- we don't have yet automation for separate-key style fields.
287
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
288
decodeDLId obj lid = do
289
  dtype <- fromObj obj devType
290
  case dtype of
291
    LD_DRBD8 ->
292
      case lid of
293
        JSArray [nA, nB, p, mA, mB, k] -> do
294
          nA' <- readJSON nA
295
          nB' <- readJSON nB
296
          p'  <- readJSON p
297
          mA' <- readJSON mA
298
          mB' <- readJSON mB
299
          k'  <- readJSON k
300
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
301
        _ -> fail "Can't read logical_id for DRBD8 type"
302
    LD_LV ->
303
      case lid of
304
        JSArray [vg, lv] -> do
305
          vg' <- readJSON vg
306
          lv' <- readJSON lv
307
          return $ LIDPlain vg' lv'
308
        _ -> fail "Can't read logical_id for plain type"
309
    LD_FILE ->
310
      case lid of
311
        JSArray [driver, path] -> do
312
          driver' <- readJSON driver
313
          path'   <- readJSON path
314
          return $ LIDFile driver' path'
315
        _ -> fail "Can't read logical_id for file type"
316
    LD_BLOCKDEV ->
317
      case lid of
318
        JSArray [driver, path] -> do
319
          driver' <- readJSON driver
320
          path'   <- readJSON path
321
          return $ LIDBlockDev driver' path'
322
        _ -> fail "Can't read logical_id for blockdev type"
323
    LD_RADOS ->
324
      case lid of
325
        JSArray [driver, path] -> do
326
          driver' <- readJSON driver
327
          path'   <- readJSON path
328
          return $ LIDRados driver' path'
329
        _ -> fail "Can't read logical_id for rdb type"
330

    
331
-- | Disk data structure.
332
--
333
-- This is declared manually as it's a recursive structure, and our TH
334
-- code currently can't build it.
335
data Disk = Disk
336
  { diskLogicalId  :: DiskLogicalId
337
--  , diskPhysicalId :: String
338
  , diskChildren   :: [Disk]
339
  , diskIvName     :: String
340
  , diskSize       :: Int
341
  , diskMode       :: DiskMode
342
  } deriving (Show, Eq)
343

    
344
$(buildObjectSerialisation "Disk"
345
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
346
      simpleField "logical_id"    [t| DiskLogicalId   |]
347
--  , simpleField "physical_id" [t| String   |]
348
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
349
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
350
  , simpleField "size" [t| Int |]
351
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
352
  ])
353

    
354
-- * Instance definitions
355

    
356
$(declareSADT "AdminState"
357
  [ ("AdminOffline", 'C.adminstOffline)
358
  , ("AdminDown",    'C.adminstDown)
359
  , ("AdminUp",      'C.adminstUp)
360
  ])
361
$(makeJSONInstance ''AdminState)
362

    
363
$(buildParam "Be" "bep"
364
  [ simpleField "minmem"       [t| Int  |]
365
  , simpleField "maxmem"       [t| Int  |]
366
  , simpleField "vcpus"        [t| Int  |]
367
  , simpleField "auto_balance" [t| Bool |]
368
  ])
369

    
370
$(buildObject "Instance" "inst" $
371
  [ simpleField "name"           [t| String             |]
372
  , simpleField "primary_node"   [t| String             |]
373
  , simpleField "os"             [t| String             |]
374
  , simpleField "hypervisor"     [t| Hypervisor         |]
375
  , simpleField "hvparams"       [t| HvParams           |]
376
  , simpleField "beparams"       [t| PartialBeParams    |]
377
  , simpleField "osparams"       [t| OsParams           |]
378
  , simpleField "admin_state"    [t| AdminState         |]
379
  , simpleField "nics"           [t| [PartialNic]       |]
380
  , simpleField "disks"          [t| [Disk]             |]
381
  , simpleField "disk_template"  [t| DiskTemplate       |]
382
  , optionalField $ simpleField "network_port" [t| Int  |]
383
  ]
384
  ++ timeStampFields
385
  ++ uuidFields
386
  ++ serialFields
387
  ++ tagsFields)
388

    
389
instance TimeStampObject Instance where
390
  cTimeOf = instCtime
391
  mTimeOf = instMtime
392

    
393
instance UuidObject Instance where
394
  uuidOf = instUuid
395

    
396
instance SerialNoObject Instance where
397
  serialOf = instSerial
398

    
399
instance TagsObject Instance where
400
  tagsOf = instTags
401

    
402
-- * IPolicy definitions
403

    
404
$(buildParam "ISpec" "ispec"
405
  [ simpleField C.ispecMemSize     [t| Int |]
406
  , simpleField C.ispecDiskSize    [t| Int |]
407
  , simpleField C.ispecDiskCount   [t| Int |]
408
  , simpleField C.ispecCpuCount    [t| Int |]
409
  , simpleField C.ispecNicCount    [t| Int |]
410
  , simpleField C.ispecSpindleUse  [t| Int |]
411
  ])
412

    
413
-- | Custom partial ipolicy. This is not built via buildParam since it
414
-- has a special 2-level inheritance mode.
415
$(buildObject "PartialIPolicy" "ipolicy"
416
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
417
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
418
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
419
  , optionalField . renameField "SpindleRatioP"
420
                    $ simpleField "spindle-ratio"  [t| Double |]
421
  , optionalField . renameField "VcpuRatioP"
422
                    $ simpleField "vcpu-ratio"     [t| Double |]
423
  , optionalField . renameField "DiskTemplatesP"
424
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
425
  ])
426

    
427
-- | Custom filled ipolicy. This is not built via buildParam since it
428
-- has a special 2-level inheritance mode.
429
$(buildObject "FilledIPolicy" "ipolicy"
430
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
431
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
432
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
433
  , simpleField "spindle-ratio"  [t| Double |]
434
  , simpleField "vcpu-ratio"     [t| Double |]
435
  , simpleField "disk-templates" [t| [DiskTemplate] |]
436
  ])
437

    
438
-- | Custom filler for the ipolicy types.
439
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
440
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
441
                           , ipolicyMaxSpec       = fmax
442
                           , ipolicyStdSpec       = fstd
443
                           , ipolicySpindleRatio  = fspindleRatio
444
                           , ipolicyVcpuRatio     = fvcpuRatio
445
                           , ipolicyDiskTemplates = fdiskTemplates})
446
            (PartialIPolicy { ipolicyMinSpecP       = pmin
447
                            , ipolicyMaxSpecP       = pmax
448
                            , ipolicyStdSpecP       = pstd
449
                            , ipolicySpindleRatioP  = pspindleRatio
450
                            , ipolicyVcpuRatioP     = pvcpuRatio
451
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
452
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
453
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
454
                , ipolicyStdSpec       = fillISpecParams fstd pstd
455
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
456
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
457
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
458
                                         pdiskTemplates
459
                }
460
-- * Node definitions
461

    
462
$(buildParam "ND" "ndp"
463
  [ simpleField "oob_program"   [t| String |]
464
  , simpleField "spindle_count" [t| Int    |]
465
  , simpleField "exclusive_storage" [t| Bool |]
466
  ])
467

    
468
$(buildObject "Node" "node" $
469
  [ simpleField "name"             [t| String |]
470
  , simpleField "primary_ip"       [t| String |]
471
  , simpleField "secondary_ip"     [t| String |]
472
  , simpleField "master_candidate" [t| Bool   |]
473
  , simpleField "offline"          [t| Bool   |]
474
  , simpleField "drained"          [t| Bool   |]
475
  , simpleField "group"            [t| String |]
476
  , simpleField "master_capable"   [t| Bool   |]
477
  , simpleField "vm_capable"       [t| Bool   |]
478
  , simpleField "ndparams"         [t| PartialNDParams |]
479
  , simpleField "powered"          [t| Bool   |]
480
  ]
481
  ++ timeStampFields
482
  ++ uuidFields
483
  ++ serialFields
484
  ++ tagsFields)
485

    
486
instance TimeStampObject Node where
487
  cTimeOf = nodeCtime
488
  mTimeOf = nodeMtime
489

    
490
instance UuidObject Node where
491
  uuidOf = nodeUuid
492

    
493
instance SerialNoObject Node where
494
  serialOf = nodeSerial
495

    
496
instance TagsObject Node where
497
  tagsOf = nodeTags
498

    
499
-- * NodeGroup definitions
500

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

    
504
-- | A mapping from network UUIDs to nic params of the networks.
505
type Networks = Container PartialNic
506

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

    
521
instance TimeStampObject NodeGroup where
522
  cTimeOf = groupCtime
523
  mTimeOf = groupMtime
524

    
525
instance UuidObject NodeGroup where
526
  uuidOf = groupUuid
527

    
528
instance SerialNoObject NodeGroup where
529
  serialOf = groupSerial
530

    
531
instance TagsObject NodeGroup where
532
  tagsOf = groupTags
533

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

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

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

    
550
-- | Cluster Os-HvParams (os to hvparams mapping).
551
type OsHvParams = Container ClusterHvParams
552

    
553
-- | Cluser BeParams.
554
type ClusterBeParams = Container FilledBeParams
555

    
556
-- | Cluster OsParams.
557
type ClusterOsParams = Container OsParams
558

    
559
-- | Cluster NicParams.
560
type ClusterNicParams = Container FilledNicParams
561

    
562
-- | Cluster UID Pool, list (low, high) UID ranges.
563
type UidPool = [(Int, Int)]
564

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

    
608
instance TimeStampObject Cluster where
609
  cTimeOf = clusterCtime
610
  mTimeOf = clusterMtime
611

    
612
instance UuidObject Cluster where
613
  uuidOf = clusterUuid
614

    
615
instance SerialNoObject Cluster where
616
  serialOf = clusterSerial
617

    
618
instance TagsObject Cluster where
619
  tagsOf = clusterTags
620

    
621
-- * ConfigData definitions
622

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

    
633
instance SerialNoObject ConfigData where
634
  serialOf = configSerial