Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 8a5d326f

History | View | Annotate | Download (26.1 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, 2014 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
  , ClusterOsParamsPrivate
76
  , ClusterNicParams
77
  , Cluster(..)
78
  , ConfigData(..)
79
  , TimeStampObject(..)
80
  , UuidObject(..)
81
  , SerialNoObject(..)
82
  , TagsObject(..)
83
  , DictObject(..) -- re-exported from THH
84
  , TagSet -- re-exported from THH
85
  , Network(..)
86
  , Ip4Address(..)
87
  , Ip4Network(..)
88
  , readIp4Address
89
  , nextIp4Address
90
  , IAllocatorParams
91
  ) where
92

    
93
import Control.Applicative
94
import Data.List (foldl')
95
import Data.Maybe
96
import qualified Data.Map as Map
97
import qualified Data.Set as Set
98
import Data.Word
99
import System.Time (ClockTime(..))
100
import Text.JSON (showJSON, readJSON, JSON, JSValue(..), fromJSString)
101
import qualified Text.JSON as J
102

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

    
111
-- * Generic definitions
112

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

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

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

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

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

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

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

    
147
-- * Network definitions
148

    
149
-- ** Ipv4 types
150

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

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

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

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

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

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

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

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

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

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

    
236
instance SerialNoObject Network where
237
  serialOf = networkSerial
238

    
239
instance TagsObject Network where
240
  tagsOf = networkTags
241

    
242
instance UuidObject Network where
243
  uuidOf = networkUuid
244

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

    
249
-- * NIC definitions
250

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

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

    
265
instance UuidObject PartialNic where
266
  uuidOf = nicUuid
267

    
268
-- * Disk definitions
269

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

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

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

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

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

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

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

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

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

    
418
instance UuidObject Disk where
419
  uuidOf = diskUuid
420

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

    
432
-- * Instance definitions
433

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

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

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

    
470
instance UuidObject Instance where
471
  uuidOf = instUuid
472

    
473
instance SerialNoObject Instance where
474
  serialOf = instSerial
475

    
476
instance TagsObject Instance where
477
  tagsOf = instTags
478

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

    
492
-- * IPolicy definitions
493

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

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

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

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

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

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

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

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

    
589
instance UuidObject Node where
590
  uuidOf = nodeUuid
591

    
592
instance SerialNoObject Node where
593
  serialOf = nodeSerial
594

    
595
instance TagsObject Node where
596
  tagsOf = nodeTags
597

    
598
-- * NodeGroup definitions
599

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

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

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

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

    
624
instance UuidObject NodeGroup where
625
  uuidOf = groupUuid
626

    
627
instance SerialNoObject NodeGroup where
628
  serialOf = groupSerial
629

    
630
instance TagsObject NodeGroup where
631
  tagsOf = groupTags
632

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

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

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

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

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

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

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

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

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

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

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

    
724
instance TimeStampObject Cluster where
725
  cTimeOf = clusterCtime
726
  mTimeOf = clusterMtime
727

    
728
instance UuidObject Cluster where
729
  uuidOf = clusterUuid
730

    
731
instance SerialNoObject Cluster where
732
  serialOf = clusterSerial
733

    
734
instance TagsObject Cluster where
735
  tagsOf = clusterTags
736

    
737
-- * ConfigData definitions
738

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

    
750
instance SerialNoObject ConfigData where
751
  serialOf = configSerial