Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 22381768

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

    
171
$(declareSADT "NICMode"
172
  [ ("NMBridged", 'C.nicModeBridged)
173
  , ("NMRouted",  'C.nicModeRouted)
174
  ])
175
$(makeJSONInstance ''NICMode)
176

    
177
$(buildParam "Nic" "nicp"
178
  [ simpleField "mode" [t| NICMode |]
179
  , simpleField "link" [t| String  |]
180
  ])
181

    
182
$(buildObject "PartialNic" "nic"
183
  [ simpleField "mac" [t| String |]
184
  , optionalField $ simpleField "ip" [t| String |]
185
  , simpleField "nicparams" [t| PartialNicParams |]
186
  ])
187

    
188
-- * Disk definitions
189

    
190
$(declareSADT "DiskMode"
191
  [ ("DiskRdOnly", 'C.diskRdonly)
192
  , ("DiskRdWr",   'C.diskRdwr)
193
  ])
194
$(makeJSONInstance ''DiskMode)
195

    
196
$(declareSADT "DiskType"
197
  [ ("LD_LV",       'C.ldLv)
198
  , ("LD_DRBD8",    'C.ldDrbd8)
199
  , ("LD_FILE",     'C.ldFile)
200
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
201
  , ("LD_RADOS",    'C.ldRbd)
202
  ])
203
$(makeJSONInstance ''DiskType)
204

    
205
-- | The file driver type.
206
$(declareSADT "FileDriver"
207
  [ ("FileLoop",   'C.fdLoop)
208
  , ("FileBlktap", 'C.fdBlktap)
209
  ])
210
$(makeJSONInstance ''FileDriver)
211

    
212
-- | The persistent block driver type. Currently only one type is allowed.
213
$(declareSADT "BlockDriver"
214
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
215
  ])
216
$(makeJSONInstance ''BlockDriver)
217

    
218
-- | Constant for the dev_type key entry in the disk config.
219
devType :: String
220
devType = "dev_type"
221

    
222
-- | The disk configuration type. This includes the disk type itself,
223
-- for a more complete consistency. Note that since in the Python
224
-- code-base there's no authoritative place where we document the
225
-- logical id, this is probably a good reference point.
226
data DiskLogicalId
227
  = LIDPlain String String  -- ^ Volume group, logical volume
228
  | LIDDrbd8 String String Int Int Int String
229
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
230
  | LIDFile FileDriver String -- ^ Driver, path
231
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
232
  | LIDRados String String -- ^ Unused, path
233
    deriving (Read, Show, Eq)
234

    
235
-- | Mapping from a logical id to a disk type.
236
lidDiskType :: DiskLogicalId -> DiskType
237
lidDiskType (LIDPlain {}) = LD_LV
238
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
239
lidDiskType (LIDFile  {}) = LD_FILE
240
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
241
lidDiskType (LIDRados {}) = LD_RADOS
242

    
243
-- | Builds the extra disk_type field for a given logical id.
244
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
245
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
246

    
247
-- | Custom encoder for DiskLogicalId (logical id only).
248
encodeDLId :: DiskLogicalId -> JSValue
249
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
250
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
251
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
252
          , showJSON minorA, showJSON minorB, showJSON key ]
253
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
254
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
255
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
256

    
257
-- | Custom encoder for DiskLogicalId, composing both the logical id
258
-- and the extra disk_type field.
259
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
260
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
261

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

    
308
-- | Disk data structure.
309
--
310
-- This is declared manually as it's a recursive structure, and our TH
311
-- code currently can't build it.
312
data Disk = Disk
313
  { diskLogicalId  :: DiskLogicalId
314
--  , diskPhysicalId :: String
315
  , diskChildren   :: [Disk]
316
  , diskIvName     :: String
317
  , diskSize       :: Int
318
  , diskMode       :: DiskMode
319
  } deriving (Read, Show, Eq)
320

    
321
$(buildObjectSerialisation "Disk"
322
  [ customField 'decodeDLId 'encodeFullDLId $
323
      simpleField "logical_id"    [t| DiskLogicalId   |]
324
--  , simpleField "physical_id" [t| String   |]
325
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
326
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
327
  , simpleField "size" [t| Int |]
328
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
329
  ])
330

    
331
-- * Instance definitions
332

    
333
$(declareSADT "AdminState"
334
  [ ("AdminOffline", 'C.adminstOffline)
335
  , ("AdminDown",    'C.adminstDown)
336
  , ("AdminUp",      'C.adminstUp)
337
  ])
338
$(makeJSONInstance ''AdminState)
339

    
340
$(buildParam "Be" "bep"
341
  [ simpleField "minmem"       [t| Int  |]
342
  , simpleField "maxmem"       [t| Int  |]
343
  , simpleField "vcpus"        [t| Int  |]
344
  , simpleField "auto_balance" [t| Bool |]
345
  ])
346

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

    
366
instance TimeStampObject Instance where
367
  cTimeOf = instCtime
368
  mTimeOf = instMtime
369

    
370
instance UuidObject Instance where
371
  uuidOf = instUuid
372

    
373
instance SerialNoObject Instance where
374
  serialOf = instSerial
375

    
376
instance TagsObject Instance where
377
  tagsOf = instTags
378

    
379
-- * IPolicy definitions
380

    
381
$(buildParam "ISpec" "ispec"
382
  [ simpleField C.ispecMemSize     [t| Int |]
383
  , simpleField C.ispecDiskSize    [t| Int |]
384
  , simpleField C.ispecDiskCount   [t| Int |]
385
  , simpleField C.ispecCpuCount    [t| Int |]
386
  , simpleField C.ispecNicCount    [t| Int |]
387
  , simpleField C.ispecSpindleUse  [t| Int |]
388
  ])
389

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

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

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

    
439
$(buildParam "ND" "ndp"
440
  [ simpleField "oob_program"   [t| String |]
441
  , simpleField "spindle_count" [t| Int    |]
442
  ])
443

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

    
462
instance TimeStampObject Node where
463
  cTimeOf = nodeCtime
464
  mTimeOf = nodeMtime
465

    
466
instance UuidObject Node where
467
  uuidOf = nodeUuid
468

    
469
instance SerialNoObject Node where
470
  serialOf = nodeSerial
471

    
472
instance TagsObject Node where
473
  tagsOf = nodeTags
474

    
475
-- * NodeGroup definitions
476

    
477
-- | The disk parameters type.
478
type DiskParams = Container (Container JSValue)
479

    
480
$(buildObject "NodeGroup" "group" $
481
  [ simpleField "name"         [t| String |]
482
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
483
  , simpleField "ndparams"     [t| PartialNDParams |]
484
  , simpleField "alloc_policy" [t| AllocPolicy     |]
485
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
486
  , simpleField "diskparams"   [t| DiskParams      |]
487
  ]
488
  ++ timeStampFields
489
  ++ uuidFields
490
  ++ serialFields
491
  ++ tagsFields)
492

    
493
instance TimeStampObject NodeGroup where
494
  cTimeOf = groupCtime
495
  mTimeOf = groupMtime
496

    
497
instance UuidObject NodeGroup where
498
  uuidOf = groupUuid
499

    
500
instance SerialNoObject NodeGroup where
501
  serialOf = groupSerial
502

    
503
instance TagsObject NodeGroup where
504
  tagsOf = groupTags
505

    
506
-- | IP family type
507
$(declareIADT "IpFamily"
508
  [ ("IpFamilyV4", 'C.ip4Family)
509
  , ("IpFamilyV6", 'C.ip6Family)
510
  ])
511
$(makeJSONInstance ''IpFamily)
512

    
513
-- | Conversion from IP family to IP version. This is needed because
514
-- Python uses both, depending on context.
515
ipFamilyToVersion :: IpFamily -> Int
516
ipFamilyToVersion IpFamilyV4 = C.ip4Version
517
ipFamilyToVersion IpFamilyV6 = C.ip6Version
518

    
519
-- | Cluster HvParams (hvtype to hvparams mapping).
520
type ClusterHvParams = Container HvParams
521

    
522
-- | Cluster Os-HvParams (os to hvparams mapping).
523
type OsHvParams = Container ClusterHvParams
524

    
525
-- | Cluser BeParams.
526
type ClusterBeParams = Container FilledBeParams
527

    
528
-- | Cluster OsParams.
529
type ClusterOsParams = Container OsParams
530

    
531
-- | Cluster NicParams.
532
type ClusterNicParams = Container FilledNicParams
533

    
534
-- | Cluster UID Pool, list (low, high) UID ranges.
535
type UidPool = [(Int, Int)]
536

    
537
-- * Cluster definitions
538
$(buildObject "Cluster" "cluster" $
539
  [ simpleField "rsahostkeypub"           [t| String           |]
540
  , simpleField "highest_used_port"       [t| Int              |]
541
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
542
  , simpleField "mac_prefix"              [t| String           |]
543
  , simpleField "volume_group_name"       [t| String           |]
544
  , simpleField "reserved_lvs"            [t| [String]         |]
545
  , optionalField $
546
    simpleField "drbd_usermode_helper"    [t| String           |]
547
  , simpleField "master_node"             [t| String           |]
548
  , simpleField "master_ip"               [t| String           |]
549
  , simpleField "master_netdev"           [t| String           |]
550
  , simpleField "master_netmask"          [t| Int              |]
551
  , simpleField "use_external_mip_script" [t| Bool             |]
552
  , simpleField "cluster_name"            [t| String           |]
553
  , simpleField "file_storage_dir"        [t| String           |]
554
  , simpleField "shared_file_storage_dir" [t| String           |]
555
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
556
  , simpleField "hvparams"                [t| ClusterHvParams  |]
557
  , simpleField "os_hvp"                  [t| OsHvParams       |]
558
  , simpleField "beparams"                [t| ClusterBeParams  |]
559
  , simpleField "osparams"                [t| ClusterOsParams  |]
560
  , simpleField "nicparams"               [t| ClusterNicParams |]
561
  , simpleField "ndparams"                [t| FilledNDParams   |]
562
  , simpleField "diskparams"              [t| DiskParams       |]
563
  , simpleField "candidate_pool_size"     [t| Int              |]
564
  , simpleField "modify_etc_hosts"        [t| Bool             |]
565
  , simpleField "modify_ssh_setup"        [t| Bool             |]
566
  , simpleField "maintain_node_health"    [t| Bool             |]
567
  , simpleField "uid_pool"                [t| UidPool          |]
568
  , simpleField "default_iallocator"      [t| String           |]
569
  , simpleField "hidden_os"               [t| [String]         |]
570
  , simpleField "blacklisted_os"          [t| [String]         |]
571
  , simpleField "primary_ip_family"       [t| IpFamily         |]
572
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
573
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
574
 ]
575
 ++ timeStampFields
576
 ++ uuidFields
577
 ++ serialFields
578
 ++ tagsFields)
579

    
580
instance TimeStampObject Cluster where
581
  cTimeOf = clusterCtime
582
  mTimeOf = clusterMtime
583

    
584
instance UuidObject Cluster where
585
  uuidOf = clusterUuid
586

    
587
instance SerialNoObject Cluster where
588
  serialOf = clusterSerial
589

    
590
instance TagsObject Cluster where
591
  tagsOf = clusterTags
592

    
593
-- * ConfigData definitions
594

    
595
$(buildObject "ConfigData" "config" $
596
--  timeStampFields ++
597
  [ simpleField "version"    [t| Int                 |]
598
  , simpleField "cluster"    [t| Cluster             |]
599
  , simpleField "nodes"      [t| Container Node      |]
600
  , simpleField "nodegroups" [t| Container NodeGroup |]
601
  , simpleField "instances"  [t| Container Instance  |]
602
  ]
603
  ++ serialFields)
604

    
605
instance SerialNoObject ConfigData where
606
  serialOf = configSerial