Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 0ea11dcb

History | View | Annotate | Download (20.5 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
-- * NIC definitions
170

    
171
$(buildParam "Nic" "nicp"
172
  [ simpleField "mode" [t| NICMode |]
173
  , simpleField "link" [t| String  |]
174
  ])
175

    
176
$(buildObject "PartialNic" "nic"
177
  [ simpleField "mac" [t| String |]
178
  , optionalField $ simpleField "ip" [t| String |]
179
  , simpleField "nicparams" [t| PartialNicParams |]
180
  ])
181

    
182
-- * Disk definitions
183

    
184
$(declareSADT "DiskMode"
185
  [ ("DiskRdOnly", 'C.diskRdonly)
186
  , ("DiskRdWr",   'C.diskRdwr)
187
  ])
188
$(makeJSONInstance ''DiskMode)
189

    
190
$(declareSADT "DiskType"
191
  [ ("LD_LV",       'C.ldLv)
192
  , ("LD_DRBD8",    'C.ldDrbd8)
193
  , ("LD_FILE",     'C.ldFile)
194
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
195
  , ("LD_RADOS",    'C.ldRbd)
196
  ])
197
$(makeJSONInstance ''DiskType)
198

    
199
-- | The persistent block driver type. Currently only one type is allowed.
200
$(declareSADT "BlockDriver"
201
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
202
  ])
203
$(makeJSONInstance ''BlockDriver)
204

    
205
-- | Constant for the dev_type key entry in the disk config.
206
devType :: String
207
devType = "dev_type"
208

    
209
-- | The disk configuration type. This includes the disk type itself,
210
-- for a more complete consistency. Note that since in the Python
211
-- code-base there's no authoritative place where we document the
212
-- logical id, this is probably a good reference point.
213
data DiskLogicalId
214
  = LIDPlain String String  -- ^ Volume group, logical volume
215
  | LIDDrbd8 String String Int Int Int String
216
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
217
  | LIDFile FileDriver String -- ^ Driver, path
218
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
219
  | LIDRados String String -- ^ Unused, path
220
    deriving (Show, Eq)
221

    
222
-- | Mapping from a logical id to a disk type.
223
lidDiskType :: DiskLogicalId -> DiskType
224
lidDiskType (LIDPlain {}) = LD_LV
225
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
226
lidDiskType (LIDFile  {}) = LD_FILE
227
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
228
lidDiskType (LIDRados {}) = LD_RADOS
229

    
230
-- | Builds the extra disk_type field for a given logical id.
231
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
232
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
233

    
234
-- | Custom encoder for DiskLogicalId (logical id only).
235
encodeDLId :: DiskLogicalId -> JSValue
236
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
237
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
238
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
239
          , showJSON minorA, showJSON minorB, showJSON key ]
240
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
241
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
242
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
243

    
244
-- | Custom encoder for DiskLogicalId, composing both the logical id
245
-- and the extra disk_type field.
246
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
247
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
248

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

    
295
-- | Disk data structure.
296
--
297
-- This is declared manually as it's a recursive structure, and our TH
298
-- code currently can't build it.
299
data Disk = Disk
300
  { diskLogicalId  :: DiskLogicalId
301
--  , diskPhysicalId :: String
302
  , diskChildren   :: [Disk]
303
  , diskIvName     :: String
304
  , diskSize       :: Int
305
  , diskMode       :: DiskMode
306
  } deriving (Show, Eq)
307

    
308
$(buildObjectSerialisation "Disk"
309
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
310
      simpleField "logical_id"    [t| DiskLogicalId   |]
311
--  , simpleField "physical_id" [t| String   |]
312
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
313
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
314
  , simpleField "size" [t| Int |]
315
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
316
  ])
317

    
318
-- * Instance definitions
319

    
320
$(declareSADT "AdminState"
321
  [ ("AdminOffline", 'C.adminstOffline)
322
  , ("AdminDown",    'C.adminstDown)
323
  , ("AdminUp",      'C.adminstUp)
324
  ])
325
$(makeJSONInstance ''AdminState)
326

    
327
$(buildParam "Be" "bep"
328
  [ simpleField "minmem"       [t| Int  |]
329
  , simpleField "maxmem"       [t| Int  |]
330
  , simpleField "vcpus"        [t| Int  |]
331
  , simpleField "auto_balance" [t| Bool |]
332
  ])
333

    
334
$(buildObject "Instance" "inst" $
335
  [ simpleField "name"           [t| String             |]
336
  , simpleField "primary_node"   [t| String             |]
337
  , simpleField "os"             [t| String             |]
338
  , simpleField "hypervisor"     [t| Hypervisor         |]
339
  , simpleField "hvparams"       [t| HvParams           |]
340
  , simpleField "beparams"       [t| PartialBeParams    |]
341
  , simpleField "osparams"       [t| OsParams           |]
342
  , simpleField "admin_state"    [t| AdminState         |]
343
  , simpleField "nics"           [t| [PartialNic]       |]
344
  , simpleField "disks"          [t| [Disk]             |]
345
  , simpleField "disk_template"  [t| DiskTemplate       |]
346
  , optionalField $ simpleField "network_port" [t| Int  |]
347
  ]
348
  ++ timeStampFields
349
  ++ uuidFields
350
  ++ serialFields
351
  ++ tagsFields)
352

    
353
instance TimeStampObject Instance where
354
  cTimeOf = instCtime
355
  mTimeOf = instMtime
356

    
357
instance UuidObject Instance where
358
  uuidOf = instUuid
359

    
360
instance SerialNoObject Instance where
361
  serialOf = instSerial
362

    
363
instance TagsObject Instance where
364
  tagsOf = instTags
365

    
366
-- * IPolicy definitions
367

    
368
$(buildParam "ISpec" "ispec"
369
  [ simpleField C.ispecMemSize     [t| Int |]
370
  , simpleField C.ispecDiskSize    [t| Int |]
371
  , simpleField C.ispecDiskCount   [t| Int |]
372
  , simpleField C.ispecCpuCount    [t| Int |]
373
  , simpleField C.ispecNicCount    [t| Int |]
374
  , simpleField C.ispecSpindleUse  [t| Int |]
375
  ])
376

    
377
-- | Custom partial ipolicy. This is not built via buildParam since it
378
-- has a special 2-level inheritance mode.
379
$(buildObject "PartialIPolicy" "ipolicy"
380
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
381
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
382
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
383
  , optionalField . renameField "SpindleRatioP"
384
                    $ simpleField "spindle-ratio"  [t| Double |]
385
  , optionalField . renameField "VcpuRatioP"
386
                    $ simpleField "vcpu-ratio"     [t| Double |]
387
  , optionalField . renameField "DiskTemplatesP"
388
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
389
  ])
390

    
391
-- | Custom filled ipolicy. This is not built via buildParam since it
392
-- has a special 2-level inheritance mode.
393
$(buildObject "FilledIPolicy" "ipolicy"
394
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
395
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
396
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
397
  , simpleField "spindle-ratio"  [t| Double |]
398
  , simpleField "vcpu-ratio"     [t| Double |]
399
  , simpleField "disk-templates" [t| [DiskTemplate] |]
400
  ])
401

    
402
-- | Custom filler for the ipolicy types.
403
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
404
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
405
                           , ipolicyMaxSpec       = fmax
406
                           , ipolicyStdSpec       = fstd
407
                           , ipolicySpindleRatio  = fspindleRatio
408
                           , ipolicyVcpuRatio     = fvcpuRatio
409
                           , ipolicyDiskTemplates = fdiskTemplates})
410
            (PartialIPolicy { ipolicyMinSpecP       = pmin
411
                            , ipolicyMaxSpecP       = pmax
412
                            , ipolicyStdSpecP       = pstd
413
                            , ipolicySpindleRatioP  = pspindleRatio
414
                            , ipolicyVcpuRatioP     = pvcpuRatio
415
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
416
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
417
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
418
                , ipolicyStdSpec       = fillISpecParams fstd pstd
419
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
420
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
421
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
422
                                         pdiskTemplates
423
                }
424
-- * Node definitions
425

    
426
$(buildParam "ND" "ndp"
427
  [ simpleField "oob_program"   [t| String |]
428
  , simpleField "spindle_count" [t| Int    |]
429
  , simpleField "exclusive_storage" [t| Bool |]
430
  ])
431

    
432
$(buildObject "Node" "node" $
433
  [ simpleField "name"             [t| String |]
434
  , simpleField "primary_ip"       [t| String |]
435
  , simpleField "secondary_ip"     [t| String |]
436
  , simpleField "master_candidate" [t| Bool   |]
437
  , simpleField "offline"          [t| Bool   |]
438
  , simpleField "drained"          [t| Bool   |]
439
  , simpleField "group"            [t| String |]
440
  , simpleField "master_capable"   [t| Bool   |]
441
  , simpleField "vm_capable"       [t| Bool   |]
442
  , simpleField "ndparams"         [t| PartialNDParams |]
443
  , simpleField "powered"          [t| Bool   |]
444
  ]
445
  ++ timeStampFields
446
  ++ uuidFields
447
  ++ serialFields
448
  ++ tagsFields)
449

    
450
instance TimeStampObject Node where
451
  cTimeOf = nodeCtime
452
  mTimeOf = nodeMtime
453

    
454
instance UuidObject Node where
455
  uuidOf = nodeUuid
456

    
457
instance SerialNoObject Node where
458
  serialOf = nodeSerial
459

    
460
instance TagsObject Node where
461
  tagsOf = nodeTags
462

    
463
-- * NodeGroup definitions
464

    
465
-- | The disk parameters type.
466
type DiskParams = Container (Container JSValue)
467

    
468
$(buildObject "NodeGroup" "group" $
469
  [ simpleField "name"         [t| String |]
470
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
471
  , simpleField "ndparams"     [t| PartialNDParams |]
472
  , simpleField "alloc_policy" [t| AllocPolicy     |]
473
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
474
  , simpleField "diskparams"   [t| DiskParams      |]
475
  ]
476
  ++ timeStampFields
477
  ++ uuidFields
478
  ++ serialFields
479
  ++ tagsFields)
480

    
481
instance TimeStampObject NodeGroup where
482
  cTimeOf = groupCtime
483
  mTimeOf = groupMtime
484

    
485
instance UuidObject NodeGroup where
486
  uuidOf = groupUuid
487

    
488
instance SerialNoObject NodeGroup where
489
  serialOf = groupSerial
490

    
491
instance TagsObject NodeGroup where
492
  tagsOf = groupTags
493

    
494
-- | IP family type
495
$(declareIADT "IpFamily"
496
  [ ("IpFamilyV4", 'C.ip4Family)
497
  , ("IpFamilyV6", 'C.ip6Family)
498
  ])
499
$(makeJSONInstance ''IpFamily)
500

    
501
-- | Conversion from IP family to IP version. This is needed because
502
-- Python uses both, depending on context.
503
ipFamilyToVersion :: IpFamily -> Int
504
ipFamilyToVersion IpFamilyV4 = C.ip4Version
505
ipFamilyToVersion IpFamilyV6 = C.ip6Version
506

    
507
-- | Cluster HvParams (hvtype to hvparams mapping).
508
type ClusterHvParams = Container HvParams
509

    
510
-- | Cluster Os-HvParams (os to hvparams mapping).
511
type OsHvParams = Container ClusterHvParams
512

    
513
-- | Cluser BeParams.
514
type ClusterBeParams = Container FilledBeParams
515

    
516
-- | Cluster OsParams.
517
type ClusterOsParams = Container OsParams
518

    
519
-- | Cluster NicParams.
520
type ClusterNicParams = Container FilledNicParams
521

    
522
-- | Cluster UID Pool, list (low, high) UID ranges.
523
type UidPool = [(Int, Int)]
524

    
525
-- * Cluster definitions
526
$(buildObject "Cluster" "cluster" $
527
  [ simpleField "rsahostkeypub"           [t| String           |]
528
  , simpleField "highest_used_port"       [t| Int              |]
529
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
530
  , simpleField "mac_prefix"              [t| String           |]
531
  , simpleField "volume_group_name"       [t| String           |]
532
  , simpleField "reserved_lvs"            [t| [String]         |]
533
  , optionalField $
534
    simpleField "drbd_usermode_helper"    [t| String           |]
535
  , simpleField "master_node"             [t| String           |]
536
  , simpleField "master_ip"               [t| String           |]
537
  , simpleField "master_netdev"           [t| String           |]
538
  , simpleField "master_netmask"          [t| Int              |]
539
  , simpleField "use_external_mip_script" [t| Bool             |]
540
  , simpleField "cluster_name"            [t| String           |]
541
  , simpleField "file_storage_dir"        [t| String           |]
542
  , simpleField "shared_file_storage_dir" [t| String           |]
543
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
544
  , simpleField "hvparams"                [t| ClusterHvParams  |]
545
  , simpleField "os_hvp"                  [t| OsHvParams       |]
546
  , simpleField "beparams"                [t| ClusterBeParams  |]
547
  , simpleField "osparams"                [t| ClusterOsParams  |]
548
  , simpleField "nicparams"               [t| ClusterNicParams |]
549
  , simpleField "ndparams"                [t| FilledNDParams   |]
550
  , simpleField "diskparams"              [t| DiskParams       |]
551
  , simpleField "candidate_pool_size"     [t| Int              |]
552
  , simpleField "modify_etc_hosts"        [t| Bool             |]
553
  , simpleField "modify_ssh_setup"        [t| Bool             |]
554
  , simpleField "maintain_node_health"    [t| Bool             |]
555
  , simpleField "uid_pool"                [t| UidPool          |]
556
  , simpleField "default_iallocator"      [t| String           |]
557
  , simpleField "hidden_os"               [t| [String]         |]
558
  , simpleField "blacklisted_os"          [t| [String]         |]
559
  , simpleField "primary_ip_family"       [t| IpFamily         |]
560
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
561
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
562
 ]
563
 ++ timeStampFields
564
 ++ uuidFields
565
 ++ serialFields
566
 ++ tagsFields)
567

    
568
instance TimeStampObject Cluster where
569
  cTimeOf = clusterCtime
570
  mTimeOf = clusterMtime
571

    
572
instance UuidObject Cluster where
573
  uuidOf = clusterUuid
574

    
575
instance SerialNoObject Cluster where
576
  serialOf = clusterSerial
577

    
578
instance TagsObject Cluster where
579
  tagsOf = clusterTags
580

    
581
-- * ConfigData definitions
582

    
583
$(buildObject "ConfigData" "config" $
584
--  timeStampFields ++
585
  [ simpleField "version"    [t| Int                 |]
586
  , simpleField "cluster"    [t| Cluster             |]
587
  , simpleField "nodes"      [t| Container Node      |]
588
  , simpleField "nodegroups" [t| Container NodeGroup |]
589
  , simpleField "instances"  [t| Container Instance  |]
590
  ]
591
  ++ serialFields)
592

    
593
instance SerialNoObject ConfigData where
594
  serialOf = configSerial
595

    
596
-- * Network definitions
597

    
598
-- FIXME: Not all types might be correct here, since they
599
-- haven't been exhaustively deduced from the python code yet.
600
$(buildObject "Network" "network" $
601
  [ simpleField "name"             [t| NonEmptyString |]
602
  , optionalField $
603
    simpleField "network_type"     [t| NetworkType |]
604
  , optionalField $
605
    simpleField "mac_prefix"       [t| String |]
606
  , optionalField $
607
    simpleField "family"           [t| Int |]
608
  , simpleField "network"          [t| NonEmptyString |]
609
  , optionalField $
610
    simpleField "network6"         [t| String |]
611
  , optionalField $
612
    simpleField "gateway"          [t| String |]
613
  , optionalField $
614
    simpleField "gateway6"         [t| String |]
615
  , optionalField $
616
    simpleField "size"             [t| J.JSValue |]
617
  , optionalField $
618
    simpleField "reservations"     [t| String |]
619
  , optionalField $
620
    simpleField "ext_reservations" [t| String |]
621
  ]
622
  ++ serialFields
623
  ++ tagsFields)
624

    
625
instance SerialNoObject Network where
626
  serialOf = networkSerial
627

    
628
instance TagsObject Network where
629
  tagsOf = networkTags
630