Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 6f732ae0

History | View | Annotate | Download (20.5 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

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

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

    
8
-}
9

    
10
{-
11

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

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

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

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

    
29
-}
30

    
31
module Ganeti.Objects
32
  ( 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
  ])
216

    
217
-- * Disk definitions
218

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

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

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

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

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

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

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

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

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

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

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

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

    
353
-- * Instance definitions
354

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

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

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

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

    
392
instance UuidObject Instance where
393
  uuidOf = instUuid
394

    
395
instance SerialNoObject Instance where
396
  serialOf = instSerial
397

    
398
instance TagsObject Instance where
399
  tagsOf = instTags
400

    
401
-- * IPolicy definitions
402

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

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

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

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

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

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

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

    
489
instance UuidObject Node where
490
  uuidOf = nodeUuid
491

    
492
instance SerialNoObject Node where
493
  serialOf = nodeSerial
494

    
495
instance TagsObject Node where
496
  tagsOf = nodeTags
497

    
498
-- * NodeGroup definitions
499

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

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

    
516
instance TimeStampObject NodeGroup where
517
  cTimeOf = groupCtime
518
  mTimeOf = groupMtime
519

    
520
instance UuidObject NodeGroup where
521
  uuidOf = groupUuid
522

    
523
instance SerialNoObject NodeGroup where
524
  serialOf = groupSerial
525

    
526
instance TagsObject NodeGroup where
527
  tagsOf = groupTags
528

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

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

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

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

    
548
-- | Cluser BeParams.
549
type ClusterBeParams = Container FilledBeParams
550

    
551
-- | Cluster OsParams.
552
type ClusterOsParams = Container OsParams
553

    
554
-- | Cluster NicParams.
555
type ClusterNicParams = Container FilledNicParams
556

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

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

    
603
instance TimeStampObject Cluster where
604
  cTimeOf = clusterCtime
605
  mTimeOf = clusterMtime
606

    
607
instance UuidObject Cluster where
608
  uuidOf = clusterUuid
609

    
610
instance SerialNoObject Cluster where
611
  serialOf = clusterSerial
612

    
613
instance TagsObject Cluster where
614
  tagsOf = clusterTags
615

    
616
-- * ConfigData definitions
617

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

    
628
instance SerialNoObject ConfigData where
629
  serialOf = configSerial