Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 37904802

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
  , TagSet -- re-exported from THH
92
  ) where
93

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

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

    
104
import Ganeti.THH
105

    
106
-- * Generic definitions
107

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

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

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

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

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

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

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

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

    
151
-- * Node role object
152

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

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

    
170
-- * NIC definitions
171

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

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

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

    
189
-- * Disk definitions
190

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

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

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

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

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

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

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

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

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

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

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

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

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

    
332
-- * Hypervisor definitions
333

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

    
345
-- * Instance definitions
346

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

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

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

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

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

    
396
instance UuidObject Instance where
397
  uuidOf = instUuid
398

    
399
instance SerialNoObject Instance where
400
  serialOf = instSerial
401

    
402
instance TagsObject Instance where
403
  tagsOf = instTags
404

    
405
-- * IPolicy definitions
406

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

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

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

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

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

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

    
488
instance TimeStampObject Node where
489
  cTimeOf = nodeCtime
490
  mTimeOf = nodeMtime
491

    
492
instance UuidObject Node where
493
  uuidOf = nodeUuid
494

    
495
instance SerialNoObject Node where
496
  serialOf = nodeSerial
497

    
498
instance TagsObject Node where
499
  tagsOf = nodeTags
500

    
501
-- * NodeGroup definitions
502

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

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

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

    
534
instance TimeStampObject NodeGroup where
535
  cTimeOf = groupCtime
536
  mTimeOf = groupMtime
537

    
538
instance UuidObject NodeGroup where
539
  uuidOf = groupUuid
540

    
541
instance SerialNoObject NodeGroup where
542
  serialOf = groupSerial
543

    
544
instance TagsObject NodeGroup where
545
  tagsOf = groupTags
546

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

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

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

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

    
566
-- | Cluser BeParams.
567
type ClusterBeParams = Container FilledBeParams
568

    
569
-- | Cluster OsParams.
570
type ClusterOsParams = Container OsParams
571

    
572
-- | Cluster NicParams.
573
type ClusterNicParams = Container FilledNicParams
574

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

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

    
621
instance TimeStampObject Cluster where
622
  cTimeOf = clusterCtime
623
  mTimeOf = clusterMtime
624

    
625
instance UuidObject Cluster where
626
  uuidOf = clusterUuid
627

    
628
instance SerialNoObject Cluster where
629
  serialOf = clusterSerial
630

    
631
instance TagsObject Cluster where
632
  tagsOf = clusterTags
633

    
634
-- * ConfigData definitions
635

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

    
646
instance SerialNoObject ConfigData where
647
  serialOf = configSerial