Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 76968973

History | View | Annotate | Download (24.6 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti config objects.
4

    
5
Some object fields are not implemented yet, and as such they are
6
commented out below.
7

    
8
-}
9

    
10
{-
11

    
12
Copyright (C) 2011, 2012, 2013 Google Inc.
13

    
14
This program is free software; you can redistribute it and/or modify
15
it under the terms of the GNU General Public License as published by
16
the Free Software Foundation; either version 2 of the License, or
17
(at your option) any later version.
18

    
19
This program is distributed in the hope that it will be useful, but
20
WITHOUT ANY WARRANTY; without even the implied warranty of
21
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22
General Public License for more details.
23

    
24
You should have received a copy of the GNU General Public License
25
along with this program; if not, write to the Free Software
26
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
27
02110-1301, USA.
28

    
29
-}
30

    
31
module Ganeti.Objects
32
  ( VType(..)
33
  , vTypeFromRaw
34
  , HvParams
35
  , OsParams
36
  , PartialNicParams(..)
37
  , FilledNicParams(..)
38
  , fillNicParams
39
  , allNicParamFields
40
  , PartialNic(..)
41
  , FileDriver(..)
42
  , BlockDriver(..)
43
  , DiskMode(..)
44
  , DiskType(..)
45
  , DiskLogicalId(..)
46
  , Disk(..)
47
  , includesLogicalId
48
  , DiskTemplate(..)
49
  , PartialBeParams(..)
50
  , FilledBeParams(..)
51
  , fillBeParams
52
  , allBeParamFields
53
  , AdminState(..)
54
  , adminStateFromRaw
55
  , Instance(..)
56
  , toDictInstance
57
  , PartialNDParams(..)
58
  , FilledNDParams(..)
59
  , fillNDParams
60
  , allNDParamFields
61
  , Node(..)
62
  , NodeRole(..)
63
  , nodeRoleToRaw
64
  , roleDescription
65
  , AllocPolicy(..)
66
  , FilledISpecParams(..)
67
  , PartialISpecParams(..)
68
  , fillISpecParams
69
  , allISpecParamFields
70
  , MinMaxISpecs(..)
71
  , FilledIPolicy(..)
72
  , PartialIPolicy(..)
73
  , fillIPolicy
74
  , DiskParams
75
  , NodeGroup(..)
76
  , IpFamily(..)
77
  , ipFamilyToVersion
78
  , fillDict
79
  , ClusterHvParams
80
  , OsHvParams
81
  , ClusterBeParams
82
  , ClusterOsParams
83
  , ClusterNicParams
84
  , Cluster(..)
85
  , ConfigData(..)
86
  , TimeStampObject(..)
87
  , UuidObject(..)
88
  , SerialNoObject(..)
89
  , TagsObject(..)
90
  , DictObject(..) -- re-exported from THH
91
  , TagSet -- re-exported from THH
92
  , Network(..)
93
  , Ip4Address(..)
94
  , Ip4Network(..)
95
  , readIp4Address
96
  , nextIp4Address
97
  ) where
98

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

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

    
114
-- * Generic definitions
115

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

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

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

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

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

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

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

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

    
159
-- * Node role object
160

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

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

    
178
-- * Network definitions
179

    
180
-- ** Ipv4 types
181

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

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

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

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

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

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

    
224
instance Show Ip4Network where
225
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
226

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

    
242
-- ** Ganeti \"network\" config object.
243

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

    
266
instance SerialNoObject Network where
267
  serialOf = networkSerial
268

    
269
instance TagsObject Network where
270
  tagsOf = networkTags
271

    
272
instance UuidObject Network where
273
  uuidOf = networkUuid
274

    
275
-- * NIC definitions
276

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

    
282
$(buildObject "PartialNic" "nic" $
283
  [ simpleField "mac" [t| String |]
284
  , optionalField $ simpleField "ip" [t| String |]
285
  , simpleField "nicparams" [t| PartialNicParams |]
286
  , optionalField $ simpleField "network" [t| String |]
287
  , optionalField $ simpleField "name" [t| String |]
288
  ] ++ uuidFields)
289

    
290
instance UuidObject PartialNic where
291
  uuidOf = nicUuid
292

    
293
-- * Disk definitions
294

    
295
$(declareSADT "DiskMode"
296
  [ ("DiskRdOnly", 'C.diskRdonly)
297
  , ("DiskRdWr",   'C.diskRdwr)
298
  ])
299
$(makeJSONInstance ''DiskMode)
300

    
301
$(declareSADT "DiskType"
302
  [ ("LD_LV",       'C.ldLv)
303
  , ("LD_DRBD8",    'C.ldDrbd8)
304
  , ("LD_FILE",     'C.ldFile)
305
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
306
  , ("LD_RADOS",    'C.ldRbd)
307
  , ("LD_EXT",      'C.ldExt)
308
  ])
309
$(makeJSONInstance ''DiskType)
310

    
311
-- | The persistent block driver type. Currently only one type is allowed.
312
$(declareSADT "BlockDriver"
313
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
314
  ])
315
$(makeJSONInstance ''BlockDriver)
316

    
317
-- | Constant for the dev_type key entry in the disk config.
318
devType :: String
319
devType = "dev_type"
320

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

    
335
-- | Mapping from a logical id to a disk type.
336
lidDiskType :: DiskLogicalId -> DiskType
337
lidDiskType (LIDPlain {}) = LD_LV
338
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
339
lidDiskType (LIDFile  {}) = LD_FILE
340
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
341
lidDiskType (LIDRados {}) = LD_RADOS
342
lidDiskType (LIDExt {}) = LD_EXT
343

    
344
-- | Builds the extra disk_type field for a given logical id.
345
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
346
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
347

    
348
-- | Custom encoder for DiskLogicalId (logical id only).
349
encodeDLId :: DiskLogicalId -> JSValue
350
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
351
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
352
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
353
          , showJSON minorA, showJSON minorB, showJSON key ]
354
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
355
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
356
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
357
encodeDLId (LIDExt extprovider name) =
358
  JSArray [showJSON extprovider, showJSON name]
359

    
360
-- | Custom encoder for DiskLogicalId, composing both the logical id
361
-- and the extra disk_type field.
362
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
363
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
364

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

    
418
-- | Disk data structure.
419
--
420
-- This is declared manually as it's a recursive structure, and our TH
421
-- code currently can't build it.
422
data Disk = Disk
423
  { diskLogicalId  :: DiskLogicalId
424
--  , diskPhysicalId :: String
425
  , diskChildren   :: [Disk]
426
  , diskIvName     :: String
427
  , diskSize       :: Int
428
  , diskMode       :: DiskMode
429
  , diskName       :: Maybe String
430
  , diskSpindles   :: Maybe Int
431
  , diskUuid       :: String
432
  } deriving (Show, Eq)
433

    
434
$(buildObjectSerialisation "Disk" $
435
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
436
      simpleField "logical_id"    [t| DiskLogicalId   |]
437
--  , simpleField "physical_id" [t| String   |]
438
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
439
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
440
  , simpleField "size" [t| Int |]
441
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
442
  , optionalField $ simpleField "name" [t| String |]
443
  , optionalField $ simpleField "spindles" [t| Int |]
444
  ]
445
  ++ uuidFields)
446

    
447
instance UuidObject Disk where
448
  uuidOf = diskUuid
449

    
450
-- | Determines whether a disk or one of his children has the given logical id
451
-- (determined by the volume group name and by the logical volume name).
452
-- This can be true only for DRBD or LVM disks.
453
includesLogicalId :: String -> String -> Disk -> Bool
454
includesLogicalId vg_name lv_name disk =
455
  case diskLogicalId disk of
456
    LIDPlain vg lv -> vg_name == vg && lv_name == lv
457
    LIDDrbd8 {} ->
458
      any (includesLogicalId vg_name lv_name) $ diskChildren disk
459
    _ -> False
460

    
461

    
462
-- * Instance definitions
463

    
464
$(declareSADT "AdminState"
465
  [ ("AdminOffline", 'C.adminstOffline)
466
  , ("AdminDown",    'C.adminstDown)
467
  , ("AdminUp",      'C.adminstUp)
468
  ])
469
$(makeJSONInstance ''AdminState)
470

    
471
$(buildParam "Be" "bep"
472
  [ simpleField "minmem"       [t| Int  |]
473
  , simpleField "maxmem"       [t| Int  |]
474
  , simpleField "vcpus"        [t| Int  |]
475
  , simpleField "auto_balance" [t| Bool |]
476
  ])
477

    
478
$(buildObject "Instance" "inst" $
479
  [ simpleField "name"           [t| String             |]
480
  , simpleField "primary_node"   [t| String             |]
481
  , simpleField "os"             [t| String             |]
482
  , simpleField "hypervisor"     [t| Hypervisor         |]
483
  , simpleField "hvparams"       [t| HvParams           |]
484
  , simpleField "beparams"       [t| PartialBeParams    |]
485
  , simpleField "osparams"       [t| OsParams           |]
486
  , simpleField "admin_state"    [t| AdminState         |]
487
  , simpleField "nics"           [t| [PartialNic]       |]
488
  , simpleField "disks"          [t| [Disk]             |]
489
  , simpleField "disk_template"  [t| DiskTemplate       |]
490
  , simpleField "disks_active"   [t| Bool               |]
491
  , optionalField $ simpleField "network_port" [t| Int  |]
492
  ]
493
  ++ timeStampFields
494
  ++ uuidFields
495
  ++ serialFields
496
  ++ tagsFields)
497

    
498
instance TimeStampObject Instance where
499
  cTimeOf = instCtime
500
  mTimeOf = instMtime
501

    
502
instance UuidObject Instance where
503
  uuidOf = instUuid
504

    
505
instance SerialNoObject Instance where
506
  serialOf = instSerial
507

    
508
instance TagsObject Instance where
509
  tagsOf = instTags
510

    
511
-- * IPolicy definitions
512

    
513
$(buildParam "ISpec" "ispec"
514
  [ simpleField C.ispecMemSize     [t| Int |]
515
  , simpleField C.ispecDiskSize    [t| Int |]
516
  , simpleField C.ispecDiskCount   [t| Int |]
517
  , simpleField C.ispecCpuCount    [t| Int |]
518
  , simpleField C.ispecNicCount    [t| Int |]
519
  , simpleField C.ispecSpindleUse  [t| Int |]
520
  ])
521

    
522
$(buildObject "MinMaxISpecs" "mmis"
523
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
524
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
525
  ])
526

    
527
-- | Custom partial ipolicy. This is not built via buildParam since it
528
-- has a special 2-level inheritance mode.
529
$(buildObject "PartialIPolicy" "ipolicy"
530
  [ optionalField . renameField "MinMaxISpecsP"
531
                    $ simpleField C.ispecsMinmax   [t| [MinMaxISpecs] |]
532
  , optionalField . renameField "StdSpecP"
533
                    $ simpleField "std"            [t| PartialISpecParams |]
534
  , optionalField . renameField "SpindleRatioP"
535
                    $ simpleField "spindle-ratio"  [t| Double |]
536
  , optionalField . renameField "VcpuRatioP"
537
                    $ simpleField "vcpu-ratio"     [t| Double |]
538
  , optionalField . renameField "DiskTemplatesP"
539
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
540
  ])
541

    
542
-- | Custom filled ipolicy. This is not built via buildParam since it
543
-- has a special 2-level inheritance mode.
544
$(buildObject "FilledIPolicy" "ipolicy"
545
  [ renameField "MinMaxISpecs"
546
    $ simpleField C.ispecsMinmax [t| [MinMaxISpecs] |]
547
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
548
  , simpleField "spindle-ratio"  [t| Double |]
549
  , simpleField "vcpu-ratio"     [t| Double |]
550
  , simpleField "disk-templates" [t| [DiskTemplate] |]
551
  ])
552

    
553
-- | Custom filler for the ipolicy types.
554
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
555
fillIPolicy (FilledIPolicy { ipolicyMinMaxISpecs  = fminmax
556
                           , ipolicyStdSpec       = fstd
557
                           , ipolicySpindleRatio  = fspindleRatio
558
                           , ipolicyVcpuRatio     = fvcpuRatio
559
                           , ipolicyDiskTemplates = fdiskTemplates})
560
            (PartialIPolicy { ipolicyMinMaxISpecsP  = pminmax
561
                            , ipolicyStdSpecP       = pstd
562
                            , ipolicySpindleRatioP  = pspindleRatio
563
                            , ipolicyVcpuRatioP     = pvcpuRatio
564
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
565
  FilledIPolicy { ipolicyMinMaxISpecs  = fromMaybe fminmax pminmax
566
                , ipolicyStdSpec       = case pstd of
567
                                         Nothing -> fstd
568
                                         Just p -> fillISpecParams fstd p
569
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
570
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
571
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
572
                                         pdiskTemplates
573
                }
574
-- * Node definitions
575

    
576
$(buildParam "ND" "ndp"
577
  [ simpleField "oob_program"   [t| String |]
578
  , simpleField "spindle_count" [t| Int    |]
579
  , simpleField "exclusive_storage" [t| Bool |]
580
  ])
581

    
582
$(buildObject "Node" "node" $
583
  [ simpleField "name"             [t| String |]
584
  , simpleField "primary_ip"       [t| String |]
585
  , simpleField "secondary_ip"     [t| String |]
586
  , simpleField "master_candidate" [t| Bool   |]
587
  , simpleField "offline"          [t| Bool   |]
588
  , simpleField "drained"          [t| Bool   |]
589
  , simpleField "group"            [t| String |]
590
  , simpleField "master_capable"   [t| Bool   |]
591
  , simpleField "vm_capable"       [t| Bool   |]
592
  , simpleField "ndparams"         [t| PartialNDParams |]
593
  , simpleField "powered"          [t| Bool   |]
594
  ]
595
  ++ timeStampFields
596
  ++ uuidFields
597
  ++ serialFields
598
  ++ tagsFields)
599

    
600
instance TimeStampObject Node where
601
  cTimeOf = nodeCtime
602
  mTimeOf = nodeMtime
603

    
604
instance UuidObject Node where
605
  uuidOf = nodeUuid
606

    
607
instance SerialNoObject Node where
608
  serialOf = nodeSerial
609

    
610
instance TagsObject Node where
611
  tagsOf = nodeTags
612

    
613
-- * NodeGroup definitions
614

    
615
-- | The disk parameters type.
616
type DiskParams = Container (Container JSValue)
617

    
618
-- | A mapping from network UUIDs to nic params of the networks.
619
type Networks = Container PartialNicParams
620

    
621
$(buildObject "NodeGroup" "group" $
622
  [ simpleField "name"         [t| String |]
623
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
624
  , simpleField "ndparams"     [t| PartialNDParams |]
625
  , simpleField "alloc_policy" [t| AllocPolicy     |]
626
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
627
  , simpleField "diskparams"   [t| DiskParams      |]
628
  , simpleField "networks"     [t| Networks        |]
629
  ]
630
  ++ timeStampFields
631
  ++ uuidFields
632
  ++ serialFields
633
  ++ tagsFields)
634

    
635
instance TimeStampObject NodeGroup where
636
  cTimeOf = groupCtime
637
  mTimeOf = groupMtime
638

    
639
instance UuidObject NodeGroup where
640
  uuidOf = groupUuid
641

    
642
instance SerialNoObject NodeGroup where
643
  serialOf = groupSerial
644

    
645
instance TagsObject NodeGroup where
646
  tagsOf = groupTags
647

    
648
-- | IP family type
649
$(declareIADT "IpFamily"
650
  [ ("IpFamilyV4", 'C.ip4Family)
651
  , ("IpFamilyV6", 'C.ip6Family)
652
  ])
653
$(makeJSONInstance ''IpFamily)
654

    
655
-- | Conversion from IP family to IP version. This is needed because
656
-- Python uses both, depending on context.
657
ipFamilyToVersion :: IpFamily -> Int
658
ipFamilyToVersion IpFamilyV4 = C.ip4Version
659
ipFamilyToVersion IpFamilyV6 = C.ip6Version
660

    
661
-- | Cluster HvParams (hvtype to hvparams mapping).
662
type ClusterHvParams = Container HvParams
663

    
664
-- | Cluster Os-HvParams (os to hvparams mapping).
665
type OsHvParams = Container ClusterHvParams
666

    
667
-- | Cluser BeParams.
668
type ClusterBeParams = Container FilledBeParams
669

    
670
-- | Cluster OsParams.
671
type ClusterOsParams = Container OsParams
672

    
673
-- | Cluster NicParams.
674
type ClusterNicParams = Container FilledNicParams
675

    
676
-- | Cluster UID Pool, list (low, high) UID ranges.
677
type UidPool = [(Int, Int)]
678

    
679
-- * Cluster definitions
680
$(buildObject "Cluster" "cluster" $
681
  [ simpleField "rsahostkeypub"           [t| String           |]
682
  , simpleField "highest_used_port"       [t| Int              |]
683
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
684
  , simpleField "mac_prefix"              [t| String           |]
685
  , optionalField $
686
    simpleField "volume_group_name"       [t| String           |]
687
  , simpleField "reserved_lvs"            [t| [String]         |]
688
  , optionalField $
689
    simpleField "drbd_usermode_helper"    [t| String           |]
690
  , simpleField "master_node"             [t| String           |]
691
  , simpleField "master_ip"               [t| String           |]
692
  , simpleField "master_netdev"           [t| String           |]
693
  , simpleField "master_netmask"          [t| Int              |]
694
  , simpleField "use_external_mip_script" [t| Bool             |]
695
  , simpleField "cluster_name"            [t| String           |]
696
  , simpleField "file_storage_dir"        [t| String           |]
697
  , simpleField "shared_file_storage_dir" [t| String           |]
698
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
699
  , simpleField "hvparams"                [t| ClusterHvParams  |]
700
  , simpleField "os_hvp"                  [t| OsHvParams       |]
701
  , simpleField "beparams"                [t| ClusterBeParams  |]
702
  , simpleField "osparams"                [t| ClusterOsParams  |]
703
  , simpleField "nicparams"               [t| ClusterNicParams |]
704
  , simpleField "ndparams"                [t| FilledNDParams   |]
705
  , simpleField "diskparams"              [t| DiskParams       |]
706
  , simpleField "candidate_pool_size"     [t| Int              |]
707
  , simpleField "modify_etc_hosts"        [t| Bool             |]
708
  , simpleField "modify_ssh_setup"        [t| Bool             |]
709
  , simpleField "maintain_node_health"    [t| Bool             |]
710
  , simpleField "uid_pool"                [t| UidPool          |]
711
  , simpleField "default_iallocator"      [t| String           |]
712
  , simpleField "hidden_os"               [t| [String]         |]
713
  , simpleField "blacklisted_os"          [t| [String]         |]
714
  , simpleField "primary_ip_family"       [t| IpFamily         |]
715
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
716
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
717
  , simpleField "enabled_disk_templates"  [t| [DiskTemplate]   |]
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