Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (26.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, 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
  , 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
  , ipFamilyToRaw
69
  , ipFamilyToVersion
70
  , fillDict
71
  , ClusterHvParams
72
  , OsHvParams
73
  , ClusterBeParams
74
  , ClusterOsParams
75
  , ClusterOsParamsPrivate
76
  , ClusterNicParams
77
  , UidPool
78
  , formatUidRange
79
  , UidRange
80
  , Cluster(..)
81
  , ConfigData(..)
82
  , TimeStampObject(..)
83
  , UuidObject(..)
84
  , SerialNoObject(..)
85
  , TagsObject(..)
86
  , DictObject(..) -- re-exported from THH
87
  , TagSet -- re-exported from THH
88
  , Network(..)
89
  , Ip4Address(..)
90
  , Ip4Network(..)
91
  , readIp4Address
92
  , nextIp4Address
93
  , IAllocatorParams
94
  ) where
95

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

    
106
import qualified AutoConf
107
import qualified Ganeti.Constants as C
108
import qualified Ganeti.ConstantUtils as ConstantUtils
109
import Ganeti.JSON
110
import Ganeti.Types
111
import Ganeti.THH
112
import Ganeti.THH.Field
113
import Ganeti.Utils (sepSplit, tryRead, parseUnitAssumeBinary)
114

    
115
-- * Generic definitions
116

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

    
124
-- | The hypervisor parameter type. This is currently a simple map,
125
-- without type checking on key/value pairs.
126
type HvParams = Container JSValue
127

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

    
134
-- | Class of objects that have timestamps.
135
class TimeStampObject a where
136
  cTimeOf :: a -> ClockTime
137
  mTimeOf :: a -> ClockTime
138

    
139
-- | Class of objects that have an UUID.
140
class UuidObject a where
141
  uuidOf :: a -> String
142

    
143
-- | Class of object that have a serial number.
144
class SerialNoObject a where
145
  serialOf :: a -> Int
146

    
147
-- | Class of objects that have tags.
148
class TagsObject a where
149
  tagsOf :: a -> Set.Set String
150

    
151
-- * Network definitions
152

    
153
-- ** Ipv4 types
154

    
155
-- | Custom type for a simple IPv4 address.
156
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
157
                  deriving Eq
158

    
159
instance Show Ip4Address where
160
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
161
                              show c ++ "." ++ show d
162

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

    
174
-- | JSON instance for 'Ip4Address'.
175
instance JSON Ip4Address where
176
  showJSON = showJSON . show
177
  readJSON (JSString s) = readIp4Address (fromJSString s)
178
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 address"
179

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

    
193
-- | Custom type for an IPv4 network.
194
data Ip4Network = Ip4Network Ip4Address Word8
195
                  deriving Eq
196

    
197
instance Show Ip4Network where
198
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
199

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

    
215
-- ** Ganeti \"network\" config object.
216

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

    
240
instance SerialNoObject Network where
241
  serialOf = networkSerial
242

    
243
instance TagsObject Network where
244
  tagsOf = networkTags
245

    
246
instance UuidObject Network where
247
  uuidOf = networkUuid
248

    
249
instance TimeStampObject Network where
250
  cTimeOf = networkCtime
251
  mTimeOf = networkMtime
252

    
253
-- * NIC definitions
254

    
255
$(buildParam "Nic" "nicp"
256
  [ simpleField "mode" [t| NICMode |]
257
  , simpleField "link" [t| String  |]
258
  , simpleField "vlan" [t| String |]
259
  ])
260

    
261
$(buildObject "PartialNic" "nic" $
262
  [ simpleField "mac" [t| String |]
263
  , optionalField $ simpleField "ip" [t| String |]
264
  , simpleField "nicparams" [t| PartialNicParams |]
265
  , optionalField $ simpleField "network" [t| String |]
266
  , optionalField $ simpleField "name" [t| String |]
267
  ] ++ uuidFields)
268

    
269
instance UuidObject PartialNic where
270
  uuidOf = nicUuid
271

    
272
-- * Disk definitions
273

    
274
-- | Constant for the dev_type key entry in the disk config.
275
devType :: String
276
devType = "dev_type"
277

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

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

    
303
-- | Builds the extra disk_type field for a given logical id.
304
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
305
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
306

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

    
321
-- | Custom encoder for DiskLogicalId, composing both the logical id
322
-- and the extra disk_type field.
323
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
324
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
325

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

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

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

    
422
instance UuidObject Disk where
423
  uuidOf = diskUuid
424

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

    
436
-- * Instance definitions
437

    
438
$(buildParam "Be" "bep"
439
  [ specialNumericalField 'parseUnitAssumeBinary
440
      $ simpleField "minmem"      [t| Int  |]
441
  , specialNumericalField 'parseUnitAssumeBinary
442
      $ simpleField "maxmem"      [t| Int  |]
443
  , simpleField "vcpus"           [t| Int  |]
444
  , simpleField "auto_balance"    [t| Bool |]
445
  , simpleField "always_failover" [t| Bool |]
446
  , simpleField "spindle_use"     [t| Int  |]
447
  ])
448

    
449
$(buildObject "Instance" "inst" $
450
  [ simpleField "name"             [t| String             |]
451
  , simpleField "primary_node"     [t| String             |]
452
  , simpleField "os"               [t| String             |]
453
  , simpleField "hypervisor"       [t| Hypervisor         |]
454
  , simpleField "hvparams"         [t| HvParams           |]
455
  , simpleField "beparams"         [t| PartialBeParams    |]
456
  , simpleField "osparams"         [t| OsParams           |]
457
  , simpleField "osparams_private" [t| OsParamsPrivate    |]
458
  , simpleField "admin_state"      [t| AdminState         |]
459
  , simpleField "nics"             [t| [PartialNic]       |]
460
  , simpleField "disks"            [t| [Disk]             |]
461
  , simpleField "disk_template"    [t| DiskTemplate       |]
462
  , simpleField "disks_active"     [t| Bool               |]
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
-- | Retrieves the real disk size requirements for all the disks of the
484
-- instance. This includes the metadata etc. and is different from the values
485
-- visible to the instance.
486
getDiskSizeRequirements :: Instance -> Int
487
getDiskSizeRequirements inst =
488
  sum . map
489
    (\disk -> case instDiskTemplate inst of
490
                DTDrbd8    -> diskSize disk + C.drbdMetaSize
491
                DTDiskless -> 0
492
                DTBlock    -> 0
493
                _          -> diskSize disk )
494
    $ instDisks inst
495

    
496
-- * IPolicy definitions
497

    
498
$(buildParam "ISpec" "ispec"
499
  [ simpleField ConstantUtils.ispecMemSize     [t| Int |]
500
  , simpleField ConstantUtils.ispecDiskSize    [t| Int |]
501
  , simpleField ConstantUtils.ispecDiskCount   [t| Int |]
502
  , simpleField ConstantUtils.ispecCpuCount    [t| Int |]
503
  , simpleField ConstantUtils.ispecNicCount    [t| Int |]
504
  , simpleField ConstantUtils.ispecSpindleUse  [t| Int |]
505
  ])
506

    
507
$(buildObject "MinMaxISpecs" "mmis"
508
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
509
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
510
  ])
511

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

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

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

    
561
$(buildParam "ND" "ndp"
562
  [ simpleField "oob_program"   [t| String |]
563
  , simpleField "spindle_count" [t| Int    |]
564
  , simpleField "exclusive_storage" [t| Bool |]
565
  , simpleField "ovs"           [t| Bool |]
566
  , simpleField "ovs_name"       [t| String |]
567
  , simpleField "ovs_link"       [t| String |]
568
  , simpleField "ssh_port"      [t| Int |]
569
  ])
570

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

    
589
instance TimeStampObject Node where
590
  cTimeOf = nodeCtime
591
  mTimeOf = nodeMtime
592

    
593
instance UuidObject Node where
594
  uuidOf = nodeUuid
595

    
596
instance SerialNoObject Node where
597
  serialOf = nodeSerial
598

    
599
instance TagsObject Node where
600
  tagsOf = nodeTags
601

    
602
-- * NodeGroup definitions
603

    
604
-- | The disk parameters type.
605
type DiskParams = Container (Container JSValue)
606

    
607
-- | A mapping from network UUIDs to nic params of the networks.
608
type Networks = Container PartialNicParams
609

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

    
624
instance TimeStampObject NodeGroup where
625
  cTimeOf = groupCtime
626
  mTimeOf = groupMtime
627

    
628
instance UuidObject NodeGroup where
629
  uuidOf = groupUuid
630

    
631
instance SerialNoObject NodeGroup where
632
  serialOf = groupSerial
633

    
634
instance TagsObject NodeGroup where
635
  tagsOf = groupTags
636

    
637
-- | IP family type
638
$(declareIADT "IpFamily"
639
  [ ("IpFamilyV4", 'AutoConf.pyAfInet4)
640
  , ("IpFamilyV6", 'AutoConf.pyAfInet6)
641
  ])
642
$(makeJSONInstance ''IpFamily)
643

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

    
650
-- | Cluster HvParams (hvtype to hvparams mapping).
651
type ClusterHvParams = Container HvParams
652

    
653
-- | Cluster Os-HvParams (os to hvparams mapping).
654
type OsHvParams = Container ClusterHvParams
655

    
656
-- | Cluser BeParams.
657
type ClusterBeParams = Container FilledBeParams
658

    
659
-- | Cluster OsParams.
660
type ClusterOsParams = Container OsParams
661
type ClusterOsParamsPrivate = Container (Private OsParams)
662

    
663
-- | Cluster NicParams.
664
type ClusterNicParams = Container FilledNicParams
665

    
666
-- | A low-high UID ranges.
667
type UidRange = (Int, Int)
668

    
669
formatUidRange :: UidRange -> String
670
formatUidRange (lower, higher)
671
  | lower == higher = show lower
672
  | otherwise       = show lower ++ "-" ++ show higher
673

    
674
-- | Cluster UID Pool, list (low, high) UID ranges.
675
type UidPool = [UidRange]
676

    
677
-- | The iallocator parameters type.
678
type IAllocatorParams = Container JSValue
679

    
680
-- | The master candidate client certificate digests
681
type CandidateCertificates = Container String
682

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

    
736
instance TimeStampObject Cluster where
737
  cTimeOf = clusterCtime
738
  mTimeOf = clusterMtime
739

    
740
instance UuidObject Cluster where
741
  uuidOf = clusterUuid
742

    
743
instance SerialNoObject Cluster where
744
  serialOf = clusterSerial
745

    
746
instance TagsObject Cluster where
747
  tagsOf = clusterTags
748

    
749
-- * ConfigData definitions
750

    
751
$(buildObject "ConfigData" "config" $
752
--  timeStampFields ++
753
  [ simpleField "version"    [t| Int                 |]
754
  , simpleField "cluster"    [t| Cluster             |]
755
  , simpleField "nodes"      [t| Container Node      |]
756
  , simpleField "nodegroups" [t| Container NodeGroup |]
757
  , simpleField "instances"  [t| Container Instance  |]
758
  , simpleField "networks"   [t| Container Network   |]
759
  ]
760
  ++ timeStampFields
761
  ++ serialFields)
762

    
763
instance SerialNoObject ConfigData where
764
  serialOf = configSerial
765

    
766
instance TimeStampObject ConfigData where
767
  cTimeOf = configCtime
768
  mTimeOf = configMtime