Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ d0de443e

History | View | Annotate | Download (23.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, 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
  ( 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
  , Ip4Address(..)
92
  , Ip4Network(..)
93
  , readIp4Address
94
  , nextIp4Address
95
  ) where
96

    
97
import Control.Applicative
98
import Data.List (foldl')
99
import Data.Maybe
100
import qualified Data.Map as Map
101
import qualified Data.Set as Set
102
import Data.Word
103
import Text.JSON (showJSON, readJSON, JSON, JSValue(..), fromJSString)
104
import qualified Text.JSON as J
105

    
106
import qualified Ganeti.Constants as C
107
import Ganeti.JSON
108
import Ganeti.Types
109
import Ganeti.THH
110
import Ganeti.Utils (sepSplit, tryRead)
111

    
112
-- * Generic definitions
113

    
114
-- | Fills one map with keys from the other map, if not already
115
-- existing. Mirrors objects.py:FillDict.
116
fillDict :: (Ord k) => Map.Map k v -> Map.Map k v -> [k] -> Map.Map k v
117
fillDict defaults custom skip_keys =
118
  let updated = Map.union custom defaults
119
  in foldl' (flip Map.delete) updated skip_keys
120

    
121
-- | The VTYPES, a mini-type system in Python.
122
$(declareSADT "VType"
123
  [ ("VTypeString",      'C.vtypeString)
124
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
125
  , ("VTypeBool",        'C.vtypeBool)
126
  , ("VTypeSize",        'C.vtypeSize)
127
  , ("VTypeInt",         'C.vtypeInt)
128
  ])
129
$(makeJSONInstance ''VType)
130

    
131
-- | The hypervisor parameter type. This is currently a simple map,
132
-- without type checking on key/value pairs.
133
type HvParams = Container JSValue
134

    
135
-- | The OS parameters type. This is, and will remain, a string
136
-- container, since the keys are dynamically declared by the OSes, and
137
-- the values are always strings.
138
type OsParams = Container String
139

    
140
-- | Class of objects that have timestamps.
141
class TimeStampObject a where
142
  cTimeOf :: a -> Double
143
  mTimeOf :: a -> Double
144

    
145
-- | Class of objects that have an UUID.
146
class UuidObject a where
147
  uuidOf :: a -> String
148

    
149
-- | Class of object that have a serial number.
150
class SerialNoObject a where
151
  serialOf :: a -> Int
152

    
153
-- | Class of objects that have tags.
154
class TagsObject a where
155
  tagsOf :: a -> Set.Set String
156

    
157
-- * Node role object
158

    
159
$(declareSADT "NodeRole"
160
  [ ("NROffline",   'C.nrOffline)
161
  , ("NRDrained",   'C.nrDrained)
162
  , ("NRRegular",   'C.nrRegular)
163
  , ("NRCandidate", 'C.nrMcandidate)
164
  , ("NRMaster",    'C.nrMaster)
165
  ])
166
$(makeJSONInstance ''NodeRole)
167

    
168
-- | The description of the node role.
169
roleDescription :: NodeRole -> String
170
roleDescription NROffline   = "offline"
171
roleDescription NRDrained   = "drained"
172
roleDescription NRRegular   = "regular"
173
roleDescription NRCandidate = "master candidate"
174
roleDescription NRMaster    = "master"
175

    
176
-- * Network definitions
177

    
178
-- ** Ipv4 types
179

    
180
-- | Custom type for a simple IPv4 address.
181
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
182
                  deriving Eq
183

    
184
instance Show Ip4Address where
185
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
186
                              show c ++ "." ++ show d
187

    
188
-- | Parses an IPv4 address from a string.
189
readIp4Address :: (Applicative m, Monad m) => String -> m Ip4Address
190
readIp4Address s =
191
  case sepSplit '.' s of
192
    [a, b, c, d] -> Ip4Address <$>
193
                      tryRead "first octect" a <*>
194
                      tryRead "second octet" b <*>
195
                      tryRead "third octet"  c <*>
196
                      tryRead "fourth octet" d
197
    _ -> fail $ "Can't parse IPv4 address from string " ++ s
198

    
199
-- | JSON instance for 'Ip4Address'.
200
instance JSON Ip4Address where
201
  showJSON = showJSON . show
202
  readJSON (JSString s) = readIp4Address (fromJSString s)
203
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 address"
204

    
205
-- | \"Next\" address implementation for IPv4 addresses.
206
--
207
-- Note that this loops! Note also that this is a very dumb
208
-- implementation.
209
nextIp4Address :: Ip4Address -> Ip4Address
210
nextIp4Address (Ip4Address a b c d) =
211
  let inc xs y = if all (==0) xs then y + 1 else y
212
      d' = d + 1
213
      c' = inc [d'] c
214
      b' = inc [c', d'] b
215
      a' = inc [b', c', d'] a
216
  in Ip4Address a' b' c' d'
217

    
218
-- | Custom type for an IPv4 network.
219
data Ip4Network = Ip4Network Ip4Address Word8
220
                  deriving Eq
221

    
222
instance Show Ip4Network where
223
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
224

    
225
-- | JSON instance for 'Ip4Network'.
226
instance JSON Ip4Network where
227
  showJSON = showJSON . show
228
  readJSON (JSString s) =
229
    case sepSplit '/' (fromJSString s) of
230
      [ip, nm] -> do
231
        ip' <- readIp4Address ip
232
        nm' <- tryRead "parsing netmask" nm
233
        if nm' >= 0 && nm' <= 32
234
          then return $ Ip4Network ip' nm'
235
          else fail $ "Invalid netmask " ++ show nm' ++ " from string " ++
236
                      fromJSString s
237
      _ -> fail $ "Can't parse IPv4 network from string " ++ fromJSString s
238
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 network"
239

    
240
-- ** Ganeti \"network\" config object.
241

    
242
-- FIXME: Not all types might be correct here, since they
243
-- haven't been exhaustively deduced from the python code yet.
244
$(buildObject "Network" "network" $
245
  [ simpleField "name"             [t| NonEmptyString |]
246
  , optionalField $
247
    simpleField "mac_prefix"       [t| String |]
248
  , simpleField "network"          [t| Ip4Network |]
249
  , optionalField $
250
    simpleField "network6"         [t| String |]
251
  , optionalField $
252
    simpleField "gateway"          [t| Ip4Address |]
253
  , optionalField $
254
    simpleField "gateway6"         [t| String |]
255
  , optionalField $
256
    simpleField "reservations"     [t| String |]
257
  , optionalField $
258
    simpleField "ext_reservations" [t| String |]
259
  ]
260
  ++ uuidFields
261
  ++ serialFields
262
  ++ tagsFields)
263

    
264
instance SerialNoObject Network where
265
  serialOf = networkSerial
266

    
267
instance TagsObject Network where
268
  tagsOf = networkTags
269

    
270
instance UuidObject Network where
271
  uuidOf = networkUuid
272

    
273
-- * NIC definitions
274

    
275
$(buildParam "Nic" "nicp"
276
  [ simpleField "mode" [t| NICMode |]
277
  , simpleField "link" [t| String  |]
278
  ])
279

    
280
$(buildObject "PartialNic" "nic"
281
  [ simpleField "mac" [t| String |]
282
  , optionalField $ simpleField "ip" [t| String |]
283
  , simpleField "nicparams" [t| PartialNicParams |]
284
  , optionalField $ simpleField "network" [t| String |]
285
  ])
286

    
287
-- * Disk definitions
288

    
289
$(declareSADT "DiskMode"
290
  [ ("DiskRdOnly", 'C.diskRdonly)
291
  , ("DiskRdWr",   'C.diskRdwr)
292
  ])
293
$(makeJSONInstance ''DiskMode)
294

    
295
$(declareSADT "DiskType"
296
  [ ("LD_LV",       'C.ldLv)
297
  , ("LD_DRBD8",    'C.ldDrbd8)
298
  , ("LD_FILE",     'C.ldFile)
299
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
300
  , ("LD_RADOS",    'C.ldRbd)
301
  , ("LD_EXT",      'C.ldExt)
302
  ])
303
$(makeJSONInstance ''DiskType)
304

    
305
-- | The persistent block driver type. Currently only one type is allowed.
306
$(declareSADT "BlockDriver"
307
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
308
  ])
309
$(makeJSONInstance ''BlockDriver)
310

    
311
-- | Constant for the dev_type key entry in the disk config.
312
devType :: String
313
devType = "dev_type"
314

    
315
-- | The disk configuration type. This includes the disk type itself,
316
-- for a more complete consistency. Note that since in the Python
317
-- code-base there's no authoritative place where we document the
318
-- logical id, this is probably a good reference point.
319
data DiskLogicalId
320
  = LIDPlain String String  -- ^ Volume group, logical volume
321
  | LIDDrbd8 String String Int Int Int String
322
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
323
  | LIDFile FileDriver String -- ^ Driver, path
324
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
325
  | LIDRados String String -- ^ Unused, path
326
  | LIDExt String String -- ^ ExtProvider, unique name
327
    deriving (Show, Eq)
328

    
329
-- | Mapping from a logical id to a disk type.
330
lidDiskType :: DiskLogicalId -> DiskType
331
lidDiskType (LIDPlain {}) = LD_LV
332
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
333
lidDiskType (LIDFile  {}) = LD_FILE
334
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
335
lidDiskType (LIDRados {}) = LD_RADOS
336
lidDiskType (LIDExt {}) = LD_EXT
337

    
338
-- | Builds the extra disk_type field for a given logical id.
339
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
340
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
341

    
342
-- | Custom encoder for DiskLogicalId (logical id only).
343
encodeDLId :: DiskLogicalId -> JSValue
344
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
345
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
346
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
347
          , showJSON minorA, showJSON minorB, showJSON key ]
348
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
349
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
350
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
351
encodeDLId (LIDExt extprovider name) =
352
  JSArray [showJSON extprovider, showJSON name]
353

    
354
-- | Custom encoder for DiskLogicalId, composing both the logical id
355
-- and the extra disk_type field.
356
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
357
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
358

    
359
-- | Custom decoder for DiskLogicalId. This is manual for now, since
360
-- we don't have yet automation for separate-key style fields.
361
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
362
decodeDLId obj lid = do
363
  dtype <- fromObj obj devType
364
  case dtype of
365
    LD_DRBD8 ->
366
      case lid of
367
        JSArray [nA, nB, p, mA, mB, k] -> do
368
          nA' <- readJSON nA
369
          nB' <- readJSON nB
370
          p'  <- readJSON p
371
          mA' <- readJSON mA
372
          mB' <- readJSON mB
373
          k'  <- readJSON k
374
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
375
        _ -> fail "Can't read logical_id for DRBD8 type"
376
    LD_LV ->
377
      case lid of
378
        JSArray [vg, lv] -> do
379
          vg' <- readJSON vg
380
          lv' <- readJSON lv
381
          return $ LIDPlain vg' lv'
382
        _ -> fail "Can't read logical_id for plain type"
383
    LD_FILE ->
384
      case lid of
385
        JSArray [driver, path] -> do
386
          driver' <- readJSON driver
387
          path'   <- readJSON path
388
          return $ LIDFile driver' path'
389
        _ -> fail "Can't read logical_id for file type"
390
    LD_BLOCKDEV ->
391
      case lid of
392
        JSArray [driver, path] -> do
393
          driver' <- readJSON driver
394
          path'   <- readJSON path
395
          return $ LIDBlockDev driver' path'
396
        _ -> fail "Can't read logical_id for blockdev type"
397
    LD_RADOS ->
398
      case lid of
399
        JSArray [driver, path] -> do
400
          driver' <- readJSON driver
401
          path'   <- readJSON path
402
          return $ LIDRados driver' path'
403
        _ -> fail "Can't read logical_id for rdb type"
404
    LD_EXT ->
405
      case lid of
406
        JSArray [extprovider, name] -> do
407
          extprovider' <- readJSON extprovider
408
          name'   <- readJSON name
409
          return $ LIDExt extprovider' name'
410
        _ -> fail "Can't read logical_id for extstorage type"
411

    
412
-- | Disk data structure.
413
--
414
-- This is declared manually as it's a recursive structure, and our TH
415
-- code currently can't build it.
416
data Disk = Disk
417
  { diskLogicalId  :: DiskLogicalId
418
--  , diskPhysicalId :: String
419
  , diskChildren   :: [Disk]
420
  , diskIvName     :: String
421
  , diskSize       :: Int
422
  , diskMode       :: DiskMode
423
  } deriving (Show, Eq)
424

    
425
$(buildObjectSerialisation "Disk"
426
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
427
      simpleField "logical_id"    [t| DiskLogicalId   |]
428
--  , simpleField "physical_id" [t| String   |]
429
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
430
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
431
  , simpleField "size" [t| Int |]
432
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
433
  ])
434

    
435
-- * Instance definitions
436

    
437
$(declareSADT "AdminState"
438
  [ ("AdminOffline", 'C.adminstOffline)
439
  , ("AdminDown",    'C.adminstDown)
440
  , ("AdminUp",      'C.adminstUp)
441
  ])
442
$(makeJSONInstance ''AdminState)
443

    
444
$(buildParam "Be" "bep"
445
  [ simpleField "minmem"       [t| Int  |]
446
  , simpleField "maxmem"       [t| Int  |]
447
  , simpleField "vcpus"        [t| Int  |]
448
  , simpleField "auto_balance" [t| Bool |]
449
  ])
450

    
451
$(buildObject "Instance" "inst" $
452
  [ simpleField "name"           [t| String             |]
453
  , simpleField "primary_node"   [t| String             |]
454
  , simpleField "os"             [t| String             |]
455
  , simpleField "hypervisor"     [t| Hypervisor         |]
456
  , simpleField "hvparams"       [t| HvParams           |]
457
  , simpleField "beparams"       [t| PartialBeParams    |]
458
  , simpleField "osparams"       [t| OsParams           |]
459
  , simpleField "admin_state"    [t| AdminState         |]
460
  , simpleField "nics"           [t| [PartialNic]       |]
461
  , simpleField "disks"          [t| [Disk]             |]
462
  , simpleField "disk_template"  [t| DiskTemplate       |]
463
  , optionalField $ simpleField "network_port" [t| Int  |]
464
  ]
465
  ++ timeStampFields
466
  ++ uuidFields
467
  ++ serialFields
468
  ++ tagsFields)
469

    
470
instance TimeStampObject Instance where
471
  cTimeOf = instCtime
472
  mTimeOf = instMtime
473

    
474
instance UuidObject Instance where
475
  uuidOf = instUuid
476

    
477
instance SerialNoObject Instance where
478
  serialOf = instSerial
479

    
480
instance TagsObject Instance where
481
  tagsOf = instTags
482

    
483
-- * IPolicy definitions
484

    
485
$(buildParam "ISpec" "ispec"
486
  [ simpleField C.ispecMemSize     [t| Int |]
487
  , simpleField C.ispecDiskSize    [t| Int |]
488
  , simpleField C.ispecDiskCount   [t| Int |]
489
  , simpleField C.ispecCpuCount    [t| Int |]
490
  , simpleField C.ispecNicCount    [t| Int |]
491
  , simpleField C.ispecSpindleUse  [t| Int |]
492
  ])
493

    
494
-- | Custom partial ipolicy. This is not built via buildParam since it
495
-- has a special 2-level inheritance mode.
496
$(buildObject "PartialIPolicy" "ipolicy"
497
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
498
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
499
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
500
  , optionalField . renameField "SpindleRatioP"
501
                    $ simpleField "spindle-ratio"  [t| Double |]
502
  , optionalField . renameField "VcpuRatioP"
503
                    $ simpleField "vcpu-ratio"     [t| Double |]
504
  , optionalField . renameField "DiskTemplatesP"
505
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
506
  ])
507

    
508
-- | Custom filled ipolicy. This is not built via buildParam since it
509
-- has a special 2-level inheritance mode.
510
$(buildObject "FilledIPolicy" "ipolicy"
511
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
512
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
513
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
514
  , simpleField "spindle-ratio"  [t| Double |]
515
  , simpleField "vcpu-ratio"     [t| Double |]
516
  , simpleField "disk-templates" [t| [DiskTemplate] |]
517
  ])
518

    
519
-- | Custom filler for the ipolicy types.
520
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
521
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
522
                           , ipolicyMaxSpec       = fmax
523
                           , ipolicyStdSpec       = fstd
524
                           , ipolicySpindleRatio  = fspindleRatio
525
                           , ipolicyVcpuRatio     = fvcpuRatio
526
                           , ipolicyDiskTemplates = fdiskTemplates})
527
            (PartialIPolicy { ipolicyMinSpecP       = pmin
528
                            , ipolicyMaxSpecP       = pmax
529
                            , ipolicyStdSpecP       = pstd
530
                            , ipolicySpindleRatioP  = pspindleRatio
531
                            , ipolicyVcpuRatioP     = pvcpuRatio
532
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
533
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
534
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
535
                , ipolicyStdSpec       = fillISpecParams fstd pstd
536
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
537
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
538
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
539
                                         pdiskTemplates
540
                }
541
-- * Node definitions
542

    
543
$(buildParam "ND" "ndp"
544
  [ simpleField "oob_program"   [t| String |]
545
  , simpleField "spindle_count" [t| Int    |]
546
  , simpleField "exclusive_storage" [t| Bool |]
547
  ])
548

    
549
$(buildObject "Node" "node" $
550
  [ simpleField "name"             [t| String |]
551
  , simpleField "primary_ip"       [t| String |]
552
  , simpleField "secondary_ip"     [t| String |]
553
  , simpleField "master_candidate" [t| Bool   |]
554
  , simpleField "offline"          [t| Bool   |]
555
  , simpleField "drained"          [t| Bool   |]
556
  , simpleField "group"            [t| String |]
557
  , simpleField "master_capable"   [t| Bool   |]
558
  , simpleField "vm_capable"       [t| Bool   |]
559
  , simpleField "ndparams"         [t| PartialNDParams |]
560
  , simpleField "powered"          [t| Bool   |]
561
  ]
562
  ++ timeStampFields
563
  ++ uuidFields
564
  ++ serialFields
565
  ++ tagsFields)
566

    
567
instance TimeStampObject Node where
568
  cTimeOf = nodeCtime
569
  mTimeOf = nodeMtime
570

    
571
instance UuidObject Node where
572
  uuidOf = nodeUuid
573

    
574
instance SerialNoObject Node where
575
  serialOf = nodeSerial
576

    
577
instance TagsObject Node where
578
  tagsOf = nodeTags
579

    
580
-- * NodeGroup definitions
581

    
582
-- | The disk parameters type.
583
type DiskParams = Container (Container JSValue)
584

    
585
-- | A mapping from network UUIDs to nic params of the networks.
586
type Networks = Container PartialNicParams
587

    
588
$(buildObject "NodeGroup" "group" $
589
  [ simpleField "name"         [t| String |]
590
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
591
  , simpleField "ndparams"     [t| PartialNDParams |]
592
  , simpleField "alloc_policy" [t| AllocPolicy     |]
593
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
594
  , simpleField "diskparams"   [t| DiskParams      |]
595
  , simpleField "networks"     [t| Networks        |]
596
  ]
597
  ++ timeStampFields
598
  ++ uuidFields
599
  ++ serialFields
600
  ++ tagsFields)
601

    
602
instance TimeStampObject NodeGroup where
603
  cTimeOf = groupCtime
604
  mTimeOf = groupMtime
605

    
606
instance UuidObject NodeGroup where
607
  uuidOf = groupUuid
608

    
609
instance SerialNoObject NodeGroup where
610
  serialOf = groupSerial
611

    
612
instance TagsObject NodeGroup where
613
  tagsOf = groupTags
614

    
615
-- | IP family type
616
$(declareIADT "IpFamily"
617
  [ ("IpFamilyV4", 'C.ip4Family)
618
  , ("IpFamilyV6", 'C.ip6Family)
619
  ])
620
$(makeJSONInstance ''IpFamily)
621

    
622
-- | Conversion from IP family to IP version. This is needed because
623
-- Python uses both, depending on context.
624
ipFamilyToVersion :: IpFamily -> Int
625
ipFamilyToVersion IpFamilyV4 = C.ip4Version
626
ipFamilyToVersion IpFamilyV6 = C.ip6Version
627

    
628
-- | Cluster HvParams (hvtype to hvparams mapping).
629
type ClusterHvParams = Container HvParams
630

    
631
-- | Cluster Os-HvParams (os to hvparams mapping).
632
type OsHvParams = Container ClusterHvParams
633

    
634
-- | Cluser BeParams.
635
type ClusterBeParams = Container FilledBeParams
636

    
637
-- | Cluster OsParams.
638
type ClusterOsParams = Container OsParams
639

    
640
-- | Cluster NicParams.
641
type ClusterNicParams = Container FilledNicParams
642

    
643
-- | Cluster UID Pool, list (low, high) UID ranges.
644
type UidPool = [(Int, Int)]
645

    
646
-- * Cluster definitions
647
$(buildObject "Cluster" "cluster" $
648
  [ simpleField "rsahostkeypub"           [t| String           |]
649
  , simpleField "highest_used_port"       [t| Int              |]
650
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
651
  , simpleField "mac_prefix"              [t| String           |]
652
  , optionalField $
653
    simpleField "volume_group_name"       [t| String           |]
654
  , simpleField "reserved_lvs"            [t| [String]         |]
655
  , optionalField $
656
    simpleField "drbd_usermode_helper"    [t| String           |]
657
  , simpleField "master_node"             [t| String           |]
658
  , simpleField "master_ip"               [t| String           |]
659
  , simpleField "master_netdev"           [t| String           |]
660
  , simpleField "master_netmask"          [t| Int              |]
661
  , simpleField "use_external_mip_script" [t| Bool             |]
662
  , simpleField "cluster_name"            [t| String           |]
663
  , simpleField "file_storage_dir"        [t| String           |]
664
  , simpleField "shared_file_storage_dir" [t| String           |]
665
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
666
  , simpleField "hvparams"                [t| ClusterHvParams  |]
667
  , simpleField "os_hvp"                  [t| OsHvParams       |]
668
  , simpleField "beparams"                [t| ClusterBeParams  |]
669
  , simpleField "osparams"                [t| ClusterOsParams  |]
670
  , simpleField "nicparams"               [t| ClusterNicParams |]
671
  , simpleField "ndparams"                [t| FilledNDParams   |]
672
  , simpleField "diskparams"              [t| DiskParams       |]
673
  , simpleField "candidate_pool_size"     [t| Int              |]
674
  , simpleField "modify_etc_hosts"        [t| Bool             |]
675
  , simpleField "modify_ssh_setup"        [t| Bool             |]
676
  , simpleField "maintain_node_health"    [t| Bool             |]
677
  , simpleField "uid_pool"                [t| UidPool          |]
678
  , simpleField "default_iallocator"      [t| String           |]
679
  , simpleField "hidden_os"               [t| [String]         |]
680
  , simpleField "blacklisted_os"          [t| [String]         |]
681
  , simpleField "primary_ip_family"       [t| IpFamily         |]
682
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
683
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
684
  , simpleField "enabled_storage_types"   [t| [StorageType]    |]
685
 ]
686
 ++ timeStampFields
687
 ++ uuidFields
688
 ++ serialFields
689
 ++ tagsFields)
690

    
691
instance TimeStampObject Cluster where
692
  cTimeOf = clusterCtime
693
  mTimeOf = clusterMtime
694

    
695
instance UuidObject Cluster where
696
  uuidOf = clusterUuid
697

    
698
instance SerialNoObject Cluster where
699
  serialOf = clusterSerial
700

    
701
instance TagsObject Cluster where
702
  tagsOf = clusterTags
703

    
704
-- * ConfigData definitions
705

    
706
$(buildObject "ConfigData" "config" $
707
--  timeStampFields ++
708
  [ simpleField "version"    [t| Int                 |]
709
  , simpleField "cluster"    [t| Cluster             |]
710
  , simpleField "nodes"      [t| Container Node      |]
711
  , simpleField "nodegroups" [t| Container NodeGroup |]
712
  , simpleField "instances"  [t| Container Instance  |]
713
  , simpleField "networks"   [t| Container Network   |]
714
  ]
715
  ++ serialFields)
716

    
717
instance SerialNoObject ConfigData where
718
  serialOf = configSerial