Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ cd3b4ff4

History | View | Annotate | Download (25 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
  , DiskLogicalId(..)
45
  , Disk(..)
46
  , includesLogicalId
47
  , DiskTemplate(..)
48
  , PartialBeParams(..)
49
  , FilledBeParams(..)
50
  , fillBeParams
51
  , allBeParamFields
52
  , AdminState(..)
53
  , adminStateFromRaw
54
  , Instance(..)
55
  , toDictInstance
56
  , PartialNDParams(..)
57
  , FilledNDParams(..)
58
  , fillNDParams
59
  , allNDParamFields
60
  , Node(..)
61
  , NodeRole(..)
62
  , nodeRoleToRaw
63
  , roleDescription
64
  , AllocPolicy(..)
65
  , FilledISpecParams(..)
66
  , PartialISpecParams(..)
67
  , fillISpecParams
68
  , allISpecParamFields
69
  , MinMaxISpecs(..)
70
  , FilledIPolicy(..)
71
  , PartialIPolicy(..)
72
  , fillIPolicy
73
  , DiskParams
74
  , NodeGroup(..)
75
  , IpFamily(..)
76
  , ipFamilyToVersion
77
  , fillDict
78
  , ClusterHvParams
79
  , OsHvParams
80
  , ClusterBeParams
81
  , ClusterOsParams
82
  , ClusterNicParams
83
  , Cluster(..)
84
  , ConfigData(..)
85
  , TimeStampObject(..)
86
  , UuidObject(..)
87
  , SerialNoObject(..)
88
  , TagsObject(..)
89
  , DictObject(..) -- re-exported from THH
90
  , TagSet -- re-exported from THH
91
  , Network(..)
92
  , Ip4Address(..)
93
  , Ip4Network(..)
94
  , readIp4Address
95
  , nextIp4Address
96
  ) where
97

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

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

    
113
-- * Generic definitions
114

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

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

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

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

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

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

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

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

    
158
-- * Node role object
159

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

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

    
177
-- * Network definitions
178

    
179
-- ** Ipv4 types
180

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

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

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

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

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

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

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

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

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

    
243
-- FIXME: Not all types might be correct here, since they
244
-- haven't been exhaustively deduced from the python code yet.
245
$(buildObject "Network" "network" $
246
  [ simpleField "name"             [t| NonEmptyString |]
247
  , optionalField $
248
    simpleField "mac_prefix"       [t| String |]
249
  , simpleField "network"          [t| Ip4Network |]
250
  , optionalField $
251
    simpleField "network6"         [t| String |]
252
  , optionalField $
253
    simpleField "gateway"          [t| Ip4Address |]
254
  , optionalField $
255
    simpleField "gateway6"         [t| String |]
256
  , optionalField $
257
    simpleField "reservations"     [t| String |]
258
  , optionalField $
259
    simpleField "ext_reservations" [t| String |]
260
  ]
261
  ++ uuidFields
262
  ++ timeStampFields
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
instance TimeStampObject Network where
276
  cTimeOf = networkCtime
277
  mTimeOf = networkMtime
278

    
279
-- * NIC definitions
280

    
281
$(buildParam "Nic" "nicp"
282
  [ simpleField "mode" [t| NICMode |]
283
  , simpleField "link" [t| String  |]
284
  ])
285

    
286
$(buildObject "PartialNic" "nic" $
287
  [ simpleField "mac" [t| String |]
288
  , optionalField $ simpleField "ip" [t| String |]
289
  , simpleField "nicparams" [t| PartialNicParams |]
290
  , optionalField $ simpleField "network" [t| String |]
291
  , optionalField $ simpleField "name" [t| String |]
292
  ] ++ uuidFields)
293

    
294
instance UuidObject PartialNic where
295
  uuidOf = nicUuid
296

    
297
-- * Disk definitions
298

    
299
$(declareSADT "DiskMode"
300
  [ ("DiskRdOnly", 'C.diskRdonly)
301
  , ("DiskRdWr",   'C.diskRdwr)
302
  ])
303
$(makeJSONInstance ''DiskMode)
304

    
305
-- | The persistent block driver type. Currently only one type is allowed.
306
$(declareSADT "BlockDriver"
307
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
308
  ])
309
$(makeJSONInstance ''BlockDriver)
310

    
311
-- | Constant for the dev_type key entry in the disk config.
312
devType :: String
313
devType = "dev_type"
314

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

    
330
-- | Mapping from a logical id to a disk type.
331
lidDiskType :: DiskLogicalId -> DiskTemplate
332
lidDiskType (LIDPlain {}) = DTPlain
333
lidDiskType (LIDDrbd8 {}) = DTDrbd8
334
lidDiskType (LIDFile  {}) = DTFile
335
lidDiskType (LIDSharedFile  {}) = DTSharedFile
336
lidDiskType (LIDBlockDev {}) = DTBlock
337
lidDiskType (LIDRados {}) = DTRbd
338
lidDiskType (LIDExt {}) = DTExt
339

    
340
-- | Builds the extra disk_type field for a given logical id.
341
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
342
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
343

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

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

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

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

    
441
$(buildObjectSerialisation "Disk" $
442
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
443
      simpleField "logical_id"    [t| DiskLogicalId   |]
444
--  , simpleField "physical_id" [t| String   |]
445
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
446
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
447
  , simpleField "size" [t| Int |]
448
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
449
  , optionalField $ simpleField "name" [t| String |]
450
  , optionalField $ simpleField "spindles" [t| Int |]
451
  ]
452
  ++ uuidFields)
453

    
454
instance UuidObject Disk where
455
  uuidOf = diskUuid
456

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

    
468

    
469
-- * Instance definitions
470

    
471
$(declareSADT "AdminState"
472
  [ ("AdminOffline", 'C.adminstOffline)
473
  , ("AdminDown",    'C.adminstDown)
474
  , ("AdminUp",      'C.adminstUp)
475
  ])
476
$(makeJSONInstance ''AdminState)
477

    
478
$(buildParam "Be" "bep"
479
  [ simpleField "minmem"       [t| Int  |]
480
  , simpleField "maxmem"       [t| Int  |]
481
  , simpleField "vcpus"        [t| Int  |]
482
  , simpleField "auto_balance" [t| Bool |]
483
  ])
484

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

    
505
instance TimeStampObject Instance where
506
  cTimeOf = instCtime
507
  mTimeOf = instMtime
508

    
509
instance UuidObject Instance where
510
  uuidOf = instUuid
511

    
512
instance SerialNoObject Instance where
513
  serialOf = instSerial
514

    
515
instance TagsObject Instance where
516
  tagsOf = instTags
517

    
518
-- * IPolicy definitions
519

    
520
$(buildParam "ISpec" "ispec"
521
  [ simpleField C.ispecMemSize     [t| Int |]
522
  , simpleField C.ispecDiskSize    [t| Int |]
523
  , simpleField C.ispecDiskCount   [t| Int |]
524
  , simpleField C.ispecCpuCount    [t| Int |]
525
  , simpleField C.ispecNicCount    [t| Int |]
526
  , simpleField C.ispecSpindleUse  [t| Int |]
527
  ])
528

    
529
$(buildObject "MinMaxISpecs" "mmis"
530
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
531
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
532
  ])
533

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

    
549
-- | Custom filled ipolicy. This is not built via buildParam since it
550
-- has a special 2-level inheritance mode.
551
$(buildObject "FilledIPolicy" "ipolicy"
552
  [ renameField "MinMaxISpecs"
553
    $ simpleField C.ispecsMinmax [t| [MinMaxISpecs] |]
554
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
555
  , simpleField "spindle-ratio"  [t| Double |]
556
  , simpleField "vcpu-ratio"     [t| Double |]
557
  , simpleField "disk-templates" [t| [DiskTemplate] |]
558
  ])
559

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

    
583
$(buildParam "ND" "ndp"
584
  [ simpleField "oob_program"   [t| String |]
585
  , simpleField "spindle_count" [t| Int    |]
586
  , simpleField "exclusive_storage" [t| Bool |]
587
  ])
588

    
589
$(buildObject "Node" "node" $
590
  [ simpleField "name"             [t| String |]
591
  , simpleField "primary_ip"       [t| String |]
592
  , simpleField "secondary_ip"     [t| String |]
593
  , simpleField "master_candidate" [t| Bool   |]
594
  , simpleField "offline"          [t| Bool   |]
595
  , simpleField "drained"          [t| Bool   |]
596
  , simpleField "group"            [t| String |]
597
  , simpleField "master_capable"   [t| Bool   |]
598
  , simpleField "vm_capable"       [t| Bool   |]
599
  , simpleField "ndparams"         [t| PartialNDParams |]
600
  , simpleField "powered"          [t| Bool   |]
601
  ]
602
  ++ timeStampFields
603
  ++ uuidFields
604
  ++ serialFields
605
  ++ tagsFields)
606

    
607
instance TimeStampObject Node where
608
  cTimeOf = nodeCtime
609
  mTimeOf = nodeMtime
610

    
611
instance UuidObject Node where
612
  uuidOf = nodeUuid
613

    
614
instance SerialNoObject Node where
615
  serialOf = nodeSerial
616

    
617
instance TagsObject Node where
618
  tagsOf = nodeTags
619

    
620
-- * NodeGroup definitions
621

    
622
-- | The disk parameters type.
623
type DiskParams = Container (Container JSValue)
624

    
625
-- | A mapping from network UUIDs to nic params of the networks.
626
type Networks = Container PartialNicParams
627

    
628
$(buildObject "NodeGroup" "group" $
629
  [ simpleField "name"         [t| String |]
630
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
631
  , simpleField "ndparams"     [t| PartialNDParams |]
632
  , simpleField "alloc_policy" [t| AllocPolicy     |]
633
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
634
  , simpleField "diskparams"   [t| DiskParams      |]
635
  , simpleField "networks"     [t| Networks        |]
636
  ]
637
  ++ timeStampFields
638
  ++ uuidFields
639
  ++ serialFields
640
  ++ tagsFields)
641

    
642
instance TimeStampObject NodeGroup where
643
  cTimeOf = groupCtime
644
  mTimeOf = groupMtime
645

    
646
instance UuidObject NodeGroup where
647
  uuidOf = groupUuid
648

    
649
instance SerialNoObject NodeGroup where
650
  serialOf = groupSerial
651

    
652
instance TagsObject NodeGroup where
653
  tagsOf = groupTags
654

    
655
-- | IP family type
656
$(declareIADT "IpFamily"
657
  [ ("IpFamilyV4", 'C.ip4Family)
658
  , ("IpFamilyV6", 'C.ip6Family)
659
  ])
660
$(makeJSONInstance ''IpFamily)
661

    
662
-- | Conversion from IP family to IP version. This is needed because
663
-- Python uses both, depending on context.
664
ipFamilyToVersion :: IpFamily -> Int
665
ipFamilyToVersion IpFamilyV4 = C.ip4Version
666
ipFamilyToVersion IpFamilyV6 = C.ip6Version
667

    
668
-- | Cluster HvParams (hvtype to hvparams mapping).
669
type ClusterHvParams = Container HvParams
670

    
671
-- | Cluster Os-HvParams (os to hvparams mapping).
672
type OsHvParams = Container ClusterHvParams
673

    
674
-- | Cluser BeParams.
675
type ClusterBeParams = Container FilledBeParams
676

    
677
-- | Cluster OsParams.
678
type ClusterOsParams = Container OsParams
679

    
680
-- | Cluster NicParams.
681
type ClusterNicParams = Container FilledNicParams
682

    
683
-- | Cluster UID Pool, list (low, high) UID ranges.
684
type UidPool = [(Int, Int)]
685

    
686
-- * Cluster definitions
687
$(buildObject "Cluster" "cluster" $
688
  [ simpleField "rsahostkeypub"           [t| String           |]
689
  , simpleField "dsahostkeypub"           [t| String           |]
690
  , simpleField "highest_used_port"       [t| Int              |]
691
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
692
  , simpleField "mac_prefix"              [t| String           |]
693
  , optionalField $
694
    simpleField "volume_group_name"       [t| String           |]
695
  , simpleField "reserved_lvs"            [t| [String]         |]
696
  , optionalField $
697
    simpleField "drbd_usermode_helper"    [t| String           |]
698
  , simpleField "master_node"             [t| String           |]
699
  , simpleField "master_ip"               [t| String           |]
700
  , simpleField "master_netdev"           [t| String           |]
701
  , simpleField "master_netmask"          [t| Int              |]
702
  , simpleField "use_external_mip_script" [t| Bool             |]
703
  , simpleField "cluster_name"            [t| String           |]
704
  , simpleField "file_storage_dir"        [t| String           |]
705
  , simpleField "shared_file_storage_dir" [t| String           |]
706
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
707
  , simpleField "hvparams"                [t| ClusterHvParams  |]
708
  , simpleField "os_hvp"                  [t| OsHvParams       |]
709
  , simpleField "beparams"                [t| ClusterBeParams  |]
710
  , simpleField "osparams"                [t| ClusterOsParams  |]
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 "hidden_os"               [t| [String]         |]
721
  , simpleField "blacklisted_os"          [t| [String]         |]
722
  , simpleField "primary_ip_family"       [t| IpFamily         |]
723
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
724
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
725
  , simpleField "enabled_disk_templates"  [t| [DiskTemplate]   |]
726
 ]
727
 ++ timeStampFields
728
 ++ uuidFields
729
 ++ serialFields
730
 ++ tagsFields)
731

    
732
instance TimeStampObject Cluster where
733
  cTimeOf = clusterCtime
734
  mTimeOf = clusterMtime
735

    
736
instance UuidObject Cluster where
737
  uuidOf = clusterUuid
738

    
739
instance SerialNoObject Cluster where
740
  serialOf = clusterSerial
741

    
742
instance TagsObject Cluster where
743
  tagsOf = clusterTags
744

    
745
-- * ConfigData definitions
746

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

    
758
instance SerialNoObject ConfigData where
759
  serialOf = configSerial