Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ f3baf5ef

History | View | Annotate | Download (20.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
  ( VType(..)
33
  , vTypeFromRaw
34
  , HvParams
35
  , OsParams
36
  , NICMode(..)
37
  , PartialNicParams(..)
38
  , FilledNicParams(..)
39
  , fillNicParams
40
  , allNicParamFields
41
  , PartialNic(..)
42
  , DiskMode(..)
43
  , DiskType(..)
44
  , DiskLogicalId(..)
45
  , Disk(..)
46
  , DiskTemplate(..)
47
  , PartialBeParams(..)
48
  , FilledBeParams(..)
49
  , fillBeParams
50
  , allBeParamFields
51
  , Hypervisor(..)
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
  ) where
90

    
91
import Data.List (foldl')
92
import Data.Maybe
93
import qualified Data.Map as Map
94
import qualified Data.Set as Set
95
import Text.JSON (makeObj, showJSON, readJSON, JSON, JSValue(..))
96
import qualified Text.JSON as J
97

    
98
import qualified Ganeti.Constants as C
99
import Ganeti.JSON
100

    
101
import Ganeti.THH
102

    
103
-- * Generic definitions
104

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

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

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

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

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

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

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

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

    
148
-- * Node role object
149

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

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

    
167
-- * NIC definitions
168

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

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

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

    
186
-- * Disk definitions
187

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

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

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

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

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

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

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

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

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

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

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

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

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

    
329
-- * Hypervisor definitions
330

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

    
342
-- * Instance definitions
343

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

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

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

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

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

    
393
instance UuidObject Instance where
394
  uuidOf = instUuid
395

    
396
instance SerialNoObject Instance where
397
  serialOf = instSerial
398

    
399
instance TagsObject Instance where
400
  tagsOf = instTags
401

    
402
-- * IPolicy definitions
403

    
404
$(buildParam "ISpec" "ispec" $
405
  [ simpleField C.ispecMemSize     [t| Int |]
406
  , simpleField C.ispecDiskSize    [t| Int |]
407
  , simpleField C.ispecDiskCount   [t| Int |]
408
  , simpleField C.ispecCpuCount    [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
  ])
465

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

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

    
488
instance UuidObject Node where
489
  uuidOf = nodeUuid
490

    
491
instance SerialNoObject Node where
492
  serialOf = nodeSerial
493

    
494
instance TagsObject Node where
495
  tagsOf = nodeTags
496

    
497
-- * NodeGroup definitions
498

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

    
514
-- | The disk parameters type.
515
type DiskParams = Container (Container JSValue)
516

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

    
530
instance TimeStampObject NodeGroup where
531
  cTimeOf = groupCtime
532
  mTimeOf = groupMtime
533

    
534
instance UuidObject NodeGroup where
535
  uuidOf = groupUuid
536

    
537
instance SerialNoObject NodeGroup where
538
  serialOf = groupSerial
539

    
540
instance TagsObject NodeGroup where
541
  tagsOf = groupTags
542

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

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

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

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

    
562
-- | Cluser BeParams.
563
type ClusterBeParams = Container FilledBeParams
564

    
565
-- | Cluster OsParams.
566
type ClusterOsParams = Container OsParams
567

    
568
-- | Cluster NicParams.
569
type ClusterNicParams = Container FilledNicParams
570

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

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

    
617
instance TimeStampObject Cluster where
618
  cTimeOf = clusterCtime
619
  mTimeOf = clusterMtime
620

    
621
instance UuidObject Cluster where
622
  uuidOf = clusterUuid
623

    
624
instance SerialNoObject Cluster where
625
  serialOf = clusterSerial
626

    
627
instance TagsObject Cluster where
628
  tagsOf = clusterTags
629

    
630
-- * ConfigData definitions
631

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

    
642
instance SerialNoObject ConfigData where
643
  serialOf = configSerial