Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ c65621d7

History | View | Annotate | Download (19.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
  ( 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 persistent block driver type. Currently only one type is allowed.
206
$(declareSADT "BlockDriver"
207
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
208
  ])
209
$(makeJSONInstance ''BlockDriver)
210

    
211
-- | Constant for the dev_type key entry in the disk config.
212
devType :: String
213
devType = "dev_type"
214

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

    
228
-- | Mapping from a logical id to a disk type.
229
lidDiskType :: DiskLogicalId -> DiskType
230
lidDiskType (LIDPlain {}) = LD_LV
231
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
232
lidDiskType (LIDFile  {}) = LD_FILE
233
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
234
lidDiskType (LIDRados {}) = LD_RADOS
235

    
236
-- | Builds the extra disk_type field for a given logical id.
237
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
238
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
239

    
240
-- | Custom encoder for DiskLogicalId (logical id only).
241
encodeDLId :: DiskLogicalId -> JSValue
242
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
243
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
244
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
245
          , showJSON minorA, showJSON minorB, showJSON key ]
246
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
247
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
248
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
249

    
250
-- | Custom encoder for DiskLogicalId, composing both the logical id
251
-- and the extra disk_type field.
252
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
253
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
254

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

    
301
-- | Disk data structure.
302
--
303
-- This is declared manually as it's a recursive structure, and our TH
304
-- code currently can't build it.
305
data Disk = Disk
306
  { diskLogicalId  :: DiskLogicalId
307
--  , diskPhysicalId :: String
308
  , diskChildren   :: [Disk]
309
  , diskIvName     :: String
310
  , diskSize       :: Int
311
  , diskMode       :: DiskMode
312
  } deriving (Read, Show, Eq)
313

    
314
$(buildObjectSerialisation "Disk"
315
  [ customField 'decodeDLId 'encodeFullDLId $
316
      simpleField "logical_id"    [t| DiskLogicalId   |]
317
--  , simpleField "physical_id" [t| String   |]
318
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
319
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
320
  , simpleField "size" [t| Int |]
321
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
322
  ])
323

    
324
-- * Instance definitions
325

    
326
$(declareSADT "AdminState"
327
  [ ("AdminOffline", 'C.adminstOffline)
328
  , ("AdminDown",    'C.adminstDown)
329
  , ("AdminUp",      'C.adminstUp)
330
  ])
331
$(makeJSONInstance ''AdminState)
332

    
333
$(buildParam "Be" "bep"
334
  [ simpleField "minmem"       [t| Int  |]
335
  , simpleField "maxmem"       [t| Int  |]
336
  , simpleField "vcpus"        [t| Int  |]
337
  , simpleField "auto_balance" [t| Bool |]
338
  ])
339

    
340
$(buildObject "Instance" "inst" $
341
  [ simpleField "name"           [t| String             |]
342
  , simpleField "primary_node"   [t| String             |]
343
  , simpleField "os"             [t| String             |]
344
  , simpleField "hypervisor"     [t| Hypervisor         |]
345
  , simpleField "hvparams"       [t| HvParams           |]
346
  , simpleField "beparams"       [t| PartialBeParams    |]
347
  , simpleField "osparams"       [t| OsParams           |]
348
  , simpleField "admin_state"    [t| AdminState         |]
349
  , simpleField "nics"           [t| [PartialNic]       |]
350
  , simpleField "disks"          [t| [Disk]             |]
351
  , simpleField "disk_template"  [t| DiskTemplate       |]
352
  , optionalField $ simpleField "network_port" [t| Int  |]
353
  ]
354
  ++ timeStampFields
355
  ++ uuidFields
356
  ++ serialFields
357
  ++ tagsFields)
358

    
359
instance TimeStampObject Instance where
360
  cTimeOf = instCtime
361
  mTimeOf = instMtime
362

    
363
instance UuidObject Instance where
364
  uuidOf = instUuid
365

    
366
instance SerialNoObject Instance where
367
  serialOf = instSerial
368

    
369
instance TagsObject Instance where
370
  tagsOf = instTags
371

    
372
-- * IPolicy definitions
373

    
374
$(buildParam "ISpec" "ispec"
375
  [ simpleField C.ispecMemSize     [t| Int |]
376
  , simpleField C.ispecDiskSize    [t| Int |]
377
  , simpleField C.ispecDiskCount   [t| Int |]
378
  , simpleField C.ispecCpuCount    [t| Int |]
379
  , simpleField C.ispecNicCount    [t| Int |]
380
  , simpleField C.ispecSpindleUse  [t| Int |]
381
  ])
382

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

    
397
-- | Custom filled ipolicy. This is not built via buildParam since it
398
-- has a special 2-level inheritance mode.
399
$(buildObject "FilledIPolicy" "ipolicy"
400
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
401
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
402
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
403
  , simpleField "spindle-ratio"  [t| Double |]
404
  , simpleField "vcpu-ratio"     [t| Double |]
405
  , simpleField "disk-templates" [t| [DiskTemplate] |]
406
  ])
407

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

    
432
$(buildParam "ND" "ndp"
433
  [ simpleField "oob_program"   [t| String |]
434
  , simpleField "spindle_count" [t| Int    |]
435
  ])
436

    
437
$(buildObject "Node" "node" $
438
  [ simpleField "name"             [t| String |]
439
  , simpleField "primary_ip"       [t| String |]
440
  , simpleField "secondary_ip"     [t| String |]
441
  , simpleField "master_candidate" [t| Bool   |]
442
  , simpleField "offline"          [t| Bool   |]
443
  , simpleField "drained"          [t| Bool   |]
444
  , simpleField "group"            [t| String |]
445
  , simpleField "master_capable"   [t| Bool   |]
446
  , simpleField "vm_capable"       [t| Bool   |]
447
  , simpleField "ndparams"         [t| PartialNDParams |]
448
  , simpleField "powered"          [t| Bool   |]
449
  ]
450
  ++ timeStampFields
451
  ++ uuidFields
452
  ++ serialFields
453
  ++ tagsFields)
454

    
455
instance TimeStampObject Node where
456
  cTimeOf = nodeCtime
457
  mTimeOf = nodeMtime
458

    
459
instance UuidObject Node where
460
  uuidOf = nodeUuid
461

    
462
instance SerialNoObject Node where
463
  serialOf = nodeSerial
464

    
465
instance TagsObject Node where
466
  tagsOf = nodeTags
467

    
468
-- * NodeGroup definitions
469

    
470
-- | The disk parameters type.
471
type DiskParams = Container (Container JSValue)
472

    
473
$(buildObject "NodeGroup" "group" $
474
  [ simpleField "name"         [t| String |]
475
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
476
  , simpleField "ndparams"     [t| PartialNDParams |]
477
  , simpleField "alloc_policy" [t| AllocPolicy     |]
478
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
479
  , simpleField "diskparams"   [t| DiskParams      |]
480
  ]
481
  ++ timeStampFields
482
  ++ uuidFields
483
  ++ serialFields
484
  ++ tagsFields)
485

    
486
instance TimeStampObject NodeGroup where
487
  cTimeOf = groupCtime
488
  mTimeOf = groupMtime
489

    
490
instance UuidObject NodeGroup where
491
  uuidOf = groupUuid
492

    
493
instance SerialNoObject NodeGroup where
494
  serialOf = groupSerial
495

    
496
instance TagsObject NodeGroup where
497
  tagsOf = groupTags
498

    
499
-- | IP family type
500
$(declareIADT "IpFamily"
501
  [ ("IpFamilyV4", 'C.ip4Family)
502
  , ("IpFamilyV6", 'C.ip6Family)
503
  ])
504
$(makeJSONInstance ''IpFamily)
505

    
506
-- | Conversion from IP family to IP version. This is needed because
507
-- Python uses both, depending on context.
508
ipFamilyToVersion :: IpFamily -> Int
509
ipFamilyToVersion IpFamilyV4 = C.ip4Version
510
ipFamilyToVersion IpFamilyV6 = C.ip6Version
511

    
512
-- | Cluster HvParams (hvtype to hvparams mapping).
513
type ClusterHvParams = Container HvParams
514

    
515
-- | Cluster Os-HvParams (os to hvparams mapping).
516
type OsHvParams = Container ClusterHvParams
517

    
518
-- | Cluser BeParams.
519
type ClusterBeParams = Container FilledBeParams
520

    
521
-- | Cluster OsParams.
522
type ClusterOsParams = Container OsParams
523

    
524
-- | Cluster NicParams.
525
type ClusterNicParams = Container FilledNicParams
526

    
527
-- | Cluster UID Pool, list (low, high) UID ranges.
528
type UidPool = [(Int, Int)]
529

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

    
573
instance TimeStampObject Cluster where
574
  cTimeOf = clusterCtime
575
  mTimeOf = clusterMtime
576

    
577
instance UuidObject Cluster where
578
  uuidOf = clusterUuid
579

    
580
instance SerialNoObject Cluster where
581
  serialOf = clusterSerial
582

    
583
instance TagsObject Cluster where
584
  tagsOf = clusterTags
585

    
586
-- * ConfigData definitions
587

    
588
$(buildObject "ConfigData" "config" $
589
--  timeStampFields ++
590
  [ simpleField "version"    [t| Int                 |]
591
  , simpleField "cluster"    [t| Cluster             |]
592
  , simpleField "nodes"      [t| Container Node      |]
593
  , simpleField "nodegroups" [t| Container NodeGroup |]
594
  , simpleField "instances"  [t| Container Instance  |]
595
  ]
596
  ++ serialFields)
597

    
598
instance SerialNoObject ConfigData where
599
  serialOf = configSerial