Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 8d2b6a12

History | View | Annotate | Download (20.9 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
  , Hypervisor(..)
54
  , AdminState(..)
55
  , adminStateFromRaw
56
  , Instance(..)
57
  , toDictInstance
58
  , PartialNDParams(..)
59
  , FilledNDParams(..)
60
  , fillNDParams
61
  , allNDParamFields
62
  , Node(..)
63
  , NodeRole(..)
64
  , nodeRoleToRaw
65
  , roleDescription
66
  , AllocPolicy(..)
67
  , FilledISpecParams(..)
68
  , PartialISpecParams(..)
69
  , fillISpecParams
70
  , allISpecParamFields
71
  , FilledIPolicy(..)
72
  , PartialIPolicy(..)
73
  , fillIPolicy
74
  , DiskParams
75
  , NodeGroup(..)
76
  , IpFamily(..)
77
  , ipFamilyToVersion
78
  , fillDict
79
  , ClusterHvParams
80
  , OsHvParams
81
  , ClusterBeParams
82
  , ClusterOsParams
83
  , ClusterNicParams
84
  , Cluster(..)
85
  , ConfigData(..)
86
  , TimeStampObject(..)
87
  , UuidObject(..)
88
  , SerialNoObject(..)
89
  , TagsObject(..)
90
  , DictObject(..) -- 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 (makeObj, showJSON, readJSON, JSON, JSValue(..))
98
import qualified Text.JSON as J
99

    
100
import qualified Ganeti.Constants as C
101
import Ganeti.JSON
102

    
103
import Ganeti.THH
104

    
105
-- * Generic definitions
106

    
107
-- | Fills one map with keys from the other map, if not already
108
-- existing. Mirrors objects.py:FillDict.
109
fillDict :: (Ord k) => Map.Map k v -> Map.Map k v -> [k] -> Map.Map k v
110
fillDict defaults custom skip_keys =
111
  let updated = Map.union custom defaults
112
  in foldl' (flip Map.delete) updated skip_keys
113

    
114
-- | The VTYPES, a mini-type system in Python.
115
$(declareSADT "VType"
116
  [ ("VTypeString",      'C.vtypeString)
117
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
118
  , ("VTypeBool",        'C.vtypeBool)
119
  , ("VTypeSize",        'C.vtypeSize)
120
  , ("VTypeInt",         'C.vtypeInt)
121
  ])
122
$(makeJSONInstance ''VType)
123

    
124
-- | The hypervisor parameter type. This is currently a simple map,
125
-- without type checking on key/value pairs.
126
type HvParams = Container JSValue
127

    
128
-- | The OS parameters type. This is, and will remain, a string
129
-- container, since the keys are dynamically declared by the OSes, and
130
-- the values are always strings.
131
type OsParams = Container String
132

    
133
-- | Class of objects that have timestamps.
134
class TimeStampObject a where
135
  cTimeOf :: a -> Double
136
  mTimeOf :: a -> Double
137

    
138
-- | Class of objects that have an UUID.
139
class UuidObject a where
140
  uuidOf :: a -> String
141

    
142
-- | Class of object that have a serial number.
143
class SerialNoObject a where
144
  serialOf :: a -> Int
145

    
146
-- | Class of objects that have tags.
147
class TagsObject a where
148
  tagsOf :: a -> Set.Set String
149

    
150
-- * Node role object
151

    
152
$(declareSADT "NodeRole"
153
  [ ("NROffline",   'C.nrOffline)
154
  , ("NRDrained",   'C.nrDrained)
155
  , ("NRRegular",   'C.nrRegular)
156
  , ("NRCandidate", 'C.nrMcandidate)
157
  , ("NRMaster",    'C.nrMaster)
158
  ])
159
$(makeJSONInstance ''NodeRole)
160

    
161
-- | The description of the node role.
162
roleDescription :: NodeRole -> String
163
roleDescription NROffline   = "offline"
164
roleDescription NRDrained   = "drained"
165
roleDescription NRRegular   = "regular"
166
roleDescription NRCandidate = "master candidate"
167
roleDescription NRMaster    = "master"
168

    
169
-- * NIC definitions
170

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

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

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

    
188
-- * Disk definitions
189

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

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

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

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

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

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

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

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

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

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

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

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

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

    
331
-- * Hypervisor definitions
332

    
333
-- | This may be due to change when we add hypervisor parameters.
334
$(declareSADT "Hypervisor"
335
  [ ( "Kvm",    'C.htKvm )
336
  , ( "XenPvm", 'C.htXenPvm )
337
  , ( "Chroot", 'C.htChroot )
338
  , ( "XenHvm", 'C.htXenHvm )
339
  , ( "Lxc",    'C.htLxc )
340
  , ( "Fake",   'C.htFake )
341
  ])
342
$(makeJSONInstance ''Hypervisor)
343

    
344
-- * Instance definitions
345

    
346
-- | Instance disk template type. **Copied from HTools/Types.hs**
347
$(declareSADT "DiskTemplate"
348
  [ ("DTDiskless",   'C.dtDiskless)
349
  , ("DTFile",       'C.dtFile)
350
  , ("DTSharedFile", 'C.dtSharedFile)
351
  , ("DTPlain",      'C.dtPlain)
352
  , ("DTBlock",      'C.dtBlock)
353
  , ("DTDrbd8",      'C.dtDrbd8)
354
  , ("DTRados",      'C.dtRbd)
355
  ])
356
$(makeJSONInstance ''DiskTemplate)
357

    
358
$(declareSADT "AdminState"
359
  [ ("AdminOffline", 'C.adminstOffline)
360
  , ("AdminDown",    'C.adminstDown)
361
  , ("AdminUp",      'C.adminstUp)
362
  ])
363
$(makeJSONInstance ''AdminState)
364

    
365
$(buildParam "Be" "bep" $
366
  [ simpleField "minmem"       [t| Int  |]
367
  , simpleField "maxmem"       [t| Int  |]
368
  , simpleField "vcpus"        [t| Int  |]
369
  , simpleField "auto_balance" [t| Bool |]
370
  ])
371

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

    
391
instance TimeStampObject Instance where
392
  cTimeOf = instCtime
393
  mTimeOf = instMtime
394

    
395
instance UuidObject Instance where
396
  uuidOf = instUuid
397

    
398
instance SerialNoObject Instance where
399
  serialOf = instSerial
400

    
401
instance TagsObject Instance where
402
  tagsOf = instTags
403

    
404
-- * IPolicy definitions
405

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

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

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

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

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

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

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

    
490
instance UuidObject Node where
491
  uuidOf = nodeUuid
492

    
493
instance SerialNoObject Node where
494
  serialOf = nodeSerial
495

    
496
instance TagsObject Node where
497
  tagsOf = nodeTags
498

    
499
-- * NodeGroup definitions
500

    
501
-- | The Group allocation policy type.
502
--
503
-- Note that the order of constructors is important as the automatic
504
-- Ord instance will order them in the order they are defined, so when
505
-- changing this data type be careful about the interaction with the
506
-- desired sorting order.
507
--
508
-- FIXME: COPIED from Types.hs; we need to eliminate this duplication later
509
$(declareSADT "AllocPolicy"
510
  [ ("AllocPreferred",   'C.allocPolicyPreferred)
511
  , ("AllocLastResort",  'C.allocPolicyLastResort)
512
  , ("AllocUnallocable", 'C.allocPolicyUnallocable)
513
  ])
514
$(makeJSONInstance ''AllocPolicy)
515

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

    
519
$(buildObject "NodeGroup" "group" $
520
  [ simpleField "name"         [t| String |]
521
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
522
  , simpleField "ndparams"     [t| PartialNDParams |]
523
  , simpleField "alloc_policy" [t| AllocPolicy     |]
524
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
525
  , simpleField "diskparams"   [t| DiskParams      |]
526
  ]
527
  ++ timeStampFields
528
  ++ uuidFields
529
  ++ serialFields
530
  ++ tagsFields)
531

    
532
instance TimeStampObject NodeGroup where
533
  cTimeOf = groupCtime
534
  mTimeOf = groupMtime
535

    
536
instance UuidObject NodeGroup where
537
  uuidOf = groupUuid
538

    
539
instance SerialNoObject NodeGroup where
540
  serialOf = groupSerial
541

    
542
instance TagsObject NodeGroup where
543
  tagsOf = groupTags
544

    
545
-- | IP family type
546
$(declareIADT "IpFamily"
547
  [ ("IpFamilyV4", 'C.ip4Family)
548
  , ("IpFamilyV6", 'C.ip6Family)
549
  ])
550
$(makeJSONInstance ''IpFamily)
551

    
552
-- | Conversion from IP family to IP version. This is needed because
553
-- Python uses both, depending on context.
554
ipFamilyToVersion :: IpFamily -> Int
555
ipFamilyToVersion IpFamilyV4 = C.ip4Version
556
ipFamilyToVersion IpFamilyV6 = C.ip6Version
557

    
558
-- | Cluster HvParams (hvtype to hvparams mapping).
559
type ClusterHvParams = Container HvParams
560

    
561
-- | Cluster Os-HvParams (os to hvparams mapping).
562
type OsHvParams = Container ClusterHvParams
563

    
564
-- | Cluser BeParams.
565
type ClusterBeParams = Container FilledBeParams
566

    
567
-- | Cluster OsParams.
568
type ClusterOsParams = Container OsParams
569

    
570
-- | Cluster NicParams.
571
type ClusterNicParams = Container FilledNicParams
572

    
573
-- | Cluster UID Pool, list (low, high) UID ranges.
574
type UidPool = [(Int, Int)]
575

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

    
619
instance TimeStampObject Cluster where
620
  cTimeOf = clusterCtime
621
  mTimeOf = clusterMtime
622

    
623
instance UuidObject Cluster where
624
  uuidOf = clusterUuid
625

    
626
instance SerialNoObject Cluster where
627
  serialOf = clusterSerial
628

    
629
instance TagsObject Cluster where
630
  tagsOf = clusterTags
631

    
632
-- * ConfigData definitions
633

    
634
$(buildObject "ConfigData" "config" $
635
--  timeStampFields ++
636
  [ simpleField "version"    [t| Int                 |]
637
  , simpleField "cluster"    [t| Cluster             |]
638
  , simpleField "nodes"      [t| Container Node      |]
639
  , simpleField "nodegroups" [t| Container NodeGroup |]
640
  , simpleField "instances"  [t| Container Instance  |]
641
  ]
642
  ++ serialFields)
643

    
644
instance SerialNoObject ConfigData where
645
  serialOf = configSerial