Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ a5efec93

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

    
92
import Control.Applicative
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 Data.Word
98
import System.Time (ClockTime(..))
99
import Text.JSON (showJSON, readJSON, JSON, JSValue(..), fromJSString)
100
import qualified Text.JSON as J
101

    
102
import qualified AutoConf
103
import qualified Ganeti.Constants as C
104
import qualified Ganeti.ConstantUtils as ConstantUtils
105
import Ganeti.JSON
106
import Ganeti.Types
107
import Ganeti.THH
108
import Ganeti.Utils (sepSplit, tryRead, parseUnitAssumeBinary)
109

    
110
-- * Generic definitions
111

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

    
119
-- | The hypervisor parameter type. This is currently a simple map,
120
-- without type checking on key/value pairs.
121
type HvParams = Container JSValue
122

    
123
-- | The OS parameters type. This is, and will remain, a string
124
-- container, since the keys are dynamically declared by the OSes, and
125
-- the values are always strings.
126
type OsParams = Container String
127
type OsParamsPrivate = Container (Private String)
128

    
129
-- | Class of objects that have timestamps.
130
class TimeStampObject a where
131
  cTimeOf :: a -> ClockTime
132
  mTimeOf :: a -> ClockTime
133

    
134
-- | Class of objects that have an UUID.
135
class UuidObject a where
136
  uuidOf :: a -> String
137

    
138
-- | Class of object that have a serial number.
139
class SerialNoObject a where
140
  serialOf :: a -> Int
141

    
142
-- | Class of objects that have tags.
143
class TagsObject a where
144
  tagsOf :: a -> Set.Set String
145

    
146
-- * Network definitions
147

    
148
-- ** Ipv4 types
149

    
150
-- | Custom type for a simple IPv4 address.
151
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
152
                  deriving Eq
153

    
154
instance Show Ip4Address where
155
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
156
                              show c ++ "." ++ show d
157

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

    
169
-- | JSON instance for 'Ip4Address'.
170
instance JSON Ip4Address where
171
  showJSON = showJSON . show
172
  readJSON (JSString s) = readIp4Address (fromJSString s)
173
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 address"
174

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

    
188
-- | Custom type for an IPv4 network.
189
data Ip4Network = Ip4Network Ip4Address Word8
190
                  deriving Eq
191

    
192
instance Show Ip4Network where
193
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
194

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

    
210
-- ** Ganeti \"network\" config object.
211

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

    
235
instance SerialNoObject Network where
236
  serialOf = networkSerial
237

    
238
instance TagsObject Network where
239
  tagsOf = networkTags
240

    
241
instance UuidObject Network where
242
  uuidOf = networkUuid
243

    
244
instance TimeStampObject Network where
245
  cTimeOf = networkCtime
246
  mTimeOf = networkMtime
247

    
248
-- * NIC definitions
249

    
250
$(buildParam "Nic" "nicp"
251
  [ simpleField "mode" [t| NICMode |]
252
  , simpleField "link" [t| String  |]
253
  , simpleField "vlan" [t| String |]
254
  ])
255

    
256
$(buildObject "PartialNic" "nic" $
257
  [ simpleField "mac" [t| String |]
258
  , optionalField $ simpleField "ip" [t| String |]
259
  , simpleField "nicparams" [t| PartialNicParams |]
260
  , optionalField $ simpleField "network" [t| String |]
261
  , optionalField $ simpleField "name" [t| String |]
262
  ] ++ uuidFields)
263

    
264
instance UuidObject PartialNic where
265
  uuidOf = nicUuid
266

    
267
-- * Disk definitions
268

    
269
-- | Constant for the dev_type key entry in the disk config.
270
devType :: String
271
devType = "dev_type"
272

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

    
288
-- | Mapping from a logical id to a disk type.
289
lidDiskType :: DiskLogicalId -> DiskTemplate
290
lidDiskType (LIDPlain {}) = DTPlain
291
lidDiskType (LIDDrbd8 {}) = DTDrbd8
292
lidDiskType (LIDFile  {}) = DTFile
293
lidDiskType (LIDSharedFile  {}) = DTSharedFile
294
lidDiskType (LIDBlockDev {}) = DTBlock
295
lidDiskType (LIDRados {}) = DTRbd
296
lidDiskType (LIDExt {}) = DTExt
297

    
298
-- | Builds the extra disk_type field for a given logical id.
299
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
300
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
301

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

    
316
-- | Custom encoder for DiskLogicalId, composing both the logical id
317
-- and the extra disk_type field.
318
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
319
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
320

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

    
390
-- | Disk data structure.
391
--
392
-- This is declared manually as it's a recursive structure, and our TH
393
-- code currently can't build it.
394
data Disk = Disk
395
  { diskLogicalId  :: DiskLogicalId
396
  , diskChildren   :: [Disk]
397
  , diskIvName     :: String
398
  , diskSize       :: Int
399
  , diskMode       :: DiskMode
400
  , diskName       :: Maybe String
401
  , diskSpindles   :: Maybe Int
402
  , diskUuid       :: String
403
  } deriving (Show, Eq)
404

    
405
$(buildObjectSerialisation "Disk" $
406
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
407
      simpleField "logical_id"    [t| DiskLogicalId   |]
408
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
409
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
410
  , simpleField "size" [t| Int |]
411
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
412
  , optionalField $ simpleField "name" [t| String |]
413
  , optionalField $ simpleField "spindles" [t| Int |]
414
  ]
415
  ++ uuidFields)
416

    
417
instance UuidObject Disk where
418
  uuidOf = diskUuid
419

    
420
-- | Determines whether a disk or one of his children has the given logical id
421
-- (determined by the volume group name and by the logical volume name).
422
-- This can be true only for DRBD or LVM disks.
423
includesLogicalId :: String -> String -> Disk -> Bool
424
includesLogicalId vg_name lv_name disk =
425
  case diskLogicalId disk of
426
    LIDPlain vg lv -> vg_name == vg && lv_name == lv
427
    LIDDrbd8 {} ->
428
      any (includesLogicalId vg_name lv_name) $ diskChildren disk
429
    _ -> False
430

    
431
-- * Instance definitions
432

    
433
$(buildParam "Be" "bep"
434
  [ specialNumericalField 'parseUnitAssumeBinary
435
      $ simpleField "minmem"      [t| Int  |]
436
  , specialNumericalField 'parseUnitAssumeBinary
437
      $ simpleField "maxmem"      [t| Int  |]
438
  , simpleField "vcpus"           [t| Int  |]
439
  , simpleField "auto_balance"    [t| Bool |]
440
  , simpleField "always_failover" [t| Bool |]
441
  , simpleField "spindle_use"     [t| Int  |]
442
  ])
443

    
444
$(buildObject "Instance" "inst" $
445
  [ simpleField "name"             [t| String             |]
446
  , simpleField "primary_node"     [t| String             |]
447
  , simpleField "os"               [t| String             |]
448
  , simpleField "hypervisor"       [t| Hypervisor         |]
449
  , simpleField "hvparams"         [t| HvParams           |]
450
  , simpleField "beparams"         [t| PartialBeParams    |]
451
  , simpleField "osparams"         [t| OsParams           |]
452
  , simpleField "osparams_private" [t| OsParamsPrivate    |]
453
  , simpleField "admin_state"      [t| AdminState         |]
454
  , simpleField "nics"             [t| [PartialNic]       |]
455
  , simpleField "disks"            [t| [Disk]             |]
456
  , simpleField "disk_template"    [t| DiskTemplate       |]
457
  , simpleField "disks_active"     [t| Bool               |]
458
  , optionalField $ simpleField "network_port" [t| Int  |]
459
  ]
460
  ++ timeStampFields
461
  ++ uuidFields
462
  ++ serialFields
463
  ++ tagsFields)
464

    
465
instance TimeStampObject Instance where
466
  cTimeOf = instCtime
467
  mTimeOf = instMtime
468

    
469
instance UuidObject Instance where
470
  uuidOf = instUuid
471

    
472
instance SerialNoObject Instance where
473
  serialOf = instSerial
474

    
475
instance TagsObject Instance where
476
  tagsOf = instTags
477

    
478
-- | Retrieves the real disk size requirements for all the disks of the
479
-- instance. This includes the metadata etc. and is different from the values
480
-- visible to the instance.
481
getDiskSizeRequirements :: Instance -> Int
482
getDiskSizeRequirements inst =
483
  sum . map
484
    (\disk -> case instDiskTemplate inst of
485
                DTDrbd8    -> diskSize disk + C.drbdMetaSize
486
                DTDiskless -> 0
487
                DTBlock    -> 0
488
                _          -> diskSize disk )
489
    $ instDisks inst
490

    
491
-- * IPolicy definitions
492

    
493
$(buildParam "ISpec" "ispec"
494
  [ simpleField ConstantUtils.ispecMemSize     [t| Int |]
495
  , simpleField ConstantUtils.ispecDiskSize    [t| Int |]
496
  , simpleField ConstantUtils.ispecDiskCount   [t| Int |]
497
  , simpleField ConstantUtils.ispecCpuCount    [t| Int |]
498
  , simpleField ConstantUtils.ispecNicCount    [t| Int |]
499
  , simpleField ConstantUtils.ispecSpindleUse  [t| Int |]
500
  ])
501

    
502
$(buildObject "MinMaxISpecs" "mmis"
503
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
504
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
505
  ])
506

    
507
-- | Custom partial ipolicy. This is not built via buildParam since it
508
-- has a special 2-level inheritance mode.
509
$(buildObject "PartialIPolicy" "ipolicy"
510
  [ optionalField . renameField "MinMaxISpecsP" $
511
    simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
512
  , optionalField . renameField "StdSpecP" $
513
    simpleField "std" [t| PartialISpecParams |]
514
  , optionalField . renameField "SpindleRatioP" $
515
    simpleField "spindle-ratio" [t| Double |]
516
  , optionalField . renameField "VcpuRatioP" $
517
    simpleField "vcpu-ratio" [t| Double |]
518
  , optionalField . renameField "DiskTemplatesP" $
519
    simpleField "disk-templates" [t| [DiskTemplate] |]
520
  ])
521

    
522
-- | Custom filled ipolicy. This is not built via buildParam since it
523
-- has a special 2-level inheritance mode.
524
$(buildObject "FilledIPolicy" "ipolicy"
525
  [ renameField "MinMaxISpecs" $
526
    simpleField ConstantUtils.ispecsMinmax [t| [MinMaxISpecs] |]
527
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
528
  , simpleField "spindle-ratio"  [t| Double |]
529
  , simpleField "vcpu-ratio"     [t| Double |]
530
  , simpleField "disk-templates" [t| [DiskTemplate] |]
531
  ])
532

    
533
-- | Custom filler for the ipolicy types.
534
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
535
fillIPolicy (FilledIPolicy { ipolicyMinMaxISpecs  = fminmax
536
                           , ipolicyStdSpec       = fstd
537
                           , ipolicySpindleRatio  = fspindleRatio
538
                           , ipolicyVcpuRatio     = fvcpuRatio
539
                           , ipolicyDiskTemplates = fdiskTemplates})
540
            (PartialIPolicy { ipolicyMinMaxISpecsP  = pminmax
541
                            , ipolicyStdSpecP       = pstd
542
                            , ipolicySpindleRatioP  = pspindleRatio
543
                            , ipolicyVcpuRatioP     = pvcpuRatio
544
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
545
  FilledIPolicy { ipolicyMinMaxISpecs  = fromMaybe fminmax pminmax
546
                , ipolicyStdSpec       = case pstd of
547
                                         Nothing -> fstd
548
                                         Just p -> fillISpecParams fstd p
549
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
550
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
551
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
552
                                         pdiskTemplates
553
                }
554
-- * Node definitions
555

    
556
$(buildParam "ND" "ndp"
557
  [ simpleField "oob_program"   [t| String |]
558
  , simpleField "spindle_count" [t| Int    |]
559
  , simpleField "exclusive_storage" [t| Bool |]
560
  , simpleField "ovs"           [t| Bool |]
561
  , simpleField "ovs_name"       [t| String |]
562
  , simpleField "ovs_link"       [t| String |]
563
  , simpleField "ssh_port"      [t| Int |]
564
  ])
565

    
566
$(buildObject "Node" "node" $
567
  [ simpleField "name"             [t| String |]
568
  , simpleField "primary_ip"       [t| String |]
569
  , simpleField "secondary_ip"     [t| String |]
570
  , simpleField "master_candidate" [t| Bool   |]
571
  , simpleField "offline"          [t| Bool   |]
572
  , simpleField "drained"          [t| Bool   |]
573
  , simpleField "group"            [t| String |]
574
  , simpleField "master_capable"   [t| Bool   |]
575
  , simpleField "vm_capable"       [t| Bool   |]
576
  , simpleField "ndparams"         [t| PartialNDParams |]
577
  , simpleField "powered"          [t| Bool   |]
578
  ]
579
  ++ timeStampFields
580
  ++ uuidFields
581
  ++ serialFields
582
  ++ tagsFields)
583

    
584
instance TimeStampObject Node where
585
  cTimeOf = nodeCtime
586
  mTimeOf = nodeMtime
587

    
588
instance UuidObject Node where
589
  uuidOf = nodeUuid
590

    
591
instance SerialNoObject Node where
592
  serialOf = nodeSerial
593

    
594
instance TagsObject Node where
595
  tagsOf = nodeTags
596

    
597
-- * NodeGroup definitions
598

    
599
-- | The disk parameters type.
600
type DiskParams = Container (Container JSValue)
601

    
602
-- | A mapping from network UUIDs to nic params of the networks.
603
type Networks = Container PartialNicParams
604

    
605
$(buildObject "NodeGroup" "group" $
606
  [ simpleField "name"         [t| String |]
607
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
608
  , simpleField "ndparams"     [t| PartialNDParams |]
609
  , simpleField "alloc_policy" [t| AllocPolicy     |]
610
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
611
  , simpleField "diskparams"   [t| DiskParams      |]
612
  , simpleField "networks"     [t| Networks        |]
613
  ]
614
  ++ timeStampFields
615
  ++ uuidFields
616
  ++ serialFields
617
  ++ tagsFields)
618

    
619
instance TimeStampObject NodeGroup where
620
  cTimeOf = groupCtime
621
  mTimeOf = groupMtime
622

    
623
instance UuidObject NodeGroup where
624
  uuidOf = groupUuid
625

    
626
instance SerialNoObject NodeGroup where
627
  serialOf = groupSerial
628

    
629
instance TagsObject NodeGroup where
630
  tagsOf = groupTags
631

    
632
-- | IP family type
633
$(declareIADT "IpFamily"
634
  [ ("IpFamilyV4", 'AutoConf.pyAfInet4)
635
  , ("IpFamilyV6", 'AutoConf.pyAfInet6)
636
  ])
637
$(makeJSONInstance ''IpFamily)
638

    
639
-- | Conversion from IP family to IP version. This is needed because
640
-- Python uses both, depending on context.
641
ipFamilyToVersion :: IpFamily -> Int
642
ipFamilyToVersion IpFamilyV4 = C.ip4Version
643
ipFamilyToVersion IpFamilyV6 = C.ip6Version
644

    
645
-- | Cluster HvParams (hvtype to hvparams mapping).
646
type ClusterHvParams = Container HvParams
647

    
648
-- | Cluster Os-HvParams (os to hvparams mapping).
649
type OsHvParams = Container ClusterHvParams
650

    
651
-- | Cluser BeParams.
652
type ClusterBeParams = Container FilledBeParams
653

    
654
-- | Cluster OsParams.
655
type ClusterOsParams = Container OsParams
656
type ClusterOsParamsPrivate = Container (Private OsParams)
657

    
658
-- | Cluster NicParams.
659
type ClusterNicParams = Container FilledNicParams
660

    
661
-- | Cluster UID Pool, list (low, high) UID ranges.
662
type UidPool = [(Int, Int)]
663

    
664
-- | The iallocator parameters type.
665
type IAllocatorParams = Container JSValue
666

    
667
-- | The master candidate client certificate digests
668
type CandidateCertificates = Container String
669

    
670
-- * Cluster definitions
671
$(buildObject "Cluster" "cluster" $
672
  [ simpleField "rsahostkeypub"             [t| String                 |]
673
  , optionalField $
674
    simpleField "dsahostkeypub"             [t| String                 |]
675
  , simpleField "highest_used_port"         [t| Int                    |]
676
  , simpleField "tcpudp_port_pool"          [t| [Int]                  |]
677
  , simpleField "mac_prefix"                [t| String                 |]
678
  , optionalField $
679
    simpleField "volume_group_name"         [t| String                 |]
680
  , simpleField "reserved_lvs"              [t| [String]               |]
681
  , optionalField $
682
    simpleField "drbd_usermode_helper"      [t| String                 |]
683
  , simpleField "master_node"               [t| String                 |]
684
  , simpleField "master_ip"                 [t| String                 |]
685
  , simpleField "master_netdev"             [t| String                 |]
686
  , simpleField "master_netmask"            [t| Int                    |]
687
  , simpleField "use_external_mip_script"   [t| Bool                   |]
688
  , simpleField "cluster_name"              [t| String                 |]
689
  , simpleField "file_storage_dir"          [t| String                 |]
690
  , simpleField "shared_file_storage_dir"   [t| String                 |]
691
  , simpleField "gluster_storage_dir"       [t| String                 |]
692
  , simpleField "enabled_hypervisors"       [t| [Hypervisor]           |]
693
  , simpleField "hvparams"                  [t| ClusterHvParams        |]
694
  , simpleField "os_hvp"                    [t| OsHvParams             |]
695
  , simpleField "beparams"                  [t| ClusterBeParams        |]
696
  , simpleField "osparams"                  [t| ClusterOsParams        |]
697
  , simpleField "osparams_private_cluster"  [t| ClusterOsParamsPrivate |]
698
  , simpleField "nicparams"                 [t| ClusterNicParams       |]
699
  , simpleField "ndparams"                  [t| FilledNDParams         |]
700
  , simpleField "diskparams"                [t| DiskParams             |]
701
  , simpleField "candidate_pool_size"       [t| Int                    |]
702
  , simpleField "modify_etc_hosts"          [t| Bool                   |]
703
  , simpleField "modify_ssh_setup"          [t| Bool                   |]
704
  , simpleField "maintain_node_health"      [t| Bool                   |]
705
  , simpleField "uid_pool"                  [t| UidPool                |]
706
  , simpleField "default_iallocator"        [t| String                 |]
707
  , simpleField "default_iallocator_params" [t| IAllocatorParams       |]
708
  , simpleField "hidden_os"                 [t| [String]               |]
709
  , simpleField "blacklisted_os"            [t| [String]               |]
710
  , simpleField "primary_ip_family"         [t| IpFamily               |]
711
  , simpleField "prealloc_wipe_disks"       [t| Bool                   |]
712
  , simpleField "ipolicy"                   [t| FilledIPolicy          |]
713
  , simpleField "enabled_disk_templates"    [t| [DiskTemplate]         |]
714
  , simpleField "candidate_certs"           [t| CandidateCertificates  |]
715
  , simpleField "max_running_jobs"          [t| Int                    |]
716
 ]
717
 ++ timeStampFields
718
 ++ uuidFields
719
 ++ serialFields
720
 ++ tagsFields)
721

    
722
instance TimeStampObject Cluster where
723
  cTimeOf = clusterCtime
724
  mTimeOf = clusterMtime
725

    
726
instance UuidObject Cluster where
727
  uuidOf = clusterUuid
728

    
729
instance SerialNoObject Cluster where
730
  serialOf = clusterSerial
731

    
732
instance TagsObject Cluster where
733
  tagsOf = clusterTags
734

    
735
-- * ConfigData definitions
736

    
737
$(buildObject "ConfigData" "config" $
738
--  timeStampFields ++
739
  [ simpleField "version"    [t| Int                 |]
740
  , simpleField "cluster"    [t| Cluster             |]
741
  , simpleField "nodes"      [t| Container Node      |]
742
  , simpleField "nodegroups" [t| Container NodeGroup |]
743
  , simpleField "instances"  [t| Container Instance  |]
744
  , simpleField "networks"   [t| Container Network   |]
745
  ]
746
  ++ serialFields)
747

    
748
instance SerialNoObject ConfigData where
749
  serialOf = configSerial