Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 0c6d6a52

History | View | Annotate | Download (21.3 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
  ++ uuidFields
196
  ++ serialFields
197
  ++ tagsFields)
198

    
199
instance SerialNoObject Network where
200
  serialOf = networkSerial
201

    
202
instance TagsObject Network where
203
  tagsOf = networkTags
204

    
205
instance UuidObject Network where
206
  uuidOf = networkUuid
207

    
208
-- * NIC definitions
209

    
210
$(buildParam "Nic" "nicp"
211
  [ simpleField "mode" [t| NICMode |]
212
  , simpleField "link" [t| String  |]
213
  ])
214

    
215
$(buildObject "PartialNic" "nic"
216
  [ simpleField "mac" [t| String |]
217
  , optionalField $ simpleField "ip" [t| String |]
218
  , simpleField "nicparams" [t| PartialNicParams |]
219
  , optionalField $ simpleField "network" [t| String |]
220
  ])
221

    
222
-- * Disk definitions
223

    
224
$(declareSADT "DiskMode"
225
  [ ("DiskRdOnly", 'C.diskRdonly)
226
  , ("DiskRdWr",   'C.diskRdwr)
227
  ])
228
$(makeJSONInstance ''DiskMode)
229

    
230
$(declareSADT "DiskType"
231
  [ ("LD_LV",       'C.ldLv)
232
  , ("LD_DRBD8",    'C.ldDrbd8)
233
  , ("LD_FILE",     'C.ldFile)
234
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
235
  , ("LD_RADOS",    'C.ldRbd)
236
  , ("LD_EXT",      'C.ldExt)
237
  ])
238
$(makeJSONInstance ''DiskType)
239

    
240
-- | The persistent block driver type. Currently only one type is allowed.
241
$(declareSADT "BlockDriver"
242
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
243
  ])
244
$(makeJSONInstance ''BlockDriver)
245

    
246
-- | Constant for the dev_type key entry in the disk config.
247
devType :: String
248
devType = "dev_type"
249

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

    
264
-- | Mapping from a logical id to a disk type.
265
lidDiskType :: DiskLogicalId -> DiskType
266
lidDiskType (LIDPlain {}) = LD_LV
267
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
268
lidDiskType (LIDFile  {}) = LD_FILE
269
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
270
lidDiskType (LIDRados {}) = LD_RADOS
271
lidDiskType (LIDExt {}) = LD_EXT
272

    
273
-- | Builds the extra disk_type field for a given logical id.
274
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
275
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
276

    
277
-- | Custom encoder for DiskLogicalId (logical id only).
278
encodeDLId :: DiskLogicalId -> JSValue
279
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
280
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
281
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
282
          , showJSON minorA, showJSON minorB, showJSON key ]
283
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
284
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
285
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
286
encodeDLId (LIDExt extprovider name) =
287
  JSArray [showJSON extprovider, showJSON name]
288

    
289
-- | Custom encoder for DiskLogicalId, composing both the logical id
290
-- and the extra disk_type field.
291
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
292
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
293

    
294
-- | Custom decoder for DiskLogicalId. This is manual for now, since
295
-- we don't have yet automation for separate-key style fields.
296
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
297
decodeDLId obj lid = do
298
  dtype <- fromObj obj devType
299
  case dtype of
300
    LD_DRBD8 ->
301
      case lid of
302
        JSArray [nA, nB, p, mA, mB, k] -> do
303
          nA' <- readJSON nA
304
          nB' <- readJSON nB
305
          p'  <- readJSON p
306
          mA' <- readJSON mA
307
          mB' <- readJSON mB
308
          k'  <- readJSON k
309
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
310
        _ -> fail "Can't read logical_id for DRBD8 type"
311
    LD_LV ->
312
      case lid of
313
        JSArray [vg, lv] -> do
314
          vg' <- readJSON vg
315
          lv' <- readJSON lv
316
          return $ LIDPlain vg' lv'
317
        _ -> fail "Can't read logical_id for plain type"
318
    LD_FILE ->
319
      case lid of
320
        JSArray [driver, path] -> do
321
          driver' <- readJSON driver
322
          path'   <- readJSON path
323
          return $ LIDFile driver' path'
324
        _ -> fail "Can't read logical_id for file type"
325
    LD_BLOCKDEV ->
326
      case lid of
327
        JSArray [driver, path] -> do
328
          driver' <- readJSON driver
329
          path'   <- readJSON path
330
          return $ LIDBlockDev driver' path'
331
        _ -> fail "Can't read logical_id for blockdev type"
332
    LD_RADOS ->
333
      case lid of
334
        JSArray [driver, path] -> do
335
          driver' <- readJSON driver
336
          path'   <- readJSON path
337
          return $ LIDRados driver' path'
338
        _ -> fail "Can't read logical_id for rdb type"
339
    LD_EXT ->
340
      case lid of
341
        JSArray [extprovider, name] -> do
342
          extprovider' <- readJSON extprovider
343
          name'   <- readJSON name
344
          return $ LIDExt extprovider' name'
345
        _ -> fail "Can't read logical_id for extstorage type"
346

    
347
-- | Disk data structure.
348
--
349
-- This is declared manually as it's a recursive structure, and our TH
350
-- code currently can't build it.
351
data Disk = Disk
352
  { diskLogicalId  :: DiskLogicalId
353
--  , diskPhysicalId :: String
354
  , diskChildren   :: [Disk]
355
  , diskIvName     :: String
356
  , diskSize       :: Int
357
  , diskMode       :: DiskMode
358
  } deriving (Show, Eq)
359

    
360
$(buildObjectSerialisation "Disk"
361
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
362
      simpleField "logical_id"    [t| DiskLogicalId   |]
363
--  , simpleField "physical_id" [t| String   |]
364
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
365
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
366
  , simpleField "size" [t| Int |]
367
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
368
  ])
369

    
370
-- * Instance definitions
371

    
372
$(declareSADT "AdminState"
373
  [ ("AdminOffline", 'C.adminstOffline)
374
  , ("AdminDown",    'C.adminstDown)
375
  , ("AdminUp",      'C.adminstUp)
376
  ])
377
$(makeJSONInstance ''AdminState)
378

    
379
$(buildParam "Be" "bep"
380
  [ simpleField "minmem"       [t| Int  |]
381
  , simpleField "maxmem"       [t| Int  |]
382
  , simpleField "vcpus"        [t| Int  |]
383
  , simpleField "auto_balance" [t| Bool |]
384
  ])
385

    
386
$(buildObject "Instance" "inst" $
387
  [ simpleField "name"           [t| String             |]
388
  , simpleField "primary_node"   [t| String             |]
389
  , simpleField "os"             [t| String             |]
390
  , simpleField "hypervisor"     [t| Hypervisor         |]
391
  , simpleField "hvparams"       [t| HvParams           |]
392
  , simpleField "beparams"       [t| PartialBeParams    |]
393
  , simpleField "osparams"       [t| OsParams           |]
394
  , simpleField "admin_state"    [t| AdminState         |]
395
  , simpleField "nics"           [t| [PartialNic]       |]
396
  , simpleField "disks"          [t| [Disk]             |]
397
  , simpleField "disk_template"  [t| DiskTemplate       |]
398
  , optionalField $ simpleField "network_port" [t| Int  |]
399
  ]
400
  ++ timeStampFields
401
  ++ uuidFields
402
  ++ serialFields
403
  ++ tagsFields)
404

    
405
instance TimeStampObject Instance where
406
  cTimeOf = instCtime
407
  mTimeOf = instMtime
408

    
409
instance UuidObject Instance where
410
  uuidOf = instUuid
411

    
412
instance SerialNoObject Instance where
413
  serialOf = instSerial
414

    
415
instance TagsObject Instance where
416
  tagsOf = instTags
417

    
418
-- * IPolicy definitions
419

    
420
$(buildParam "ISpec" "ispec"
421
  [ simpleField C.ispecMemSize     [t| Int |]
422
  , simpleField C.ispecDiskSize    [t| Int |]
423
  , simpleField C.ispecDiskCount   [t| Int |]
424
  , simpleField C.ispecCpuCount    [t| Int |]
425
  , simpleField C.ispecNicCount    [t| Int |]
426
  , simpleField C.ispecSpindleUse  [t| Int |]
427
  ])
428

    
429
-- | Custom partial ipolicy. This is not built via buildParam since it
430
-- has a special 2-level inheritance mode.
431
$(buildObject "PartialIPolicy" "ipolicy"
432
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
433
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
434
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
435
  , optionalField . renameField "SpindleRatioP"
436
                    $ simpleField "spindle-ratio"  [t| Double |]
437
  , optionalField . renameField "VcpuRatioP"
438
                    $ simpleField "vcpu-ratio"     [t| Double |]
439
  , optionalField . renameField "DiskTemplatesP"
440
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
441
  ])
442

    
443
-- | Custom filled ipolicy. This is not built via buildParam since it
444
-- has a special 2-level inheritance mode.
445
$(buildObject "FilledIPolicy" "ipolicy"
446
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
447
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
448
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
449
  , simpleField "spindle-ratio"  [t| Double |]
450
  , simpleField "vcpu-ratio"     [t| Double |]
451
  , simpleField "disk-templates" [t| [DiskTemplate] |]
452
  ])
453

    
454
-- | Custom filler for the ipolicy types.
455
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
456
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
457
                           , ipolicyMaxSpec       = fmax
458
                           , ipolicyStdSpec       = fstd
459
                           , ipolicySpindleRatio  = fspindleRatio
460
                           , ipolicyVcpuRatio     = fvcpuRatio
461
                           , ipolicyDiskTemplates = fdiskTemplates})
462
            (PartialIPolicy { ipolicyMinSpecP       = pmin
463
                            , ipolicyMaxSpecP       = pmax
464
                            , ipolicyStdSpecP       = pstd
465
                            , ipolicySpindleRatioP  = pspindleRatio
466
                            , ipolicyVcpuRatioP     = pvcpuRatio
467
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
468
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
469
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
470
                , ipolicyStdSpec       = fillISpecParams fstd pstd
471
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
472
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
473
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
474
                                         pdiskTemplates
475
                }
476
-- * Node definitions
477

    
478
$(buildParam "ND" "ndp"
479
  [ simpleField "oob_program"   [t| String |]
480
  , simpleField "spindle_count" [t| Int    |]
481
  , simpleField "exclusive_storage" [t| Bool |]
482
  ])
483

    
484
$(buildObject "Node" "node" $
485
  [ simpleField "name"             [t| String |]
486
  , simpleField "primary_ip"       [t| String |]
487
  , simpleField "secondary_ip"     [t| String |]
488
  , simpleField "master_candidate" [t| Bool   |]
489
  , simpleField "offline"          [t| Bool   |]
490
  , simpleField "drained"          [t| Bool   |]
491
  , simpleField "group"            [t| String |]
492
  , simpleField "master_capable"   [t| Bool   |]
493
  , simpleField "vm_capable"       [t| Bool   |]
494
  , simpleField "ndparams"         [t| PartialNDParams |]
495
  , simpleField "powered"          [t| Bool   |]
496
  ]
497
  ++ timeStampFields
498
  ++ uuidFields
499
  ++ serialFields
500
  ++ tagsFields)
501

    
502
instance TimeStampObject Node where
503
  cTimeOf = nodeCtime
504
  mTimeOf = nodeMtime
505

    
506
instance UuidObject Node where
507
  uuidOf = nodeUuid
508

    
509
instance SerialNoObject Node where
510
  serialOf = nodeSerial
511

    
512
instance TagsObject Node where
513
  tagsOf = nodeTags
514

    
515
-- * NodeGroup definitions
516

    
517
-- | The disk parameters type.
518
type DiskParams = Container (Container JSValue)
519

    
520
-- | A mapping from network UUIDs to nic params of the networks.
521
type Networks = Container PartialNicParams
522

    
523
$(buildObject "NodeGroup" "group" $
524
  [ simpleField "name"         [t| String |]
525
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
526
  , simpleField "ndparams"     [t| PartialNDParams |]
527
  , simpleField "alloc_policy" [t| AllocPolicy     |]
528
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
529
  , simpleField "diskparams"   [t| DiskParams      |]
530
  , simpleField "networks"     [t| Networks        |]
531
  ]
532
  ++ timeStampFields
533
  ++ uuidFields
534
  ++ serialFields
535
  ++ tagsFields)
536

    
537
instance TimeStampObject NodeGroup where
538
  cTimeOf = groupCtime
539
  mTimeOf = groupMtime
540

    
541
instance UuidObject NodeGroup where
542
  uuidOf = groupUuid
543

    
544
instance SerialNoObject NodeGroup where
545
  serialOf = groupSerial
546

    
547
instance TagsObject NodeGroup where
548
  tagsOf = groupTags
549

    
550
-- | IP family type
551
$(declareIADT "IpFamily"
552
  [ ("IpFamilyV4", 'C.ip4Family)
553
  , ("IpFamilyV6", 'C.ip6Family)
554
  ])
555
$(makeJSONInstance ''IpFamily)
556

    
557
-- | Conversion from IP family to IP version. This is needed because
558
-- Python uses both, depending on context.
559
ipFamilyToVersion :: IpFamily -> Int
560
ipFamilyToVersion IpFamilyV4 = C.ip4Version
561
ipFamilyToVersion IpFamilyV6 = C.ip6Version
562

    
563
-- | Cluster HvParams (hvtype to hvparams mapping).
564
type ClusterHvParams = Container HvParams
565

    
566
-- | Cluster Os-HvParams (os to hvparams mapping).
567
type OsHvParams = Container ClusterHvParams
568

    
569
-- | Cluser BeParams.
570
type ClusterBeParams = Container FilledBeParams
571

    
572
-- | Cluster OsParams.
573
type ClusterOsParams = Container OsParams
574

    
575
-- | Cluster NicParams.
576
type ClusterNicParams = Container FilledNicParams
577

    
578
-- | Cluster UID Pool, list (low, high) UID ranges.
579
type UidPool = [(Int, Int)]
580

    
581
-- * Cluster definitions
582
$(buildObject "Cluster" "cluster" $
583
  [ simpleField "rsahostkeypub"           [t| String           |]
584
  , simpleField "highest_used_port"       [t| Int              |]
585
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
586
  , simpleField "mac_prefix"              [t| String           |]
587
  , simpleField "volume_group_name"       [t| String           |]
588
  , simpleField "reserved_lvs"            [t| [String]         |]
589
  , optionalField $
590
    simpleField "drbd_usermode_helper"    [t| String           |]
591
  , simpleField "master_node"             [t| String           |]
592
  , simpleField "master_ip"               [t| String           |]
593
  , simpleField "master_netdev"           [t| String           |]
594
  , simpleField "master_netmask"          [t| Int              |]
595
  , simpleField "use_external_mip_script" [t| Bool             |]
596
  , simpleField "cluster_name"            [t| String           |]
597
  , simpleField "file_storage_dir"        [t| String           |]
598
  , simpleField "shared_file_storage_dir" [t| String           |]
599
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
600
  , simpleField "hvparams"                [t| ClusterHvParams  |]
601
  , simpleField "os_hvp"                  [t| OsHvParams       |]
602
  , simpleField "beparams"                [t| ClusterBeParams  |]
603
  , simpleField "osparams"                [t| ClusterOsParams  |]
604
  , simpleField "nicparams"               [t| ClusterNicParams |]
605
  , simpleField "ndparams"                [t| FilledNDParams   |]
606
  , simpleField "diskparams"              [t| DiskParams       |]
607
  , simpleField "candidate_pool_size"     [t| Int              |]
608
  , simpleField "modify_etc_hosts"        [t| Bool             |]
609
  , simpleField "modify_ssh_setup"        [t| Bool             |]
610
  , simpleField "maintain_node_health"    [t| Bool             |]
611
  , simpleField "uid_pool"                [t| UidPool          |]
612
  , simpleField "default_iallocator"      [t| String           |]
613
  , simpleField "hidden_os"               [t| [String]         |]
614
  , simpleField "blacklisted_os"          [t| [String]         |]
615
  , simpleField "primary_ip_family"       [t| IpFamily         |]
616
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
617
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
618
 ]
619
 ++ timeStampFields
620
 ++ uuidFields
621
 ++ serialFields
622
 ++ tagsFields)
623

    
624
instance TimeStampObject Cluster where
625
  cTimeOf = clusterCtime
626
  mTimeOf = clusterMtime
627

    
628
instance UuidObject Cluster where
629
  uuidOf = clusterUuid
630

    
631
instance SerialNoObject Cluster where
632
  serialOf = clusterSerial
633

    
634
instance TagsObject Cluster where
635
  tagsOf = clusterTags
636

    
637
-- * ConfigData definitions
638

    
639
$(buildObject "ConfigData" "config" $
640
--  timeStampFields ++
641
  [ simpleField "version"    [t| Int                 |]
642
  , simpleField "cluster"    [t| Cluster             |]
643
  , simpleField "nodes"      [t| Container Node      |]
644
  , simpleField "nodegroups" [t| Container NodeGroup |]
645
  , simpleField "instances"  [t| Container Instance  |]
646
  , simpleField "networks"   [t| Container Network   |]
647
  ]
648
  ++ serialFields)
649

    
650
instance SerialNoObject ConfigData where
651
  serialOf = configSerial