Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 346c3037

History | View | Annotate | Download (23.6 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 Ganeti.JSON
100
import Ganeti.Types
101
import Ganeti.THH
102
import Ganeti.Utils (sepSplit, tryRead)
103

    
104
-- * Generic definitions
105

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

    
113
-- | The hypervisor parameter type. This is currently a simple map,
114
-- without type checking on key/value pairs.
115
type HvParams = Container JSValue
116

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

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

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

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

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

    
139
-- * Network definitions
140

    
141
-- ** Ipv4 types
142

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

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

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

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

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

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

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

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

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

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

    
228
instance SerialNoObject Network where
229
  serialOf = networkSerial
230

    
231
instance TagsObject Network where
232
  tagsOf = networkTags
233

    
234
instance UuidObject Network where
235
  uuidOf = networkUuid
236

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

    
241
-- * NIC definitions
242

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

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

    
257
instance UuidObject PartialNic where
258
  uuidOf = nicUuid
259

    
260
-- * Disk definitions
261

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

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

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

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

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

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

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

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

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

    
403
instance UuidObject Disk where
404
  uuidOf = diskUuid
405

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

    
417
-- * Instance definitions
418

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

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

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

    
450
instance UuidObject Instance where
451
  uuidOf = instUuid
452

    
453
instance SerialNoObject Instance where
454
  serialOf = instSerial
455

    
456
instance TagsObject Instance where
457
  tagsOf = instTags
458

    
459
-- * IPolicy definitions
460

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

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

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

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

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

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

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

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

    
555
instance UuidObject Node where
556
  uuidOf = nodeUuid
557

    
558
instance SerialNoObject Node where
559
  serialOf = nodeSerial
560

    
561
instance TagsObject Node where
562
  tagsOf = nodeTags
563

    
564
-- * NodeGroup definitions
565

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

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

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

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

    
590
instance UuidObject NodeGroup where
591
  uuidOf = groupUuid
592

    
593
instance SerialNoObject NodeGroup where
594
  serialOf = groupSerial
595

    
596
instance TagsObject NodeGroup where
597
  tagsOf = groupTags
598

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

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

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

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

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

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

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

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

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

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

    
681
instance UuidObject Cluster where
682
  uuidOf = clusterUuid
683

    
684
instance SerialNoObject Cluster where
685
  serialOf = clusterSerial
686

    
687
instance TagsObject Cluster where
688
  tagsOf = clusterTags
689

    
690
-- * ConfigData definitions
691

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

    
703
instance SerialNoObject ConfigData where
704
  serialOf = configSerial