Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ ae8e7986

History | View | Annotate | Download (23.7 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, 2013 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
  ( HvParams
33
  , OsParams
34
  , PartialNicParams(..)
35
  , FilledNicParams(..)
36
  , fillNicParams
37
  , allNicParamFields
38
  , PartialNic(..)
39
  , FileDriver(..)
40
  , DiskLogicalId(..)
41
  , Disk(..)
42
  , includesLogicalId
43
  , DiskTemplate(..)
44
  , PartialBeParams(..)
45
  , FilledBeParams(..)
46
  , fillBeParams
47
  , allBeParamFields
48
  , Instance(..)
49
  , toDictInstance
50
  , PartialNDParams(..)
51
  , FilledNDParams(..)
52
  , fillNDParams
53
  , allNDParamFields
54
  , Node(..)
55
  , AllocPolicy(..)
56
  , FilledISpecParams(..)
57
  , PartialISpecParams(..)
58
  , fillISpecParams
59
  , allISpecParamFields
60
  , MinMaxISpecs(..)
61
  , FilledIPolicy(..)
62
  , PartialIPolicy(..)
63
  , fillIPolicy
64
  , DiskParams
65
  , NodeGroup(..)
66
  , IpFamily(..)
67
  , ipFamilyToVersion
68
  , fillDict
69
  , ClusterHvParams
70
  , OsHvParams
71
  , ClusterBeParams
72
  , ClusterOsParams
73
  , ClusterNicParams
74
  , Cluster(..)
75
  , ConfigData(..)
76
  , TimeStampObject(..)
77
  , UuidObject(..)
78
  , SerialNoObject(..)
79
  , TagsObject(..)
80
  , DictObject(..) -- re-exported from THH
81
  , TagSet -- re-exported from THH
82
  , Network(..)
83
  , Ip4Address(..)
84
  , Ip4Network(..)
85
  , readIp4Address
86
  , nextIp4Address
87
  ) where
88

    
89
import Control.Applicative
90
import Data.List (foldl')
91
import Data.Maybe
92
import qualified Data.Map as Map
93
import qualified Data.Set as Set
94
import Data.Word
95
import Text.JSON (showJSON, readJSON, JSON, JSValue(..), fromJSString)
96
import qualified Text.JSON as J
97

    
98
import qualified Ganeti.Constants as C
99
import qualified Ganeti.ConstantUtils as ConstantUtils
100
import Ganeti.JSON
101
import Ganeti.Types
102
import Ganeti.THH
103
import Ganeti.Utils (sepSplit, tryRead)
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 hypervisor parameter type. This is currently a simple map,
115
-- without type checking on key/value pairs.
116
type HvParams = Container JSValue
117

    
118
-- | The OS parameters type. This is, and will remain, a string
119
-- container, since the keys are dynamically declared by the OSes, and
120
-- the values are always strings.
121
type OsParams = Container String
122

    
123
-- | Class of objects that have timestamps.
124
class TimeStampObject a where
125
  cTimeOf :: a -> Double
126
  mTimeOf :: a -> Double
127

    
128
-- | Class of objects that have an UUID.
129
class UuidObject a where
130
  uuidOf :: a -> String
131

    
132
-- | Class of object that have a serial number.
133
class SerialNoObject a where
134
  serialOf :: a -> Int
135

    
136
-- | Class of objects that have tags.
137
class TagsObject a where
138
  tagsOf :: a -> Set.Set String
139

    
140
-- * Network definitions
141

    
142
-- ** Ipv4 types
143

    
144
-- | Custom type for a simple IPv4 address.
145
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
146
                  deriving Eq
147

    
148
instance Show Ip4Address where
149
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
150
                              show c ++ "." ++ show d
151

    
152
-- | Parses an IPv4 address from a string.
153
readIp4Address :: (Applicative m, Monad m) => String -> m Ip4Address
154
readIp4Address s =
155
  case sepSplit '.' s of
156
    [a, b, c, d] -> Ip4Address <$>
157
                      tryRead "first octect" a <*>
158
                      tryRead "second octet" b <*>
159
                      tryRead "third octet"  c <*>
160
                      tryRead "fourth octet" d
161
    _ -> fail $ "Can't parse IPv4 address from string " ++ s
162

    
163
-- | JSON instance for 'Ip4Address'.
164
instance JSON Ip4Address where
165
  showJSON = showJSON . show
166
  readJSON (JSString s) = readIp4Address (fromJSString s)
167
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 address"
168

    
169
-- | \"Next\" address implementation for IPv4 addresses.
170
--
171
-- Note that this loops! Note also that this is a very dumb
172
-- implementation.
173
nextIp4Address :: Ip4Address -> Ip4Address
174
nextIp4Address (Ip4Address a b c d) =
175
  let inc xs y = if all (==0) xs then y + 1 else y
176
      d' = d + 1
177
      c' = inc [d'] c
178
      b' = inc [c', d'] b
179
      a' = inc [b', c', d'] a
180
  in Ip4Address a' b' c' d'
181

    
182
-- | Custom type for an IPv4 network.
183
data Ip4Network = Ip4Network Ip4Address Word8
184
                  deriving Eq
185

    
186
instance Show Ip4Network where
187
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
188

    
189
-- | JSON instance for 'Ip4Network'.
190
instance JSON Ip4Network where
191
  showJSON = showJSON . show
192
  readJSON (JSString s) =
193
    case sepSplit '/' (fromJSString s) of
194
      [ip, nm] -> do
195
        ip' <- readIp4Address ip
196
        nm' <- tryRead "parsing netmask" nm
197
        if nm' >= 0 && nm' <= 32
198
          then return $ Ip4Network ip' nm'
199
          else fail $ "Invalid netmask " ++ show nm' ++ " from string " ++
200
                      fromJSString s
201
      _ -> fail $ "Can't parse IPv4 network from string " ++ fromJSString s
202
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 network"
203

    
204
-- ** Ganeti \"network\" config object.
205

    
206
-- FIXME: Not all types might be correct here, since they
207
-- haven't been exhaustively deduced from the python code yet.
208
$(buildObject "Network" "network" $
209
  [ simpleField "name"             [t| NonEmptyString |]
210
  , optionalField $
211
    simpleField "mac_prefix"       [t| String |]
212
  , simpleField "network"          [t| Ip4Network |]
213
  , optionalField $
214
    simpleField "network6"         [t| String |]
215
  , optionalField $
216
    simpleField "gateway"          [t| Ip4Address |]
217
  , optionalField $
218
    simpleField "gateway6"         [t| String |]
219
  , optionalField $
220
    simpleField "reservations"     [t| String |]
221
  , optionalField $
222
    simpleField "ext_reservations" [t| String |]
223
  ]
224
  ++ uuidFields
225
  ++ timeStampFields
226
  ++ serialFields
227
  ++ tagsFields)
228

    
229
instance SerialNoObject Network where
230
  serialOf = networkSerial
231

    
232
instance TagsObject Network where
233
  tagsOf = networkTags
234

    
235
instance UuidObject Network where
236
  uuidOf = networkUuid
237

    
238
instance TimeStampObject Network where
239
  cTimeOf = networkCtime
240
  mTimeOf = networkMtime
241

    
242
-- * NIC definitions
243

    
244
$(buildParam "Nic" "nicp"
245
  [ simpleField "mode" [t| NICMode |]
246
  , simpleField "link" [t| String  |]
247
  , simpleField "vlan" [t| Maybe String |]
248
  ])
249

    
250
$(buildObject "PartialNic" "nic" $
251
  [ simpleField "mac" [t| String |]
252
  , optionalField $ simpleField "ip" [t| String |]
253
  , simpleField "nicparams" [t| PartialNicParams |]
254
  , optionalField $ simpleField "network" [t| String |]
255
  , optionalField $ simpleField "name" [t| String |]
256
  ] ++ uuidFields)
257

    
258
instance UuidObject PartialNic where
259
  uuidOf = nicUuid
260

    
261
-- * Disk definitions
262

    
263
-- | Constant for the dev_type key entry in the disk config.
264
devType :: String
265
devType = "dev_type"
266

    
267
-- | The disk configuration type. This includes the disk type itself,
268
-- for a more complete consistency. Note that since in the Python
269
-- code-base there's no authoritative place where we document the
270
-- logical id, this is probably a good reference point.
271
data DiskLogicalId
272
  = LIDPlain String String  -- ^ Volume group, logical volume
273
  | LIDDrbd8 String String Int Int Int String
274
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
275
  | LIDFile FileDriver String -- ^ Driver, path
276
  | LIDSharedFile FileDriver String -- ^ Driver, path
277
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
278
  | LIDRados String String -- ^ Unused, path
279
  | LIDExt String String -- ^ ExtProvider, unique name
280
    deriving (Show, Eq)
281

    
282
-- | Mapping from a logical id to a disk type.
283
lidDiskType :: DiskLogicalId -> DiskTemplate
284
lidDiskType (LIDPlain {}) = DTPlain
285
lidDiskType (LIDDrbd8 {}) = DTDrbd8
286
lidDiskType (LIDFile  {}) = DTFile
287
lidDiskType (LIDSharedFile  {}) = DTSharedFile
288
lidDiskType (LIDBlockDev {}) = DTBlock
289
lidDiskType (LIDRados {}) = DTRbd
290
lidDiskType (LIDExt {}) = DTExt
291

    
292
-- | Builds the extra disk_type field for a given logical id.
293
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
294
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
295

    
296
-- | Custom encoder for DiskLogicalId (logical id only).
297
encodeDLId :: DiskLogicalId -> JSValue
298
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
299
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
300
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
301
          , showJSON minorA, showJSON minorB, showJSON key ]
302
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
303
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
304
encodeDLId (LIDSharedFile driver name) =
305
  JSArray [showJSON driver, showJSON name]
306
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
307
encodeDLId (LIDExt extprovider name) =
308
  JSArray [showJSON extprovider, showJSON name]
309

    
310
-- | Custom encoder for DiskLogicalId, composing both the logical id
311
-- and the extra disk_type field.
312
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
313
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
314

    
315
-- | Custom decoder for DiskLogicalId. This is manual for now, since
316
-- we don't have yet automation for separate-key style fields.
317
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
318
decodeDLId obj lid = do
319
  dtype <- fromObj obj devType
320
  case dtype of
321
    DTDrbd8 ->
322
      case lid of
323
        JSArray [nA, nB, p, mA, mB, k] -> do
324
          nA' <- readJSON nA
325
          nB' <- readJSON nB
326
          p'  <- readJSON p
327
          mA' <- readJSON mA
328
          mB' <- readJSON mB
329
          k'  <- readJSON k
330
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
331
        _ -> fail "Can't read logical_id for DRBD8 type"
332
    DTPlain ->
333
      case lid of
334
        JSArray [vg, lv] -> do
335
          vg' <- readJSON vg
336
          lv' <- readJSON lv
337
          return $ LIDPlain vg' lv'
338
        _ -> fail "Can't read logical_id for plain type"
339
    DTFile ->
340
      case lid of
341
        JSArray [driver, path] -> do
342
          driver' <- readJSON driver
343
          path'   <- readJSON path
344
          return $ LIDFile driver' path'
345
        _ -> fail "Can't read logical_id for file type"
346
    DTSharedFile ->
347
      case lid of
348
        JSArray [driver, path] -> do
349
          driver' <- readJSON driver
350
          path'   <- readJSON path
351
          return $ LIDSharedFile driver' path'
352
        _ -> fail "Can't read logical_id for shared file type"
353
    DTBlock ->
354
      case lid of
355
        JSArray [driver, path] -> do
356
          driver' <- readJSON driver
357
          path'   <- readJSON path
358
          return $ LIDBlockDev driver' path'
359
        _ -> fail "Can't read logical_id for blockdev type"
360
    DTRbd ->
361
      case lid of
362
        JSArray [driver, path] -> do
363
          driver' <- readJSON driver
364
          path'   <- readJSON path
365
          return $ LIDRados driver' path'
366
        _ -> fail "Can't read logical_id for rdb type"
367
    DTExt ->
368
      case lid of
369
        JSArray [extprovider, name] -> do
370
          extprovider' <- readJSON extprovider
371
          name'   <- readJSON name
372
          return $ LIDExt extprovider' name'
373
        _ -> fail "Can't read logical_id for extstorage type"
374
    DTDiskless ->
375
      fail "Retrieved 'diskless' disk."
376

    
377
-- | Disk data structure.
378
--
379
-- This is declared manually as it's a recursive structure, and our TH
380
-- code currently can't build it.
381
data Disk = Disk
382
  { diskLogicalId  :: DiskLogicalId
383
  , diskChildren   :: [Disk]
384
  , diskIvName     :: String
385
  , diskSize       :: Int
386
  , diskMode       :: DiskMode
387
  , diskName       :: Maybe String
388
  , diskSpindles   :: Maybe Int
389
  , diskUuid       :: String
390
  } deriving (Show, Eq)
391

    
392
$(buildObjectSerialisation "Disk" $
393
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
394
      simpleField "logical_id"    [t| DiskLogicalId   |]
395
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
396
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
397
  , simpleField "size" [t| Int |]
398
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
399
  , optionalField $ simpleField "name" [t| String |]
400
  , optionalField $ simpleField "spindles" [t| Int |]
401
  ]
402
  ++ uuidFields)
403

    
404
instance UuidObject Disk where
405
  uuidOf = diskUuid
406

    
407
-- | Determines whether a disk or one of his children has the given logical id
408
-- (determined by the volume group name and by the logical volume name).
409
-- This can be true only for DRBD or LVM disks.
410
includesLogicalId :: String -> String -> Disk -> Bool
411
includesLogicalId vg_name lv_name disk =
412
  case diskLogicalId disk of
413
    LIDPlain vg lv -> vg_name == vg && lv_name == lv
414
    LIDDrbd8 {} ->
415
      any (includesLogicalId vg_name lv_name) $ diskChildren disk
416
    _ -> False
417

    
418
-- * Instance definitions
419

    
420
$(buildParam "Be" "bep"
421
  [ simpleField "minmem"       [t| Int  |]
422
  , simpleField "maxmem"       [t| Int  |]
423
  , simpleField "vcpus"        [t| Int  |]
424
  , simpleField "auto_balance" [t| Bool |]
425
  ])
426

    
427
$(buildObject "Instance" "inst" $
428
  [ simpleField "name"           [t| String             |]
429
  , simpleField "primary_node"   [t| String             |]
430
  , simpleField "os"             [t| String             |]
431
  , simpleField "hypervisor"     [t| Hypervisor         |]
432
  , simpleField "hvparams"       [t| HvParams           |]
433
  , simpleField "beparams"       [t| PartialBeParams    |]
434
  , simpleField "osparams"       [t| OsParams           |]
435
  , simpleField "admin_state"    [t| AdminState         |]
436
  , simpleField "nics"           [t| [PartialNic]       |]
437
  , simpleField "disks"          [t| [Disk]             |]
438
  , simpleField "disk_template"  [t| DiskTemplate       |]
439
  , simpleField "disks_active"   [t| Bool               |]
440
  , optionalField $ simpleField "network_port" [t| Int  |]
441
  ]
442
  ++ timeStampFields
443
  ++ uuidFields
444
  ++ serialFields
445
  ++ tagsFields)
446

    
447
instance TimeStampObject Instance where
448
  cTimeOf = instCtime
449
  mTimeOf = instMtime
450

    
451
instance UuidObject Instance where
452
  uuidOf = instUuid
453

    
454
instance SerialNoObject Instance where
455
  serialOf = instSerial
456

    
457
instance TagsObject Instance where
458
  tagsOf = instTags
459

    
460
-- * IPolicy definitions
461

    
462
$(buildParam "ISpec" "ispec"
463
  [ simpleField ConstantUtils.ispecMemSize     [t| Int |]
464
  , simpleField ConstantUtils.ispecDiskSize    [t| Int |]
465
  , simpleField ConstantUtils.ispecDiskCount   [t| Int |]
466
  , simpleField ConstantUtils.ispecCpuCount    [t| Int |]
467
  , simpleField ConstantUtils.ispecNicCount    [t| Int |]
468
  , simpleField ConstantUtils.ispecSpindleUse  [t| Int |]
469
  ])
470

    
471
$(buildObject "MinMaxISpecs" "mmis"
472
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
473
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
474
  ])
475

    
476
-- | Custom partial ipolicy. This is not built via buildParam since it
477
-- has a special 2-level inheritance mode.
478
$(buildObject "PartialIPolicy" "ipolicy"
479
  [ optionalField . renameField "MinMaxISpecsP" $
480
    simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
481
  , optionalField . renameField "StdSpecP" $
482
    simpleField "std" [t| PartialISpecParams |]
483
  , optionalField . renameField "SpindleRatioP" $
484
    simpleField "spindle-ratio" [t| Double |]
485
  , optionalField . renameField "VcpuRatioP" $
486
    simpleField "vcpu-ratio" [t| Double |]
487
  , optionalField . renameField "DiskTemplatesP" $
488
    simpleField "disk-templates" [t| [DiskTemplate] |]
489
  ])
490

    
491
-- | Custom filled ipolicy. This is not built via buildParam since it
492
-- has a special 2-level inheritance mode.
493
$(buildObject "FilledIPolicy" "ipolicy"
494
  [ renameField "MinMaxISpecs" $
495
    simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
496
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
497
  , simpleField "spindle-ratio"  [t| Double |]
498
  , simpleField "vcpu-ratio"     [t| Double |]
499
  , simpleField "disk-templates" [t| [DiskTemplate] |]
500
  ])
501

    
502
-- | Custom filler for the ipolicy types.
503
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
504
fillIPolicy (FilledIPolicy { ipolicyMinMaxISpecs  = fminmax
505
                           , ipolicyStdSpec       = fstd
506
                           , ipolicySpindleRatio  = fspindleRatio
507
                           , ipolicyVcpuRatio     = fvcpuRatio
508
                           , ipolicyDiskTemplates = fdiskTemplates})
509
            (PartialIPolicy { ipolicyMinMaxISpecsP  = pminmax
510
                            , ipolicyStdSpecP       = pstd
511
                            , ipolicySpindleRatioP  = pspindleRatio
512
                            , ipolicyVcpuRatioP     = pvcpuRatio
513
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
514
  FilledIPolicy { ipolicyMinMaxISpecs  = fromMaybe fminmax pminmax
515
                , ipolicyStdSpec       = case pstd of
516
                                         Nothing -> fstd
517
                                         Just p -> fillISpecParams fstd p
518
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
519
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
520
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
521
                                         pdiskTemplates
522
                }
523
-- * Node definitions
524

    
525
$(buildParam "ND" "ndp"
526
  [ simpleField "oob_program"   [t| String |]
527
  , simpleField "spindle_count" [t| Int    |]
528
  , simpleField "exclusive_storage" [t| Bool |]
529
  , simpleField "ovs"           [t| Bool |]
530
  , simpleField "ovs_name"       [t| String |]
531
  , simpleField "ovs_link"       [t| String |]
532
  ])
533

    
534
$(buildObject "Node" "node" $
535
  [ simpleField "name"             [t| String |]
536
  , simpleField "primary_ip"       [t| String |]
537
  , simpleField "secondary_ip"     [t| String |]
538
  , simpleField "master_candidate" [t| Bool   |]
539
  , simpleField "offline"          [t| Bool   |]
540
  , simpleField "drained"          [t| Bool   |]
541
  , simpleField "group"            [t| String |]
542
  , simpleField "master_capable"   [t| Bool   |]
543
  , simpleField "vm_capable"       [t| Bool   |]
544
  , simpleField "ndparams"         [t| PartialNDParams |]
545
  , simpleField "powered"          [t| Bool   |]
546
  ]
547
  ++ timeStampFields
548
  ++ uuidFields
549
  ++ serialFields
550
  ++ tagsFields)
551

    
552
instance TimeStampObject Node where
553
  cTimeOf = nodeCtime
554
  mTimeOf = nodeMtime
555

    
556
instance UuidObject Node where
557
  uuidOf = nodeUuid
558

    
559
instance SerialNoObject Node where
560
  serialOf = nodeSerial
561

    
562
instance TagsObject Node where
563
  tagsOf = nodeTags
564

    
565
-- * NodeGroup definitions
566

    
567
-- | The disk parameters type.
568
type DiskParams = Container (Container JSValue)
569

    
570
-- | A mapping from network UUIDs to nic params of the networks.
571
type Networks = Container PartialNicParams
572

    
573
$(buildObject "NodeGroup" "group" $
574
  [ simpleField "name"         [t| String |]
575
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
576
  , simpleField "ndparams"     [t| PartialNDParams |]
577
  , simpleField "alloc_policy" [t| AllocPolicy     |]
578
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
579
  , simpleField "diskparams"   [t| DiskParams      |]
580
  , simpleField "networks"     [t| Networks        |]
581
  ]
582
  ++ timeStampFields
583
  ++ uuidFields
584
  ++ serialFields
585
  ++ tagsFields)
586

    
587
instance TimeStampObject NodeGroup where
588
  cTimeOf = groupCtime
589
  mTimeOf = groupMtime
590

    
591
instance UuidObject NodeGroup where
592
  uuidOf = groupUuid
593

    
594
instance SerialNoObject NodeGroup where
595
  serialOf = groupSerial
596

    
597
instance TagsObject NodeGroup where
598
  tagsOf = groupTags
599

    
600
-- | IP family type
601
$(declareIADT "IpFamily"
602
  [ ("IpFamilyV4", 'C.ip4Family)
603
  , ("IpFamilyV6", 'C.ip6Family)
604
  ])
605
$(makeJSONInstance ''IpFamily)
606

    
607
-- | Conversion from IP family to IP version. This is needed because
608
-- Python uses both, depending on context.
609
ipFamilyToVersion :: IpFamily -> Int
610
ipFamilyToVersion IpFamilyV4 = C.ip4Version
611
ipFamilyToVersion IpFamilyV6 = C.ip6Version
612

    
613
-- | Cluster HvParams (hvtype to hvparams mapping).
614
type ClusterHvParams = Container HvParams
615

    
616
-- | Cluster Os-HvParams (os to hvparams mapping).
617
type OsHvParams = Container ClusterHvParams
618

    
619
-- | Cluser BeParams.
620
type ClusterBeParams = Container FilledBeParams
621

    
622
-- | Cluster OsParams.
623
type ClusterOsParams = Container OsParams
624

    
625
-- | Cluster NicParams.
626
type ClusterNicParams = Container FilledNicParams
627

    
628
-- | Cluster UID Pool, list (low, high) UID ranges.
629
type UidPool = [(Int, Int)]
630

    
631
-- * Cluster definitions
632
$(buildObject "Cluster" "cluster" $
633
  [ simpleField "rsahostkeypub"           [t| String           |]
634
  , optionalField $
635
    simpleField "dsahostkeypub"           [t| String           |]
636
  , simpleField "highest_used_port"       [t| Int              |]
637
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
638
  , simpleField "mac_prefix"              [t| String           |]
639
  , optionalField $
640
    simpleField "volume_group_name"       [t| String           |]
641
  , simpleField "reserved_lvs"            [t| [String]         |]
642
  , optionalField $
643
    simpleField "drbd_usermode_helper"    [t| String           |]
644
  , simpleField "master_node"             [t| String           |]
645
  , simpleField "master_ip"               [t| String           |]
646
  , simpleField "master_netdev"           [t| String           |]
647
  , simpleField "master_netmask"          [t| Int              |]
648
  , simpleField "use_external_mip_script" [t| Bool             |]
649
  , simpleField "cluster_name"            [t| String           |]
650
  , simpleField "file_storage_dir"        [t| String           |]
651
  , simpleField "shared_file_storage_dir" [t| String           |]
652
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
653
  , simpleField "hvparams"                [t| ClusterHvParams  |]
654
  , simpleField "os_hvp"                  [t| OsHvParams       |]
655
  , simpleField "beparams"                [t| ClusterBeParams  |]
656
  , simpleField "osparams"                [t| ClusterOsParams  |]
657
  , simpleField "nicparams"               [t| ClusterNicParams |]
658
  , simpleField "ndparams"                [t| FilledNDParams   |]
659
  , simpleField "diskparams"              [t| DiskParams       |]
660
  , simpleField "candidate_pool_size"     [t| Int              |]
661
  , simpleField "modify_etc_hosts"        [t| Bool             |]
662
  , simpleField "modify_ssh_setup"        [t| Bool             |]
663
  , simpleField "maintain_node_health"    [t| Bool             |]
664
  , simpleField "uid_pool"                [t| UidPool          |]
665
  , simpleField "default_iallocator"      [t| String           |]
666
  , simpleField "hidden_os"               [t| [String]         |]
667
  , simpleField "blacklisted_os"          [t| [String]         |]
668
  , simpleField "primary_ip_family"       [t| IpFamily         |]
669
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
670
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
671
  , simpleField "enabled_disk_templates"  [t| [DiskTemplate]   |]
672
 ]
673
 ++ timeStampFields
674
 ++ uuidFields
675
 ++ serialFields
676
 ++ tagsFields)
677

    
678
instance TimeStampObject Cluster where
679
  cTimeOf = clusterCtime
680
  mTimeOf = clusterMtime
681

    
682
instance UuidObject Cluster where
683
  uuidOf = clusterUuid
684

    
685
instance SerialNoObject Cluster where
686
  serialOf = clusterSerial
687

    
688
instance TagsObject Cluster where
689
  tagsOf = clusterTags
690

    
691
-- * ConfigData definitions
692

    
693
$(buildObject "ConfigData" "config" $
694
--  timeStampFields ++
695
  [ simpleField "version"    [t| Int                 |]
696
  , simpleField "cluster"    [t| Cluster             |]
697
  , simpleField "nodes"      [t| Container Node      |]
698
  , simpleField "nodegroups" [t| Container NodeGroup |]
699
  , simpleField "instances"  [t| Container Instance  |]
700
  , simpleField "networks"   [t| Container Network   |]
701
  ]
702
  ++ serialFields)
703

    
704
instance SerialNoObject ConfigData where
705
  serialOf = configSerial