Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 64b0309a

History | View | Annotate | Download (21 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 "mac_prefix"       [t| String |]
177
  , simpleField "network"          [t| NonEmptyString |]
178
  , optionalField $
179
    simpleField "network6"         [t| String |]
180
  , optionalField $
181
    simpleField "gateway"          [t| String |]
182
  , optionalField $
183
    simpleField "gateway6"         [t| String |]
184
  , optionalField $
185
    simpleField "reservations"     [t| String |]
186
  , optionalField $
187
    simpleField "ext_reservations" [t| String |]
188
  ]
189
  ++ serialFields
190
  ++ tagsFields)
191

    
192
instance SerialNoObject Network where
193
  serialOf = networkSerial
194

    
195
instance TagsObject Network where
196
  tagsOf = networkTags
197

    
198
-- * NIC definitions
199

    
200
$(buildParam "Nic" "nicp"
201
  [ simpleField "mode" [t| NICMode |]
202
  , simpleField "link" [t| String  |]
203
  ])
204

    
205
$(buildObject "PartialNic" "nic"
206
  [ simpleField "mac" [t| String |]
207
  , optionalField $ simpleField "ip" [t| String |]
208
  , simpleField "nicparams" [t| PartialNicParams |]
209
  , optionalField $ simpleField "network" [t| String |]
210
  ])
211

    
212
-- * Disk definitions
213

    
214
$(declareSADT "DiskMode"
215
  [ ("DiskRdOnly", 'C.diskRdonly)
216
  , ("DiskRdWr",   'C.diskRdwr)
217
  ])
218
$(makeJSONInstance ''DiskMode)
219

    
220
$(declareSADT "DiskType"
221
  [ ("LD_LV",       'C.ldLv)
222
  , ("LD_DRBD8",    'C.ldDrbd8)
223
  , ("LD_FILE",     'C.ldFile)
224
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
225
  , ("LD_RADOS",    'C.ldRbd)
226
  , ("LD_EXT",      'C.ldExt)
227
  ])
228
$(makeJSONInstance ''DiskType)
229

    
230
-- | The persistent block driver type. Currently only one type is allowed.
231
$(declareSADT "BlockDriver"
232
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
233
  ])
234
$(makeJSONInstance ''BlockDriver)
235

    
236
-- | Constant for the dev_type key entry in the disk config.
237
devType :: String
238
devType = "dev_type"
239

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

    
254
-- | Mapping from a logical id to a disk type.
255
lidDiskType :: DiskLogicalId -> DiskType
256
lidDiskType (LIDPlain {}) = LD_LV
257
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
258
lidDiskType (LIDFile  {}) = LD_FILE
259
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
260
lidDiskType (LIDRados {}) = LD_RADOS
261
lidDiskType (LIDExt {}) = LD_EXT
262

    
263
-- | Builds the extra disk_type field for a given logical id.
264
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
265
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
266

    
267
-- | Custom encoder for DiskLogicalId (logical id only).
268
encodeDLId :: DiskLogicalId -> JSValue
269
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
270
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
271
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
272
          , showJSON minorA, showJSON minorB, showJSON key ]
273
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
274
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
275
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
276
encodeDLId (LIDExt extprovider name) =
277
  JSArray [showJSON extprovider, showJSON name]
278

    
279
-- | Custom encoder for DiskLogicalId, composing both the logical id
280
-- and the extra disk_type field.
281
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
282
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
283

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

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

    
350
$(buildObjectSerialisation "Disk"
351
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
352
      simpleField "logical_id"    [t| DiskLogicalId   |]
353
--  , simpleField "physical_id" [t| String   |]
354
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
355
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
356
  , simpleField "size" [t| Int |]
357
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
358
  ])
359

    
360
-- * Instance definitions
361

    
362
$(declareSADT "AdminState"
363
  [ ("AdminOffline", 'C.adminstOffline)
364
  , ("AdminDown",    'C.adminstDown)
365
  , ("AdminUp",      'C.adminstUp)
366
  ])
367
$(makeJSONInstance ''AdminState)
368

    
369
$(buildParam "Be" "bep"
370
  [ simpleField "minmem"       [t| Int  |]
371
  , simpleField "maxmem"       [t| Int  |]
372
  , simpleField "vcpus"        [t| Int  |]
373
  , simpleField "auto_balance" [t| Bool |]
374
  ])
375

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

    
395
instance TimeStampObject Instance where
396
  cTimeOf = instCtime
397
  mTimeOf = instMtime
398

    
399
instance UuidObject Instance where
400
  uuidOf = instUuid
401

    
402
instance SerialNoObject Instance where
403
  serialOf = instSerial
404

    
405
instance TagsObject Instance where
406
  tagsOf = instTags
407

    
408
-- * IPolicy definitions
409

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

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

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

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

    
468
$(buildParam "ND" "ndp"
469
  [ simpleField "oob_program"   [t| String |]
470
  , simpleField "spindle_count" [t| Int    |]
471
  , simpleField "exclusive_storage" [t| Bool |]
472
  ])
473

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

    
492
instance TimeStampObject Node where
493
  cTimeOf = nodeCtime
494
  mTimeOf = nodeMtime
495

    
496
instance UuidObject Node where
497
  uuidOf = nodeUuid
498

    
499
instance SerialNoObject Node where
500
  serialOf = nodeSerial
501

    
502
instance TagsObject Node where
503
  tagsOf = nodeTags
504

    
505
-- * NodeGroup definitions
506

    
507
-- | The disk parameters type.
508
type DiskParams = Container (Container JSValue)
509

    
510
-- | A mapping from network UUIDs to nic params of the networks.
511
type Networks = Container PartialNicParams
512

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

    
527
instance TimeStampObject NodeGroup where
528
  cTimeOf = groupCtime
529
  mTimeOf = groupMtime
530

    
531
instance UuidObject NodeGroup where
532
  uuidOf = groupUuid
533

    
534
instance SerialNoObject NodeGroup where
535
  serialOf = groupSerial
536

    
537
instance TagsObject NodeGroup where
538
  tagsOf = groupTags
539

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

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

    
553
-- | Cluster HvParams (hvtype to hvparams mapping).
554
type ClusterHvParams = Container HvParams
555

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

    
559
-- | Cluser BeParams.
560
type ClusterBeParams = Container FilledBeParams
561

    
562
-- | Cluster OsParams.
563
type ClusterOsParams = Container OsParams
564

    
565
-- | Cluster NicParams.
566
type ClusterNicParams = Container FilledNicParams
567

    
568
-- | Cluster UID Pool, list (low, high) UID ranges.
569
type UidPool = [(Int, Int)]
570

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

    
615
instance TimeStampObject Cluster where
616
  cTimeOf = clusterCtime
617
  mTimeOf = clusterMtime
618

    
619
instance UuidObject Cluster where
620
  uuidOf = clusterUuid
621

    
622
instance SerialNoObject Cluster where
623
  serialOf = clusterSerial
624

    
625
instance TagsObject Cluster where
626
  tagsOf = clusterTags
627

    
628
-- * ConfigData definitions
629

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

    
640
instance SerialNoObject ConfigData where
641
  serialOf = configSerial