Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 3bcf2140

History | View | Annotate | Download (25.2 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
  , getDiskSizeRequirements
51
  , PartialNDParams(..)
52
  , FilledNDParams(..)
53
  , fillNDParams
54
  , allNDParamFields
55
  , Node(..)
56
  , AllocPolicy(..)
57
  , FilledISpecParams(..)
58
  , PartialISpecParams(..)
59
  , fillISpecParams
60
  , allISpecParamFields
61
  , MinMaxISpecs(..)
62
  , FilledIPolicy(..)
63
  , PartialIPolicy(..)
64
  , fillIPolicy
65
  , DiskParams
66
  , NodeGroup(..)
67
  , IpFamily(..)
68
  , ipFamilyToVersion
69
  , fillDict
70
  , ClusterHvParams
71
  , OsHvParams
72
  , ClusterBeParams
73
  , ClusterOsParams
74
  , ClusterNicParams
75
  , Cluster(..)
76
  , ConfigData(..)
77
  , TimeStampObject(..)
78
  , UuidObject(..)
79
  , SerialNoObject(..)
80
  , TagsObject(..)
81
  , DictObject(..) -- re-exported from THH
82
  , TagSet -- re-exported from THH
83
  , Network(..)
84
  , Ip4Address(..)
85
  , Ip4Network(..)
86
  , readIp4Address
87
  , nextIp4Address
88
  , IAllocatorParams
89
  ) where
90

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

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

    
108
-- * Generic definitions
109

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

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

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

    
126
-- | Class of objects that have timestamps.
127
class TimeStampObject a where
128
  cTimeOf :: a -> Double
129
  mTimeOf :: a -> Double
130

    
131
-- | Class of objects that have an UUID.
132
class UuidObject a where
133
  uuidOf :: a -> String
134

    
135
-- | Class of object that have a serial number.
136
class SerialNoObject a where
137
  serialOf :: a -> Int
138

    
139
-- | Class of objects that have tags.
140
class TagsObject a where
141
  tagsOf :: a -> Set.Set String
142

    
143
-- * Network definitions
144

    
145
-- ** Ipv4 types
146

    
147
-- | Custom type for a simple IPv4 address.
148
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
149
                  deriving Eq
150

    
151
instance Show Ip4Address where
152
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
153
                              show c ++ "." ++ show d
154

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

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

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

    
185
-- | Custom type for an IPv4 network.
186
data Ip4Network = Ip4Network Ip4Address Word8
187
                  deriving Eq
188

    
189
instance Show Ip4Network where
190
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
191

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

    
207
-- ** Ganeti \"network\" config object.
208

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

    
232
instance SerialNoObject Network where
233
  serialOf = networkSerial
234

    
235
instance TagsObject Network where
236
  tagsOf = networkTags
237

    
238
instance UuidObject Network where
239
  uuidOf = networkUuid
240

    
241
instance TimeStampObject Network where
242
  cTimeOf = networkCtime
243
  mTimeOf = networkMtime
244

    
245
-- * NIC definitions
246

    
247
$(buildParam "Nic" "nicp"
248
  [ simpleField "mode" [t| NICMode |]
249
  , simpleField "link" [t| String  |]
250
  , simpleField "vlan" [t| String |]
251
  ])
252

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

    
261
instance UuidObject PartialNic where
262
  uuidOf = nicUuid
263

    
264
-- * Disk definitions
265

    
266
-- | Constant for the dev_type key entry in the disk config.
267
devType :: String
268
devType = "dev_type"
269

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

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

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

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

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

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

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

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

    
414
instance UuidObject Disk where
415
  uuidOf = diskUuid
416

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

    
428
-- * Instance definitions
429

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

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

    
461
instance TimeStampObject Instance where
462
  cTimeOf = instCtime
463
  mTimeOf = instMtime
464

    
465
instance UuidObject Instance where
466
  uuidOf = instUuid
467

    
468
instance SerialNoObject Instance where
469
  serialOf = instSerial
470

    
471
instance TagsObject Instance where
472
  tagsOf = instTags
473

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

    
487
-- * IPolicy definitions
488

    
489
$(buildParam "ISpec" "ispec"
490
  [ simpleField ConstantUtils.ispecMemSize     [t| Int |]
491
  , simpleField ConstantUtils.ispecDiskSize    [t| Int |]
492
  , simpleField ConstantUtils.ispecDiskCount   [t| Int |]
493
  , simpleField ConstantUtils.ispecCpuCount    [t| Int |]
494
  , simpleField ConstantUtils.ispecNicCount    [t| Int |]
495
  , simpleField ConstantUtils.ispecSpindleUse  [t| Int |]
496
  ])
497

    
498
$(buildObject "MinMaxISpecs" "mmis"
499
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
500
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
501
  ])
502

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

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

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

    
552
$(buildParam "ND" "ndp"
553
  [ simpleField "oob_program"   [t| String |]
554
  , simpleField "spindle_count" [t| Int    |]
555
  , simpleField "exclusive_storage" [t| Bool |]
556
  , simpleField "ovs"           [t| Bool |]
557
  , simpleField "ovs_name"       [t| String |]
558
  , simpleField "ovs_link"       [t| String |]
559
  , simpleField "ssh_port"      [t| Int |]
560
  ])
561

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

    
580
instance TimeStampObject Node where
581
  cTimeOf = nodeCtime
582
  mTimeOf = nodeMtime
583

    
584
instance UuidObject Node where
585
  uuidOf = nodeUuid
586

    
587
instance SerialNoObject Node where
588
  serialOf = nodeSerial
589

    
590
instance TagsObject Node where
591
  tagsOf = nodeTags
592

    
593
-- * NodeGroup definitions
594

    
595
-- | The disk parameters type.
596
type DiskParams = Container (Container JSValue)
597

    
598
-- | A mapping from network UUIDs to nic params of the networks.
599
type Networks = Container PartialNicParams
600

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

    
615
instance TimeStampObject NodeGroup where
616
  cTimeOf = groupCtime
617
  mTimeOf = groupMtime
618

    
619
instance UuidObject NodeGroup where
620
  uuidOf = groupUuid
621

    
622
instance SerialNoObject NodeGroup where
623
  serialOf = groupSerial
624

    
625
instance TagsObject NodeGroup where
626
  tagsOf = groupTags
627

    
628
-- | IP family type
629
$(declareIADT "IpFamily"
630
  [ ("IpFamilyV4", 'AutoConf.pyAfInet4)
631
  , ("IpFamilyV6", 'AutoConf.pyAfInet6)
632
  ])
633
$(makeJSONInstance ''IpFamily)
634

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

    
641
-- | Cluster HvParams (hvtype to hvparams mapping).
642
type ClusterHvParams = Container HvParams
643

    
644
-- | Cluster Os-HvParams (os to hvparams mapping).
645
type OsHvParams = Container ClusterHvParams
646

    
647
-- | Cluser BeParams.
648
type ClusterBeParams = Container FilledBeParams
649

    
650
-- | Cluster OsParams.
651
type ClusterOsParams = Container OsParams
652

    
653
-- | Cluster NicParams.
654
type ClusterNicParams = Container FilledNicParams
655

    
656
-- | Cluster UID Pool, list (low, high) UID ranges.
657
type UidPool = [(Int, Int)]
658

    
659
-- | The iallocator parameters type.
660
type IAllocatorParams = Container JSValue
661

    
662
-- | The master candidate client certificate digests
663
type CandidateCertificates = Container String
664

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

    
715
instance TimeStampObject Cluster where
716
  cTimeOf = clusterCtime
717
  mTimeOf = clusterMtime
718

    
719
instance UuidObject Cluster where
720
  uuidOf = clusterUuid
721

    
722
instance SerialNoObject Cluster where
723
  serialOf = clusterSerial
724

    
725
instance TagsObject Cluster where
726
  tagsOf = clusterTags
727

    
728
-- * ConfigData definitions
729

    
730
$(buildObject "ConfigData" "config" $
731
--  timeStampFields ++
732
  [ simpleField "version"    [t| Int                 |]
733
  , simpleField "cluster"    [t| Cluster             |]
734
  , simpleField "nodes"      [t| Container Node      |]
735
  , simpleField "nodegroups" [t| Container NodeGroup |]
736
  , simpleField "instances"  [t| Container Instance  |]
737
  , simpleField "networks"   [t| Container Network   |]
738
  ]
739
  ++ serialFields)
740

    
741
instance SerialNoObject ConfigData where
742
  serialOf = configSerial