Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 3add7574

History | View | Annotate | Download (21.2 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

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

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

    
8
-}
9

    
10
{-
11

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

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

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

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

    
29
-}
30

    
31
module Ganeti.Objects
32
  ( VType(..)
33
  , vTypeFromRaw
34
  , HvParams
35
  , OsParams
36
  , PartialNicParams(..)
37
  , FilledNicParams(..)
38
  , fillNicParams
39
  , allNicParamFields
40
  , PartialNic(..)
41
  , FileDriver(..)
42
  , BlockDriver(..)
43
  , DiskMode(..)
44
  , DiskType(..)
45
  , DiskLogicalId(..)
46
  , Disk(..)
47
  , DiskTemplate(..)
48
  , PartialBeParams(..)
49
  , FilledBeParams(..)
50
  , fillBeParams
51
  , allBeParamFields
52
  , AdminState(..)
53
  , adminStateFromRaw
54
  , Instance(..)
55
  , toDictInstance
56
  , PartialNDParams(..)
57
  , FilledNDParams(..)
58
  , fillNDParams
59
  , allNDParamFields
60
  , Node(..)
61
  , NodeRole(..)
62
  , nodeRoleToRaw
63
  , roleDescription
64
  , AllocPolicy(..)
65
  , FilledISpecParams(..)
66
  , PartialISpecParams(..)
67
  , fillISpecParams
68
  , allISpecParamFields
69
  , FilledIPolicy(..)
70
  , PartialIPolicy(..)
71
  , fillIPolicy
72
  , DiskParams
73
  , NodeGroup(..)
74
  , IpFamily(..)
75
  , ipFamilyToVersion
76
  , fillDict
77
  , ClusterHvParams
78
  , OsHvParams
79
  , ClusterBeParams
80
  , ClusterOsParams
81
  , ClusterNicParams
82
  , Cluster(..)
83
  , ConfigData(..)
84
  , TimeStampObject(..)
85
  , UuidObject(..)
86
  , SerialNoObject(..)
87
  , TagsObject(..)
88
  , DictObject(..) -- re-exported from THH
89
  , TagSet -- re-exported from THH
90
  , Network(..)
91
  ) where
92

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

    
100
import qualified Ganeti.Constants as C
101
import Ganeti.JSON
102
import Ganeti.Types
103
import Ganeti.THH
104

    
105
-- * Generic definitions
106

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

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

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

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

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

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

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

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

    
150
-- * Node role object
151

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

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

    
169
-- * Network definitions
170

    
171
-- FIXME: Not all types might be correct here, since they
172
-- haven't been exhaustively deduced from the python code yet.
173
$(buildObject "Network" "network" $
174
  [ simpleField "name"             [t| NonEmptyString |]
175
  , optionalField $
176
    simpleField "network_type"     [t| NetworkType |]
177
  , optionalField $
178
    simpleField "mac_prefix"       [t| String |]
179
  , optionalField $
180
    simpleField "family"           [t| Int |]
181
  , simpleField "network"          [t| NonEmptyString |]
182
  , optionalField $
183
    simpleField "network6"         [t| String |]
184
  , optionalField $
185
    simpleField "gateway"          [t| String |]
186
  , optionalField $
187
    simpleField "gateway6"         [t| String |]
188
  , optionalField $
189
    simpleField "size"             [t| J.JSValue |]
190
  , optionalField $
191
    simpleField "reservations"     [t| String |]
192
  , optionalField $
193
    simpleField "ext_reservations" [t| String |]
194
  ]
195
  ++ serialFields
196
  ++ tagsFields)
197

    
198
instance SerialNoObject Network where
199
  serialOf = networkSerial
200

    
201
instance TagsObject Network where
202
  tagsOf = networkTags
203

    
204
-- * NIC definitions
205

    
206
$(buildParam "Nic" "nicp"
207
  [ simpleField "mode" [t| NICMode |]
208
  , simpleField "link" [t| String  |]
209
  ])
210

    
211
$(buildObject "PartialNic" "nic"
212
  [ simpleField "mac" [t| String |]
213
  , optionalField $ simpleField "ip" [t| String |]
214
  , simpleField "nicparams" [t| PartialNicParams |]
215
  , optionalField $ simpleField "network" [t| Network |]
216
  ])
217

    
218
-- * Disk definitions
219

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

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

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

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

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

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

    
269
-- | Builds the extra disk_type field for a given logical id.
270
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
271
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
272

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

    
285
-- | Custom encoder for DiskLogicalId, composing both the logical id
286
-- and the extra disk_type field.
287
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
288
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
289

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

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

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

    
366
-- * Instance definitions
367

    
368
$(declareSADT "AdminState"
369
  [ ("AdminOffline", 'C.adminstOffline)
370
  , ("AdminDown",    'C.adminstDown)
371
  , ("AdminUp",      'C.adminstUp)
372
  ])
373
$(makeJSONInstance ''AdminState)
374

    
375
$(buildParam "Be" "bep"
376
  [ simpleField "minmem"       [t| Int  |]
377
  , simpleField "maxmem"       [t| Int  |]
378
  , simpleField "vcpus"        [t| Int  |]
379
  , simpleField "auto_balance" [t| Bool |]
380
  ])
381

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

    
401
instance TimeStampObject Instance where
402
  cTimeOf = instCtime
403
  mTimeOf = instMtime
404

    
405
instance UuidObject Instance where
406
  uuidOf = instUuid
407

    
408
instance SerialNoObject Instance where
409
  serialOf = instSerial
410

    
411
instance TagsObject Instance where
412
  tagsOf = instTags
413

    
414
-- * IPolicy definitions
415

    
416
$(buildParam "ISpec" "ispec"
417
  [ simpleField C.ispecMemSize     [t| Int |]
418
  , simpleField C.ispecDiskSize    [t| Int |]
419
  , simpleField C.ispecDiskCount   [t| Int |]
420
  , simpleField C.ispecCpuCount    [t| Int |]
421
  , simpleField C.ispecNicCount    [t| Int |]
422
  , simpleField C.ispecSpindleUse  [t| Int |]
423
  ])
424

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

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

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

    
474
$(buildParam "ND" "ndp"
475
  [ simpleField "oob_program"   [t| String |]
476
  , simpleField "spindle_count" [t| Int    |]
477
  , simpleField "exclusive_storage" [t| Bool |]
478
  ])
479

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

    
498
instance TimeStampObject Node where
499
  cTimeOf = nodeCtime
500
  mTimeOf = nodeMtime
501

    
502
instance UuidObject Node where
503
  uuidOf = nodeUuid
504

    
505
instance SerialNoObject Node where
506
  serialOf = nodeSerial
507

    
508
instance TagsObject Node where
509
  tagsOf = nodeTags
510

    
511
-- * NodeGroup definitions
512

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

    
516
-- | A mapping from network UUIDs to nic params of the networks.
517
type Networks = Container PartialNic
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
  , simpleField "networks"     [t| Networks        |]
527
  ]
528
  ++ timeStampFields
529
  ++ uuidFields
530
  ++ serialFields
531
  ++ tagsFields)
532

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

    
537
instance UuidObject NodeGroup where
538
  uuidOf = groupUuid
539

    
540
instance SerialNoObject NodeGroup where
541
  serialOf = groupSerial
542

    
543
instance TagsObject NodeGroup where
544
  tagsOf = groupTags
545

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

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

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

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

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

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

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

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

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

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

    
624
instance UuidObject Cluster where
625
  uuidOf = clusterUuid
626

    
627
instance SerialNoObject Cluster where
628
  serialOf = clusterSerial
629

    
630
instance TagsObject Cluster where
631
  tagsOf = clusterTags
632

    
633
-- * ConfigData definitions
634

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

    
645
instance SerialNoObject ConfigData where
646
  serialOf = configSerial