Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 04dd53a3

History | View | Annotate | Download (19.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

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

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

    
8
-}
9

    
10
{-
11

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

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

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

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

    
29
-}
30

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

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

    
88
import qualified Ganeti.Constants as C
89
import Ganeti.HTools.JSON
90

    
91
import Ganeti.THH
92

    
93
-- * Generic definitions
94

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

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

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

    
111
-- | Class of objects that have timestamps.
112
class TimeStampObject a where
113
  cTimeOf :: a -> Double
114
  mTimeOf :: a -> Double
115

    
116
-- | Class of objects that have an UUID.
117
class UuidObject a where
118
  uuidOf :: a -> String
119

    
120
-- | Class of object that have a serial number.
121
class SerialNoObject a where
122
  serialOf :: a -> Int
123

    
124
-- | Class of objects that have tags.
125
class TagsObject a where
126
  tagsOf :: a -> Set.Set String
127

    
128
-- * NIC definitions
129

    
130
$(declareSADT "NICMode"
131
  [ ("NMBridged", 'C.nicModeBridged)
132
  , ("NMRouted",  'C.nicModeRouted)
133
  ])
134
$(makeJSONInstance ''NICMode)
135

    
136
$(buildParam "Nic" "nicp"
137
  [ simpleField "mode" [t| NICMode |]
138
  , simpleField "link" [t| String  |]
139
  ])
140

    
141
$(buildObject "PartialNic" "nic"
142
  [ simpleField "mac" [t| String |]
143
  , optionalField $ simpleField "ip" [t| String |]
144
  , simpleField "nicparams" [t| PartialNicParams |]
145
  ])
146

    
147
-- * Disk definitions
148

    
149
$(declareSADT "DiskMode"
150
  [ ("DiskRdOnly", 'C.diskRdonly)
151
  , ("DiskRdWr",   'C.diskRdwr)
152
  ])
153
$(makeJSONInstance ''DiskMode)
154

    
155
$(declareSADT "DiskType"
156
  [ ("LD_LV",       'C.ldLv)
157
  , ("LD_DRBD8",    'C.ldDrbd8)
158
  , ("LD_FILE",     'C.ldFile)
159
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
160
  , ("LD_RADOS",    'C.ldRbd)
161
  ])
162
$(makeJSONInstance ''DiskType)
163

    
164
-- | The file driver type.
165
$(declareSADT "FileDriver"
166
  [ ("FileLoop",   'C.fdLoop)
167
  , ("FileBlktap", 'C.fdBlktap)
168
  ])
169
$(makeJSONInstance ''FileDriver)
170

    
171
-- | The persistent block driver type. Currently only one type is allowed.
172
$(declareSADT "BlockDriver"
173
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
174
  ])
175
$(makeJSONInstance ''BlockDriver)
176

    
177
-- | Constant for the dev_type key entry in the disk config.
178
devType :: String
179
devType = "dev_type"
180

    
181
-- | The disk configuration type. This includes the disk type itself,
182
-- for a more complete consistency. Note that since in the Python
183
-- code-base there's no authoritative place where we document the
184
-- logical id, this is probably a good reference point.
185
data DiskLogicalId
186
  = LIDPlain String String  -- ^ Volume group, logical volume
187
  | LIDDrbd8 String String Int Int Int String
188
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
189
  | LIDFile FileDriver String -- ^ Driver, path
190
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
191
  | LIDRados String String -- ^ Unused, path
192
    deriving (Read, Show, Eq)
193

    
194
-- | Mapping from a logical id to a disk type.
195
lidDiskType :: DiskLogicalId -> DiskType
196
lidDiskType (LIDPlain {}) = LD_LV
197
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
198
lidDiskType (LIDFile  {}) = LD_FILE
199
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
200
lidDiskType (LIDRados {}) = LD_RADOS
201

    
202
-- | Builds the extra disk_type field for a given logical id.
203
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
204
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
205

    
206
-- | Custom encoder for DiskLogicalId (logical id only).
207
encodeDLId :: DiskLogicalId -> JSValue
208
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
209
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
210
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
211
          , showJSON minorA, showJSON minorB, showJSON key ]
212
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
213
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
214
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
215

    
216
-- | Custom encoder for DiskLogicalId, composing both the logical id
217
-- and the extra disk_type field.
218
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
219
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
220

    
221
-- | Custom decoder for DiskLogicalId. This is manual for now, since
222
-- we don't have yet automation for separate-key style fields.
223
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
224
decodeDLId obj lid = do
225
  dtype <- fromObj obj devType
226
  case dtype of
227
    LD_DRBD8 ->
228
      case lid of
229
        JSArray [nA, nB, p, mA, mB, k] -> do
230
          nA' <- readJSON nA
231
          nB' <- readJSON nB
232
          p'  <- readJSON p
233
          mA' <- readJSON mA
234
          mB' <- readJSON mB
235
          k'  <- readJSON k
236
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
237
        _ -> fail $ "Can't read logical_id for DRBD8 type"
238
    LD_LV ->
239
      case lid of
240
        JSArray [vg, lv] -> do
241
          vg' <- readJSON vg
242
          lv' <- readJSON lv
243
          return $ LIDPlain vg' lv'
244
        _ -> fail $ "Can't read logical_id for plain type"
245
    LD_FILE ->
246
      case lid of
247
        JSArray [driver, path] -> do
248
          driver' <- readJSON driver
249
          path'   <- readJSON path
250
          return $ LIDFile driver' path'
251
        _ -> fail $ "Can't read logical_id for file type"
252
    LD_BLOCKDEV ->
253
      case lid of
254
        JSArray [driver, path] -> do
255
          driver' <- readJSON driver
256
          path'   <- readJSON path
257
          return $ LIDBlockDev driver' path'
258
        _ -> fail $ "Can't read logical_id for blockdev type"
259
    LD_RADOS ->
260
      case lid of
261
        JSArray [driver, path] -> do
262
          driver' <- readJSON driver
263
          path'   <- readJSON path
264
          return $ LIDRados driver' path'
265
        _ -> fail $ "Can't read logical_id for rdb type"
266

    
267
-- | Disk data structure.
268
--
269
-- This is declared manually as it's a recursive structure, and our TH
270
-- code currently can't build it.
271
data Disk = Disk
272
  { diskLogicalId  :: DiskLogicalId
273
--  , diskPhysicalId :: String
274
  , diskChildren   :: [Disk]
275
  , diskIvName     :: String
276
  , diskSize       :: Int
277
  , diskMode       :: DiskMode
278
  } deriving (Read, Show, Eq)
279

    
280
$(buildObjectSerialisation "Disk"
281
  [ customField 'decodeDLId 'encodeFullDLId $
282
      simpleField "logical_id"    [t| DiskLogicalId   |]
283
--  , simpleField "physical_id" [t| String   |]
284
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
285
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
286
  , simpleField "size" [t| Int |]
287
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
288
  ])
289

    
290
-- * Hypervisor definitions
291

    
292
-- | This may be due to change when we add hypervisor parameters.
293
$(declareSADT "Hypervisor"
294
  [ ( "Kvm",    'C.htKvm )
295
  , ( "XenPvm", 'C.htXenPvm )
296
  , ( "Chroot", 'C.htChroot )
297
  , ( "XenHvm", 'C.htXenHvm )
298
  , ( "Lxc",    'C.htLxc )
299
  , ( "Fake",   'C.htFake )
300
  ])
301
$(makeJSONInstance ''Hypervisor)
302

    
303
-- * Instance definitions
304

    
305
-- | Instance disk template type. **Copied from HTools/Types.hs**
306
$(declareSADT "DiskTemplate"
307
  [ ("DTDiskless",   'C.dtDiskless)
308
  , ("DTFile",       'C.dtFile)
309
  , ("DTSharedFile", 'C.dtSharedFile)
310
  , ("DTPlain",      'C.dtPlain)
311
  , ("DTBlock",      'C.dtBlock)
312
  , ("DTDrbd8",      'C.dtDrbd8)
313
  , ("DTRados",      'C.dtRbd)
314
  ])
315
$(makeJSONInstance ''DiskTemplate)
316

    
317
$(declareSADT "AdminState"
318
  [ ("AdminOffline", 'C.adminstOffline)
319
  , ("AdminDown",    'C.adminstDown)
320
  , ("AdminUp",      'C.adminstUp)
321
  ])
322
$(makeJSONInstance ''AdminState)
323

    
324
$(buildParam "Be" "bep" $
325
  [ simpleField "minmem"       [t| Int  |]
326
  , simpleField "maxmem"       [t| Int  |]
327
  , simpleField "vcpus"        [t| Int  |]
328
  , simpleField "auto_balance" [t| Bool |]
329
  ])
330

    
331
$(buildObject "Instance" "inst" $
332
  [ simpleField "name"           [t| String             |]
333
  , simpleField "primary_node"   [t| String             |]
334
  , simpleField "os"             [t| String             |]
335
  , simpleField "hypervisor"     [t| Hypervisor         |]
336
  , simpleField "hvparams"       [t| HvParams           |]
337
  , simpleField "beparams"       [t| PartialBeParams    |]
338
  , simpleField "osparams"       [t| OsParams           |]
339
  , simpleField "admin_state"    [t| AdminState         |]
340
  , simpleField "nics"           [t| [PartialNic]       |]
341
  , simpleField "disks"          [t| [Disk]             |]
342
  , simpleField "disk_template"  [t| DiskTemplate       |]
343
  , optionalField $ simpleField "network_port" [t| Int  |]
344
  ]
345
  ++ timeStampFields
346
  ++ uuidFields
347
  ++ serialFields
348
  ++ tagsFields)
349

    
350
instance TimeStampObject Instance where
351
  cTimeOf = instCtime
352
  mTimeOf = instMtime
353

    
354
instance UuidObject Instance where
355
  uuidOf = instUuid
356

    
357
instance SerialNoObject Instance where
358
  serialOf = instSerial
359

    
360
instance TagsObject Instance where
361
  tagsOf = instTags
362

    
363
-- * IPolicy definitions
364

    
365
$(buildParam "ISpec" "ispec" $
366
  [ simpleField C.ispecMemSize     [t| Int |]
367
  , simpleField C.ispecDiskSize    [t| Int |]
368
  , simpleField C.ispecDiskCount   [t| Int |]
369
  , simpleField C.ispecCpuCount    [t| Int |]
370
  , simpleField C.ispecSpindleUse  [t| Int |]
371
  ])
372

    
373
-- | Custom partial ipolicy. This is not built via buildParam since it
374
-- has a special 2-level inheritance mode.
375
$(buildObject "PartialIPolicy" "ipolicy" $
376
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
377
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
378
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
379
  , optionalField . renameField "SpindleRatioP"
380
                    $ simpleField "spindle-ratio"  [t| Double |]
381
  , optionalField . renameField "VcpuRatioP"
382
                    $ simpleField "vcpu-ratio"     [t| Double |]
383
  , optionalField . renameField "DiskTemplatesP"
384
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
385
  ])
386

    
387
-- | Custom filled ipolicy. This is not built via buildParam since it
388
-- has a special 2-level inheritance mode.
389
$(buildObject "FilledIPolicy" "ipolicy" $
390
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
391
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
392
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
393
  , simpleField "spindle-ratio"  [t| Double |]
394
  , simpleField "vcpu-ratio"     [t| Double |]
395
  , simpleField "disk-templates" [t| [DiskTemplate] |]
396
  ])
397

    
398
-- | Custom filler for the ipolicy types.
399
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
400
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
401
                           , ipolicyMaxSpec       = fmax
402
                           , ipolicyStdSpec       = fstd
403
                           , ipolicySpindleRatio  = fspindleRatio
404
                           , ipolicyVcpuRatio     = fvcpuRatio
405
                           , ipolicyDiskTemplates = fdiskTemplates})
406
            (PartialIPolicy { ipolicyMinSpecP       = pmin
407
                            , ipolicyMaxSpecP       = pmax
408
                            , ipolicyStdSpecP       = pstd
409
                            , ipolicySpindleRatioP  = pspindleRatio
410
                            , ipolicyVcpuRatioP     = pvcpuRatio
411
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
412
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
413
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
414
                , ipolicyStdSpec       = fillISpecParams fstd pstd
415
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
416
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
417
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
418
                                         pdiskTemplates
419
                }
420
-- * Node definitions
421

    
422
$(buildParam "ND" "ndp" $
423
  [ simpleField "oob_program"   [t| String |]
424
  , simpleField "spindle_count" [t| Int    |]
425
  ])
426

    
427
$(buildObject "Node" "node" $
428
  [ simpleField "name"             [t| String |]
429
  , simpleField "primary_ip"       [t| String |]
430
  , simpleField "secondary_ip"     [t| String |]
431
  , simpleField "master_candidate" [t| Bool   |]
432
  , simpleField "offline"          [t| Bool   |]
433
  , simpleField "drained"          [t| Bool   |]
434
  , simpleField "group"            [t| String |]
435
  , simpleField "master_capable"   [t| Bool   |]
436
  , simpleField "vm_capable"       [t| Bool   |]
437
  , simpleField "ndparams"         [t| PartialNDParams |]
438
  , simpleField "powered"          [t| Bool   |]
439
  ]
440
  ++ timeStampFields
441
  ++ uuidFields
442
  ++ serialFields
443
  ++ tagsFields)
444

    
445
instance TimeStampObject Node where
446
  cTimeOf = nodeCtime
447
  mTimeOf = nodeMtime
448

    
449
instance UuidObject Node where
450
  uuidOf = nodeUuid
451

    
452
instance SerialNoObject Node where
453
  serialOf = nodeSerial
454

    
455
instance TagsObject Node where
456
  tagsOf = nodeTags
457

    
458
-- * NodeGroup definitions
459

    
460
-- | The Group allocation policy type.
461
--
462
-- Note that the order of constructors is important as the automatic
463
-- Ord instance will order them in the order they are defined, so when
464
-- changing this data type be careful about the interaction with the
465
-- desired sorting order.
466
--
467
-- FIXME: COPIED from Types.hs; we need to eliminate this duplication later
468
$(declareSADT "AllocPolicy"
469
  [ ("AllocPreferred",   'C.allocPolicyPreferred)
470
  , ("AllocLastResort",  'C.allocPolicyLastResort)
471
  , ("AllocUnallocable", 'C.allocPolicyUnallocable)
472
  ])
473
$(makeJSONInstance ''AllocPolicy)
474

    
475
-- | The disk parameters type.
476
type DiskParams = Container (Container JSValue)
477

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

    
491
instance TimeStampObject NodeGroup where
492
  cTimeOf = groupCtime
493
  mTimeOf = groupMtime
494

    
495
instance UuidObject NodeGroup where
496
  uuidOf = groupUuid
497

    
498
instance SerialNoObject NodeGroup where
499
  serialOf = groupSerial
500

    
501
instance TagsObject NodeGroup where
502
  tagsOf = groupTags
503

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

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

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

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

    
523
-- | Cluser BeParams.
524
type ClusterBeParams = Container FilledBeParams
525

    
526
-- | Cluster OsParams.
527
type ClusterOsParams = Container OsParams
528

    
529
-- | Cluster NicParams.
530
type ClusterNicParams = Container FilledNicParams
531

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

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

    
578
instance TimeStampObject Cluster where
579
  cTimeOf = clusterCtime
580
  mTimeOf = clusterMtime
581

    
582
instance UuidObject Cluster where
583
  uuidOf = clusterUuid
584

    
585
instance SerialNoObject Cluster where
586
  serialOf = clusterSerial
587

    
588
instance TagsObject Cluster where
589
  tagsOf = clusterTags
590

    
591
-- * ConfigData definitions
592

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

    
603
instance SerialNoObject ConfigData where
604
  serialOf = configSerial