Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (24.9 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
  , 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
  , FilledMinMaxISpecs(..)
70
  , PartialMinMaxISpecs(..)
71
  , fillMinMaxISpecs
72
  , FilledIPolicy(..)
73
  , PartialIPolicy(..)
74
  , fillIPolicy
75
  , DiskParams
76
  , NodeGroup(..)
77
  , IpFamily(..)
78
  , ipFamilyToVersion
79
  , fillDict
80
  , ClusterHvParams
81
  , OsHvParams
82
  , ClusterBeParams
83
  , ClusterOsParams
84
  , ClusterNicParams
85
  , Cluster(..)
86
  , ConfigData(..)
87
  , TimeStampObject(..)
88
  , UuidObject(..)
89
  , SerialNoObject(..)
90
  , TagsObject(..)
91
  , DictObject(..) -- re-exported from THH
92
  , TagSet -- re-exported from THH
93
  , Network(..)
94
  , Ip4Address(..)
95
  , Ip4Network(..)
96
  , readIp4Address
97
  , nextIp4Address
98
  ) where
99

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

    
109
import qualified Ganeti.Constants as C
110
import Ganeti.JSON
111
import Ganeti.Types
112
import Ganeti.THH
113
import Ganeti.Utils (sepSplit, tryRead)
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 VTYPES, a mini-type system in Python.
125
$(declareSADT "VType"
126
  [ ("VTypeString",      'C.vtypeString)
127
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
128
  , ("VTypeBool",        'C.vtypeBool)
129
  , ("VTypeSize",        'C.vtypeSize)
130
  , ("VTypeInt",         'C.vtypeInt)
131
  ])
132
$(makeJSONInstance ''VType)
133

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

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

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

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

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

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

    
160
-- * Node role object
161

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

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

    
179
-- * Network definitions
180

    
181
-- ** Ipv4 types
182

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

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

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

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

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

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

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

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

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

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

    
267
instance SerialNoObject Network where
268
  serialOf = networkSerial
269

    
270
instance TagsObject Network where
271
  tagsOf = networkTags
272

    
273
instance UuidObject Network where
274
  uuidOf = networkUuid
275

    
276
-- * NIC definitions
277

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

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

    
291
instance UuidObject PartialNic where
292
  uuidOf = nicUuid
293

    
294
-- * Disk definitions
295

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

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

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

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

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

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

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

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

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

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

    
419
-- | Disk data structure.
420
--
421
-- This is declared manually as it's a recursive structure, and our TH
422
-- code currently can't build it.
423
data Disk = Disk
424
  { diskLogicalId  :: DiskLogicalId
425
--  , diskPhysicalId :: String
426
  , diskChildren   :: [Disk]
427
  , diskIvName     :: String
428
  , diskSize       :: Int
429
  , diskMode       :: DiskMode
430
  , diskName       :: Maybe String
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
  ]
444
  ++ uuidFields)
445

    
446
instance UuidObject Disk where
447
  uuidOf = diskUuid
448

    
449
-- * Instance definitions
450

    
451
$(declareSADT "AdminState"
452
  [ ("AdminOffline", 'C.adminstOffline)
453
  , ("AdminDown",    'C.adminstDown)
454
  , ("AdminUp",      'C.adminstUp)
455
  ])
456
$(makeJSONInstance ''AdminState)
457

    
458
$(buildParam "Be" "bep"
459
  [ simpleField "minmem"       [t| Int  |]
460
  , simpleField "maxmem"       [t| Int  |]
461
  , simpleField "vcpus"        [t| Int  |]
462
  , simpleField "auto_balance" [t| Bool |]
463
  ])
464

    
465
$(buildObject "Instance" "inst" $
466
  [ simpleField "name"           [t| String             |]
467
  , simpleField "primary_node"   [t| String             |]
468
  , simpleField "os"             [t| String             |]
469
  , simpleField "hypervisor"     [t| Hypervisor         |]
470
  , simpleField "hvparams"       [t| HvParams           |]
471
  , simpleField "beparams"       [t| PartialBeParams    |]
472
  , simpleField "osparams"       [t| OsParams           |]
473
  , simpleField "admin_state"    [t| AdminState         |]
474
  , simpleField "nics"           [t| [PartialNic]       |]
475
  , simpleField "disks"          [t| [Disk]             |]
476
  , simpleField "disk_template"  [t| DiskTemplate       |]
477
  , optionalField $ simpleField "network_port" [t| Int  |]
478
  ]
479
  ++ timeStampFields
480
  ++ uuidFields
481
  ++ serialFields
482
  ++ tagsFields)
483

    
484
instance TimeStampObject Instance where
485
  cTimeOf = instCtime
486
  mTimeOf = instMtime
487

    
488
instance UuidObject Instance where
489
  uuidOf = instUuid
490

    
491
instance SerialNoObject Instance where
492
  serialOf = instSerial
493

    
494
instance TagsObject Instance where
495
  tagsOf = instTags
496

    
497
-- * IPolicy definitions
498

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

    
508
-- | Partial min-max instance specs. These is not built via buildParam since
509
-- it has a special 2-level inheritance mode.
510
$(buildObject "PartialMinMaxISpecs" "mmis"
511
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
512
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
513
  ])
514

    
515
-- | Filled min-max instance specs. This is not built via buildParam since
516
-- it has a special 2-level inheritance mode.
517
$(buildObject "FilledMinMaxISpecs" "mmis"
518
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
519
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
520
  ])
521

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

    
536
-- | Custom filled ipolicy. This is not built via buildParam since it
537
-- has a special 2-level inheritance mode.
538
$(buildObject "FilledIPolicy" "ipolicy"
539
  [ renameField "MinMaxISpecs"
540
    $ simpleField C.ispecsMinmax [t| FilledMinMaxISpecs |]
541
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
542
  , simpleField "spindle-ratio"  [t| Double |]
543
  , simpleField "vcpu-ratio"     [t| Double |]
544
  , simpleField "disk-templates" [t| [DiskTemplate] |]
545
  ])
546

    
547
-- | Custom filler for the min-max instance specs.
548
fillMinMaxISpecs :: FilledMinMaxISpecs -> Maybe PartialMinMaxISpecs ->
549
                    FilledMinMaxISpecs
550
fillMinMaxISpecs fminmax Nothing = fminmax
551
fillMinMaxISpecs (FilledMinMaxISpecs { mmisMinSpec = fmin
552
                                     , mmisMaxSpec = fmax })
553
                 (Just PartialMinMaxISpecs { mmisMinSpecP = pmin
554
                                           , mmisMaxSpecP = pmax }) =
555
  FilledMinMaxISpecs { mmisMinSpec = fillISpecParams fmin pmin
556
                     , mmisMaxSpec = fillISpecParams fmax pmax }
557

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

    
579
$(buildParam "ND" "ndp"
580
  [ simpleField "oob_program"   [t| String |]
581
  , simpleField "spindle_count" [t| Int    |]
582
  , simpleField "exclusive_storage" [t| Bool |]
583
  ])
584

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

    
603
instance TimeStampObject Node where
604
  cTimeOf = nodeCtime
605
  mTimeOf = nodeMtime
606

    
607
instance UuidObject Node where
608
  uuidOf = nodeUuid
609

    
610
instance SerialNoObject Node where
611
  serialOf = nodeSerial
612

    
613
instance TagsObject Node where
614
  tagsOf = nodeTags
615

    
616
-- * NodeGroup definitions
617

    
618
-- | The disk parameters type.
619
type DiskParams = Container (Container JSValue)
620

    
621
-- | A mapping from network UUIDs to nic params of the networks.
622
type Networks = Container PartialNicParams
623

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

    
638
instance TimeStampObject NodeGroup where
639
  cTimeOf = groupCtime
640
  mTimeOf = groupMtime
641

    
642
instance UuidObject NodeGroup where
643
  uuidOf = groupUuid
644

    
645
instance SerialNoObject NodeGroup where
646
  serialOf = groupSerial
647

    
648
instance TagsObject NodeGroup where
649
  tagsOf = groupTags
650

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

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

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

    
667
-- | Cluster Os-HvParams (os to hvparams mapping).
668
type OsHvParams = Container ClusterHvParams
669

    
670
-- | Cluser BeParams.
671
type ClusterBeParams = Container FilledBeParams
672

    
673
-- | Cluster OsParams.
674
type ClusterOsParams = Container OsParams
675

    
676
-- | Cluster NicParams.
677
type ClusterNicParams = Container FilledNicParams
678

    
679
-- | Cluster UID Pool, list (low, high) UID ranges.
680
type UidPool = [(Int, Int)]
681

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

    
727
instance TimeStampObject Cluster where
728
  cTimeOf = clusterCtime
729
  mTimeOf = clusterMtime
730

    
731
instance UuidObject Cluster where
732
  uuidOf = clusterUuid
733

    
734
instance SerialNoObject Cluster where
735
  serialOf = clusterSerial
736

    
737
instance TagsObject Cluster where
738
  tagsOf = clusterTags
739

    
740
-- * ConfigData definitions
741

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

    
753
instance SerialNoObject ConfigData where
754
  serialOf = configSerial