Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 8106dd64

History | View | Annotate | Download (27.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common Ganeti types.
4

    
5
This holds types common to both core work, and to htools. Types that
6
are very core specific (e.g. configuration objects) should go in
7
'Ganeti.Objects', while types that are specific to htools in-memory
8
representation should go into 'Ganeti.HTools.Types'.
9

    
10
-}
11

    
12
{-
13

    
14
Copyright (C) 2012, 2013 Google Inc.
15

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

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

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

    
31
-}
32

    
33
module Ganeti.Types
34
  ( AllocPolicy(..)
35
  , allocPolicyFromRaw
36
  , allocPolicyToRaw
37
  , InstanceStatus(..)
38
  , instanceStatusFromRaw
39
  , instanceStatusToRaw
40
  , DiskTemplate(..)
41
  , diskTemplateToRaw
42
  , diskTemplateFromRaw
43
  , TagKind(..)
44
  , tagKindToRaw
45
  , tagKindFromRaw
46
  , NonNegative
47
  , fromNonNegative
48
  , mkNonNegative
49
  , Positive
50
  , fromPositive
51
  , mkPositive
52
  , Negative
53
  , fromNegative
54
  , mkNegative
55
  , NonEmpty
56
  , fromNonEmpty
57
  , mkNonEmpty
58
  , NonEmptyString
59
  , QueryResultCode
60
  , IPv4Address
61
  , mkIPv4Address
62
  , IPv4Network
63
  , mkIPv4Network
64
  , IPv6Address
65
  , mkIPv6Address
66
  , IPv6Network
67
  , mkIPv6Network
68
  , MigrationMode(..)
69
  , migrationModeToRaw
70
  , VerifyOptionalChecks(..)
71
  , verifyOptionalChecksToRaw
72
  , DdmSimple(..)
73
  , DdmFull(..)
74
  , ddmFullToRaw
75
  , CVErrorCode(..)
76
  , cVErrorCodeToRaw
77
  , Hypervisor(..)
78
  , hypervisorToRaw
79
  , OobCommand(..)
80
  , oobCommandToRaw
81
  , OobStatus(..)
82
  , oobStatusToRaw
83
  , StorageType(..)
84
  , storageTypeToRaw
85
  , EvacMode(..)
86
  , evacModeToRaw
87
  , FileDriver(..)
88
  , fileDriverToRaw
89
  , InstCreateMode(..)
90
  , instCreateModeToRaw
91
  , RebootType(..)
92
  , rebootTypeToRaw
93
  , ExportMode(..)
94
  , exportModeToRaw
95
  , IAllocatorTestDir(..)
96
  , iAllocatorTestDirToRaw
97
  , IAllocatorMode(..)
98
  , iAllocatorModeToRaw
99
  , NICMode(..)
100
  , nICModeToRaw
101
  , JobStatus(..)
102
  , jobStatusToRaw
103
  , jobStatusFromRaw
104
  , FinalizedJobStatus(..)
105
  , finalizedJobStatusToRaw
106
  , JobId
107
  , fromJobId
108
  , makeJobId
109
  , makeJobIdS
110
  , RelativeJobId
111
  , JobIdDep(..)
112
  , JobDependency(..)
113
  , absoluteJobDependency
114
  , OpSubmitPriority(..)
115
  , opSubmitPriorityToRaw
116
  , parseSubmitPriority
117
  , fmtSubmitPriority
118
  , OpStatus(..)
119
  , opStatusToRaw
120
  , opStatusFromRaw
121
  , ELogType(..)
122
  , eLogTypeToRaw
123
  , ReasonElem
124
  , ReasonTrail
125
  , StorageUnit(..)
126
  , StorageUnitRaw(..)
127
  , StorageKey
128
  , addParamsToStorageUnit
129
  , diskTemplateToStorageType
130
  , VType(..)
131
  , vTypeFromRaw
132
  , vTypeToRaw
133
  , NodeRole(..)
134
  , nodeRoleToRaw
135
  , roleDescription
136
  , DiskMode(..)
137
  , diskModeToRaw
138
  , BlockDriver(..)
139
  , blockDriverToRaw
140
  , AdminState(..)
141
  , adminStateFromRaw
142
  , adminStateToRaw
143
  , StorageField(..)
144
  , storageFieldToRaw
145
  , DiskAccessMode(..)
146
  , diskAccessModeToRaw
147
  , LocalDiskStatus(..)
148
  , localDiskStatusFromRaw
149
  , localDiskStatusToRaw
150
  , localDiskStatusName
151
  , ReplaceDisksMode(..)
152
  , replaceDisksModeToRaw
153
  , RpcTimeout(..)
154
  , rpcTimeoutFromRaw -- FIXME: no used anywhere
155
  , rpcTimeoutToRaw
156
  , ImportExportCompression(..)
157
  , importExportCompressionToRaw
158
  , HotplugTarget(..)
159
  , hotplugTargetToRaw
160
  , HotplugAction(..)
161
  , hotplugActionToRaw
162
  ) where
163

    
164
import Control.Monad (liftM)
165
import qualified Text.JSON as JSON
166
import Text.JSON (JSON, readJSON, showJSON)
167
import Data.Ratio (numerator, denominator)
168

    
169
import qualified Ganeti.ConstantUtils as ConstantUtils
170
import Ganeti.JSON
171
import qualified Ganeti.THH as THH
172
import Ganeti.Utils
173

    
174
-- * Generic types
175

    
176
-- | Type that holds a non-negative value.
177
newtype NonNegative a = NonNegative { fromNonNegative :: a }
178
  deriving (Show, Eq)
179

    
180
-- | Smart constructor for 'NonNegative'.
181
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
182
mkNonNegative i | i >= 0 = return (NonNegative i)
183
                | otherwise = fail $ "Invalid value for non-negative type '" ++
184
                              show i ++ "'"
185

    
186
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
187
  showJSON = JSON.showJSON . fromNonNegative
188
  readJSON v = JSON.readJSON v >>= mkNonNegative
189

    
190
-- | Type that holds a positive value.
191
newtype Positive a = Positive { fromPositive :: a }
192
  deriving (Show, Eq)
193

    
194
-- | Smart constructor for 'Positive'.
195
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
196
mkPositive i | i > 0 = return (Positive i)
197
             | otherwise = fail $ "Invalid value for positive type '" ++
198
                           show i ++ "'"
199

    
200
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
201
  showJSON = JSON.showJSON . fromPositive
202
  readJSON v = JSON.readJSON v >>= mkPositive
203

    
204
-- | Type that holds a negative value.
205
newtype Negative a = Negative { fromNegative :: a }
206
  deriving (Show, Eq)
207

    
208
-- | Smart constructor for 'Negative'.
209
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
210
mkNegative i | i < 0 = return (Negative i)
211
             | otherwise = fail $ "Invalid value for negative type '" ++
212
                           show i ++ "'"
213

    
214
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
215
  showJSON = JSON.showJSON . fromNegative
216
  readJSON v = JSON.readJSON v >>= mkNegative
217

    
218
-- | Type that holds a non-null list.
219
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
220
  deriving (Show, Eq)
221

    
222
-- | Smart constructor for 'NonEmpty'.
223
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
224
mkNonEmpty [] = fail "Received empty value for non-empty list"
225
mkNonEmpty xs = return (NonEmpty xs)
226

    
227
instance (Eq a, Ord a) => Ord (NonEmpty a) where
228
  NonEmpty { fromNonEmpty = x1 } `compare` NonEmpty { fromNonEmpty = x2 } =
229
    x1 `compare` x2
230

    
231
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
232
  showJSON = JSON.showJSON . fromNonEmpty
233
  readJSON v = JSON.readJSON v >>= mkNonEmpty
234

    
235
-- | A simple type alias for non-empty strings.
236
type NonEmptyString = NonEmpty Char
237

    
238
type QueryResultCode = Int
239

    
240
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
241
  deriving (Show, Eq)
242

    
243
-- FIXME: this should check that 'address' is a valid ip
244
mkIPv4Address :: Monad m => String -> m IPv4Address
245
mkIPv4Address address =
246
  return IPv4Address { fromIPv4Address = address }
247

    
248
instance JSON.JSON IPv4Address where
249
  showJSON = JSON.showJSON . fromIPv4Address
250
  readJSON v = JSON.readJSON v >>= mkIPv4Address
251

    
252
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
253
  deriving (Show, Eq)
254

    
255
-- FIXME: this should check that 'address' is a valid ip
256
mkIPv4Network :: Monad m => String -> m IPv4Network
257
mkIPv4Network address =
258
  return IPv4Network { fromIPv4Network = address }
259

    
260
instance JSON.JSON IPv4Network where
261
  showJSON = JSON.showJSON . fromIPv4Network
262
  readJSON v = JSON.readJSON v >>= mkIPv4Network
263

    
264
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
265
  deriving (Show, Eq)
266

    
267
-- FIXME: this should check that 'address' is a valid ip
268
mkIPv6Address :: Monad m => String -> m IPv6Address
269
mkIPv6Address address =
270
  return IPv6Address { fromIPv6Address = address }
271

    
272
instance JSON.JSON IPv6Address where
273
  showJSON = JSON.showJSON . fromIPv6Address
274
  readJSON v = JSON.readJSON v >>= mkIPv6Address
275

    
276
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
277
  deriving (Show, Eq)
278

    
279
-- FIXME: this should check that 'address' is a valid ip
280
mkIPv6Network :: Monad m => String -> m IPv6Network
281
mkIPv6Network address =
282
  return IPv6Network { fromIPv6Network = address }
283

    
284
instance JSON.JSON IPv6Network where
285
  showJSON = JSON.showJSON . fromIPv6Network
286
  readJSON v = JSON.readJSON v >>= mkIPv6Network
287

    
288
-- * Ganeti types
289

    
290
-- | Instance disk template type.
291
$(THH.declareLADT ''String "DiskTemplate"
292
       [ ("DTDiskless",   "diskless")
293
       , ("DTFile",       "file")
294
       , ("DTSharedFile", "sharedfile")
295
       , ("DTPlain",      "plain")
296
       , ("DTBlock",      "blockdev")
297
       , ("DTDrbd8",      "drbd")
298
       , ("DTRbd",        "rbd")
299
       , ("DTExt",        "ext")
300
       , ("DTGluster",    "gluster")
301
       ])
302
$(THH.makeJSONInstance ''DiskTemplate)
303

    
304
instance THH.PyValue DiskTemplate where
305
  showValue = show . diskTemplateToRaw
306

    
307
instance HasStringRepr DiskTemplate where
308
  fromStringRepr = diskTemplateFromRaw
309
  toStringRepr = diskTemplateToRaw
310

    
311
-- | Data type representing what items the tag operations apply to.
312
$(THH.declareLADT ''String "TagKind"
313
  [ ("TagKindInstance", "instance")
314
  , ("TagKindNode",     "node")
315
  , ("TagKindGroup",    "nodegroup")
316
  , ("TagKindCluster",  "cluster")
317
  , ("TagKindNetwork",  "network")
318
  ])
319
$(THH.makeJSONInstance ''TagKind)
320

    
321
-- | The Group allocation policy type.
322
--
323
-- Note that the order of constructors is important as the automatic
324
-- Ord instance will order them in the order they are defined, so when
325
-- changing this data type be careful about the interaction with the
326
-- desired sorting order.
327
$(THH.declareLADT ''String "AllocPolicy"
328
       [ ("AllocPreferred",   "preferred")
329
       , ("AllocLastResort",  "last_resort")
330
       , ("AllocUnallocable", "unallocable")
331
       ])
332
$(THH.makeJSONInstance ''AllocPolicy)
333

    
334
-- | The Instance real state type.
335
$(THH.declareLADT ''String "InstanceStatus"
336
       [ ("StatusDown",    "ADMIN_down")
337
       , ("StatusOffline", "ADMIN_offline")
338
       , ("ErrorDown",     "ERROR_down")
339
       , ("ErrorUp",       "ERROR_up")
340
       , ("NodeDown",      "ERROR_nodedown")
341
       , ("NodeOffline",   "ERROR_nodeoffline")
342
       , ("Running",       "running")
343
       , ("UserDown",      "USER_down")
344
       , ("WrongNode",     "ERROR_wrongnode")
345
       ])
346
$(THH.makeJSONInstance ''InstanceStatus)
347

    
348
-- | Migration mode.
349
$(THH.declareLADT ''String "MigrationMode"
350
     [ ("MigrationLive",    "live")
351
     , ("MigrationNonLive", "non-live")
352
     ])
353
$(THH.makeJSONInstance ''MigrationMode)
354

    
355
-- | Verify optional checks.
356
$(THH.declareLADT ''String "VerifyOptionalChecks"
357
     [ ("VerifyNPlusOneMem", "nplusone_mem")
358
     ])
359
$(THH.makeJSONInstance ''VerifyOptionalChecks)
360

    
361
-- | Cluster verify error codes.
362
$(THH.declareLADT ''String "CVErrorCode"
363
  [ ("CvECLUSTERCFG",                  "ECLUSTERCFG")
364
  , ("CvECLUSTERCERT",                 "ECLUSTERCERT")
365
  , ("CvECLUSTERFILECHECK",            "ECLUSTERFILECHECK")
366
  , ("CvECLUSTERDANGLINGNODES",        "ECLUSTERDANGLINGNODES")
367
  , ("CvECLUSTERDANGLINGINST",         "ECLUSTERDANGLINGINST")
368
  , ("CvEINSTANCEBADNODE",             "EINSTANCEBADNODE")
369
  , ("CvEINSTANCEDOWN",                "EINSTANCEDOWN")
370
  , ("CvEINSTANCELAYOUT",              "EINSTANCELAYOUT")
371
  , ("CvEINSTANCEMISSINGDISK",         "EINSTANCEMISSINGDISK")
372
  , ("CvEINSTANCEFAULTYDISK",          "EINSTANCEFAULTYDISK")
373
  , ("CvEINSTANCEWRONGNODE",           "EINSTANCEWRONGNODE")
374
  , ("CvEINSTANCESPLITGROUPS",         "EINSTANCESPLITGROUPS")
375
  , ("CvEINSTANCEPOLICY",              "EINSTANCEPOLICY")
376
  , ("CvEINSTANCEUNSUITABLENODE",      "EINSTANCEUNSUITABLENODE")
377
  , ("CvEINSTANCEMISSINGCFGPARAMETER", "EINSTANCEMISSINGCFGPARAMETER")
378
  , ("CvENODEDRBD",                    "ENODEDRBD")
379
  , ("CvENODEDRBDVERSION",             "ENODEDRBDVERSION")
380
  , ("CvENODEDRBDHELPER",              "ENODEDRBDHELPER")
381
  , ("CvENODEFILECHECK",               "ENODEFILECHECK")
382
  , ("CvENODEHOOKS",                   "ENODEHOOKS")
383
  , ("CvENODEHV",                      "ENODEHV")
384
  , ("CvENODELVM",                     "ENODELVM")
385
  , ("CvENODEN1",                      "ENODEN1")
386
  , ("CvENODENET",                     "ENODENET")
387
  , ("CvENODEOS",                      "ENODEOS")
388
  , ("CvENODEORPHANINSTANCE",          "ENODEORPHANINSTANCE")
389
  , ("CvENODEORPHANLV",                "ENODEORPHANLV")
390
  , ("CvENODERPC",                     "ENODERPC")
391
  , ("CvENODESSH",                     "ENODESSH")
392
  , ("CvENODEVERSION",                 "ENODEVERSION")
393
  , ("CvENODESETUP",                   "ENODESETUP")
394
  , ("CvENODETIME",                    "ENODETIME")
395
  , ("CvENODEOOBPATH",                 "ENODEOOBPATH")
396
  , ("CvENODEUSERSCRIPTS",             "ENODEUSERSCRIPTS")
397
  , ("CvENODEFILESTORAGEPATHS",        "ENODEFILESTORAGEPATHS")
398
  , ("CvENODEFILESTORAGEPATHUNUSABLE", "ENODEFILESTORAGEPATHUNUSABLE")
399
  , ("CvENODESHAREDFILESTORAGEPATHUNUSABLE",
400
     "ENODESHAREDFILESTORAGEPATHUNUSABLE")
401
  , ("CvEGROUPDIFFERENTPVSIZE",        "EGROUPDIFFERENTPVSIZE")
402
  ])
403
$(THH.makeJSONInstance ''CVErrorCode)
404

    
405
-- | Dynamic device modification, just add\/remove version.
406
$(THH.declareLADT ''String "DdmSimple"
407
     [ ("DdmSimpleAdd",    "add")
408
     , ("DdmSimpleRemove", "remove")
409
     ])
410
$(THH.makeJSONInstance ''DdmSimple)
411

    
412
-- | Dynamic device modification, all operations version.
413
--
414
-- TODO: DDM_SWAP, DDM_MOVE?
415
$(THH.declareLADT ''String "DdmFull"
416
     [ ("DdmFullAdd",    "add")
417
     , ("DdmFullRemove", "remove")
418
     , ("DdmFullModify", "modify")
419
     ])
420
$(THH.makeJSONInstance ''DdmFull)
421

    
422
-- | Hypervisor type definitions.
423
$(THH.declareLADT ''String "Hypervisor"
424
  [ ("Kvm",    "kvm")
425
  , ("XenPvm", "xen-pvm")
426
  , ("Chroot", "chroot")
427
  , ("XenHvm", "xen-hvm")
428
  , ("Lxc",    "lxc")
429
  , ("Fake",   "fake")
430
  ])
431
$(THH.makeJSONInstance ''Hypervisor)
432

    
433
instance THH.PyValue Hypervisor where
434
  showValue = show . hypervisorToRaw
435

    
436
instance HasStringRepr Hypervisor where
437
  fromStringRepr = hypervisorFromRaw
438
  toStringRepr = hypervisorToRaw
439

    
440
-- | Oob command type.
441
$(THH.declareLADT ''String "OobCommand"
442
  [ ("OobHealth",      "health")
443
  , ("OobPowerCycle",  "power-cycle")
444
  , ("OobPowerOff",    "power-off")
445
  , ("OobPowerOn",     "power-on")
446
  , ("OobPowerStatus", "power-status")
447
  ])
448
$(THH.makeJSONInstance ''OobCommand)
449

    
450
-- | Oob command status
451
$(THH.declareLADT ''String "OobStatus"
452
  [ ("OobStatusCritical", "CRITICAL")
453
  , ("OobStatusOk",       "OK")
454
  , ("OobStatusUnknown",  "UNKNOWN")
455
  , ("OobStatusWarning",  "WARNING")
456
  ])
457
$(THH.makeJSONInstance ''OobStatus)
458

    
459
-- | Storage type.
460
$(THH.declareLADT ''String "StorageType"
461
  [ ("StorageFile", "file")
462
  , ("StorageLvmPv", "lvm-pv")
463
  , ("StorageLvmVg", "lvm-vg")
464
  , ("StorageDiskless", "diskless")
465
  , ("StorageBlock", "blockdev")
466
  , ("StorageRados", "rados")
467
  , ("StorageExt", "ext")
468
  ])
469
$(THH.makeJSONInstance ''StorageType)
470

    
471
-- | Storage keys are identifiers for storage units. Their content varies
472
-- depending on the storage type, for example a storage key for LVM storage
473
-- is the volume group name.
474
type StorageKey = String
475

    
476
-- | Storage parameters
477
type SPExclusiveStorage = Bool
478

    
479
-- | Storage units without storage-type-specific parameters
480
data StorageUnitRaw = SURaw StorageType StorageKey
481

    
482
-- | Full storage unit with storage-type-specific parameters
483
data StorageUnit = SUFile StorageKey
484
                 | SULvmPv StorageKey SPExclusiveStorage
485
                 | SULvmVg StorageKey SPExclusiveStorage
486
                 | SUDiskless StorageKey
487
                 | SUBlock StorageKey
488
                 | SURados StorageKey
489
                 | SUExt StorageKey
490
                 deriving (Eq)
491

    
492
instance Show StorageUnit where
493
  show (SUFile key) = showSUSimple StorageFile key
494
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
495
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
496
  show (SUDiskless key) = showSUSimple StorageDiskless key
497
  show (SUBlock key) = showSUSimple StorageBlock key
498
  show (SURados key) = showSUSimple StorageRados key
499
  show (SUExt key) = showSUSimple StorageExt key
500

    
501
instance JSON StorageUnit where
502
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
503
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
504
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
505
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
506
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
507
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
508
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
509
-- FIXME: add readJSON implementation
510
  readJSON = fail "Not implemented"
511

    
512
-- | Composes a string representation of storage types without
513
-- storage parameters
514
showSUSimple :: StorageType -> StorageKey -> String
515
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
516

    
517
-- | Composes a string representation of the LVM storage types
518
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
519
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
520

    
521
-- | Mapping from disk templates to storage types
522
-- FIXME: This is semantically the same as the constant
523
-- C.diskTemplatesStorageType, remove this when python constants
524
-- are generated from haskell constants
525
diskTemplateToStorageType :: DiskTemplate -> StorageType
526
diskTemplateToStorageType DTExt = StorageExt
527
diskTemplateToStorageType DTFile = StorageFile
528
diskTemplateToStorageType DTSharedFile = StorageFile
529
diskTemplateToStorageType DTDrbd8 = StorageLvmVg
530
diskTemplateToStorageType DTPlain = StorageLvmVg
531
diskTemplateToStorageType DTRbd = StorageRados
532
diskTemplateToStorageType DTDiskless = StorageDiskless
533
diskTemplateToStorageType DTBlock = StorageBlock
534
diskTemplateToStorageType DTGluster = StorageFile
535

    
536
-- | Equips a raw storage unit with its parameters
537
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
538
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
539
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
540
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
541
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
542
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
543
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
544
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
545

    
546
-- | Node evac modes.
547
--
548
-- This is part of the 'IAllocator' interface and it is used, for
549
-- example, in 'Ganeti.HTools.Loader.RqType'.  However, it must reside
550
-- in this module, and not in 'Ganeti.HTools.Types', because it is
551
-- also used by 'Ganeti.Constants'.
552
$(THH.declareLADT ''String "EvacMode"
553
  [ ("ChangePrimary",   "primary-only")
554
  , ("ChangeSecondary", "secondary-only")
555
  , ("ChangeAll",       "all")
556
  ])
557
$(THH.makeJSONInstance ''EvacMode)
558

    
559
-- | The file driver type.
560
$(THH.declareLADT ''String "FileDriver"
561
  [ ("FileLoop",   "loop")
562
  , ("FileBlktap", "blktap")
563
  ])
564
$(THH.makeJSONInstance ''FileDriver)
565

    
566
-- | The instance create mode.
567
$(THH.declareLADT ''String "InstCreateMode"
568
  [ ("InstCreate",       "create")
569
  , ("InstImport",       "import")
570
  , ("InstRemoteImport", "remote-import")
571
  ])
572
$(THH.makeJSONInstance ''InstCreateMode)
573

    
574
-- | Reboot type.
575
$(THH.declareLADT ''String "RebootType"
576
  [ ("RebootSoft", "soft")
577
  , ("RebootHard", "hard")
578
  , ("RebootFull", "full")
579
  ])
580
$(THH.makeJSONInstance ''RebootType)
581

    
582
-- | Export modes.
583
$(THH.declareLADT ''String "ExportMode"
584
  [ ("ExportModeLocal",  "local")
585
  , ("ExportModeRemote", "remote")
586
  ])
587
$(THH.makeJSONInstance ''ExportMode)
588

    
589
-- | IAllocator run types (OpTestIAllocator).
590
$(THH.declareLADT ''String "IAllocatorTestDir"
591
  [ ("IAllocatorDirIn",  "in")
592
  , ("IAllocatorDirOut", "out")
593
  ])
594
$(THH.makeJSONInstance ''IAllocatorTestDir)
595

    
596
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
597
$(THH.declareLADT ''String "IAllocatorMode"
598
  [ ("IAllocatorAlloc",       "allocate")
599
  , ("IAllocatorMultiAlloc",  "multi-allocate")
600
  , ("IAllocatorReloc",       "relocate")
601
  , ("IAllocatorNodeEvac",    "node-evacuate")
602
  , ("IAllocatorChangeGroup", "change-group")
603
  ])
604
$(THH.makeJSONInstance ''IAllocatorMode)
605

    
606
-- | Network mode.
607
$(THH.declareLADT ''String "NICMode"
608
  [ ("NMBridged", "bridged")
609
  , ("NMRouted",  "routed")
610
  , ("NMOvs",     "openvswitch")
611
  , ("NMPool",    "pool")
612
  ])
613
$(THH.makeJSONInstance ''NICMode)
614

    
615
-- | The JobStatus data type. Note that this is ordered especially
616
-- such that greater\/lesser comparison on values of this type makes
617
-- sense.
618
$(THH.declareLADT ''String "JobStatus"
619
  [ ("JOB_STATUS_QUEUED",    "queued")
620
  , ("JOB_STATUS_WAITING",   "waiting")
621
  , ("JOB_STATUS_CANCELING", "canceling")
622
  , ("JOB_STATUS_RUNNING",   "running")
623
  , ("JOB_STATUS_CANCELED",  "canceled")
624
  , ("JOB_STATUS_SUCCESS",   "success")
625
  , ("JOB_STATUS_ERROR",     "error")
626
  ])
627
$(THH.makeJSONInstance ''JobStatus)
628

    
629
-- | Finalized job status.
630
$(THH.declareLADT ''String "FinalizedJobStatus"
631
  [ ("JobStatusCanceled",   "canceled")
632
  , ("JobStatusSuccessful", "success")
633
  , ("JobStatusFailed",     "error")
634
  ])
635
$(THH.makeJSONInstance ''FinalizedJobStatus)
636

    
637
-- | The Ganeti job type.
638
newtype JobId = JobId { fromJobId :: Int }
639
  deriving (Show, Eq)
640

    
641
-- | Builds a job ID.
642
makeJobId :: (Monad m) => Int -> m JobId
643
makeJobId i | i >= 0 = return $ JobId i
644
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
645

    
646
-- | Builds a job ID from a string.
647
makeJobIdS :: (Monad m) => String -> m JobId
648
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
649

    
650
-- | Parses a job ID.
651
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
652
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
653
parseJobId (JSON.JSRational _ x) =
654
  if denominator x /= 1
655
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
656
    -- FIXME: potential integer overflow here on 32-bit platforms
657
    else makeJobId . fromIntegral . numerator $ x
658
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
659

    
660
instance JSON.JSON JobId where
661
  showJSON = JSON.showJSON . fromJobId
662
  readJSON = parseJobId
663

    
664
-- | Relative job ID type alias.
665
type RelativeJobId = Negative Int
666

    
667
-- | Job ID dependency.
668
data JobIdDep = JobDepRelative RelativeJobId
669
              | JobDepAbsolute JobId
670
                deriving (Show, Eq)
671

    
672
instance JSON.JSON JobIdDep where
673
  showJSON (JobDepRelative i) = showJSON i
674
  showJSON (JobDepAbsolute i) = showJSON i
675
  readJSON v =
676
    case JSON.readJSON v::JSON.Result (Negative Int) of
677
      -- first try relative dependency, usually most common
678
      JSON.Ok r -> return $ JobDepRelative r
679
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
680

    
681
-- | From job ID dependency and job ID, compute the absolute dependency.
682
absoluteJobIdDep :: (Monad m) => JobIdDep -> JobId -> m JobIdDep
683
absoluteJobIdDep (JobDepAbsolute jid) _ = return $ JobDepAbsolute jid
684
absoluteJobIdDep (JobDepRelative rjid) jid =
685
  liftM JobDepAbsolute . makeJobId $ fromJobId jid + fromNegative rjid 
686

    
687
-- | Job Dependency type.
688
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
689
                     deriving (Show, Eq)
690

    
691
instance JSON JobDependency where
692
  showJSON (JobDependency dep status) = showJSON (dep, status)
693
  readJSON = liftM (uncurry JobDependency) . readJSON
694

    
695
-- | From job dependency and job id compute an absolute job dependency.
696
absoluteJobDependency :: (Monad m) => JobDependency -> JobId -> m JobDependency
697
absoluteJobDependency (JobDependency jdep fstats) jid =
698
  liftM (flip JobDependency fstats) $ absoluteJobIdDep jdep jid 
699

    
700
-- | Valid opcode priorities for submit.
701
$(THH.declareIADT "OpSubmitPriority"
702
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
703
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
704
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
705
  ])
706
$(THH.makeJSONInstance ''OpSubmitPriority)
707

    
708
-- | Parse submit priorities from a string.
709
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
710
parseSubmitPriority "low"    = return OpPrioLow
711
parseSubmitPriority "normal" = return OpPrioNormal
712
parseSubmitPriority "high"   = return OpPrioHigh
713
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
714

    
715
-- | Format a submit priority as string.
716
fmtSubmitPriority :: OpSubmitPriority -> String
717
fmtSubmitPriority OpPrioLow    = "low"
718
fmtSubmitPriority OpPrioNormal = "normal"
719
fmtSubmitPriority OpPrioHigh   = "high"
720

    
721
-- | Our ADT for the OpCode status at runtime (while in a job).
722
$(THH.declareLADT ''String "OpStatus"
723
  [ ("OP_STATUS_QUEUED",    "queued")
724
  , ("OP_STATUS_WAITING",   "waiting")
725
  , ("OP_STATUS_CANCELING", "canceling")
726
  , ("OP_STATUS_RUNNING",   "running")
727
  , ("OP_STATUS_CANCELED",  "canceled")
728
  , ("OP_STATUS_SUCCESS",   "success")
729
  , ("OP_STATUS_ERROR",     "error")
730
  ])
731
$(THH.makeJSONInstance ''OpStatus)
732

    
733
-- | Type for the job message type.
734
$(THH.declareLADT ''String "ELogType"
735
  [ ("ELogMessage",      "message")
736
  , ("ELogRemoteImport", "remote-import")
737
  , ("ELogJqueueTest",   "jqueue-test")
738
  ])
739
$(THH.makeJSONInstance ''ELogType)
740

    
741
-- | Type of one element of a reason trail.
742
type ReasonElem = (String, String, Integer)
743

    
744
-- | Type representing a reason trail.
745
type ReasonTrail = [ReasonElem]
746

    
747
-- | The VTYPES, a mini-type system in Python.
748
$(THH.declareLADT ''String "VType"
749
  [ ("VTypeString",      "string")
750
  , ("VTypeMaybeString", "maybe-string")
751
  , ("VTypeBool",        "bool")
752
  , ("VTypeSize",        "size")
753
  , ("VTypeInt",         "int")
754
  ])
755
$(THH.makeJSONInstance ''VType)
756

    
757
instance THH.PyValue VType where
758
  showValue = THH.showValue . vTypeToRaw
759

    
760
-- * Node role type
761

    
762
$(THH.declareLADT ''String "NodeRole"
763
  [ ("NROffline",   "O")
764
  , ("NRDrained",   "D")
765
  , ("NRRegular",   "R")
766
  , ("NRCandidate", "C")
767
  , ("NRMaster",    "M")
768
  ])
769
$(THH.makeJSONInstance ''NodeRole)
770

    
771
-- | The description of the node role.
772
roleDescription :: NodeRole -> String
773
roleDescription NROffline   = "offline"
774
roleDescription NRDrained   = "drained"
775
roleDescription NRRegular   = "regular"
776
roleDescription NRCandidate = "master candidate"
777
roleDescription NRMaster    = "master"
778

    
779
-- * Disk types
780

    
781
$(THH.declareLADT ''String "DiskMode"
782
  [ ("DiskRdOnly", "ro")
783
  , ("DiskRdWr",   "rw")
784
  ])
785
$(THH.makeJSONInstance ''DiskMode)
786

    
787
-- | The persistent block driver type. Currently only one type is allowed.
788
$(THH.declareLADT ''String "BlockDriver"
789
  [ ("BlockDrvManual", "manual")
790
  ])
791
$(THH.makeJSONInstance ''BlockDriver)
792

    
793
-- * Instance types
794

    
795
$(THH.declareLADT ''String "AdminState"
796
  [ ("AdminOffline", "offline")
797
  , ("AdminDown",    "down")
798
  , ("AdminUp",      "up")
799
  ])
800
$(THH.makeJSONInstance ''AdminState)
801

    
802
-- * Storage field type
803

    
804
$(THH.declareLADT ''String "StorageField"
805
  [ ( "SFUsed",        "used")
806
  , ( "SFName",        "name")
807
  , ( "SFAllocatable", "allocatable")
808
  , ( "SFFree",        "free")
809
  , ( "SFSize",        "size")
810
  ])
811
$(THH.makeJSONInstance ''StorageField)
812

    
813
-- * Disk access protocol
814

    
815
$(THH.declareLADT ''String "DiskAccessMode"
816
  [ ( "DiskUserspace",   "userspace")
817
  , ( "DiskKernelspace", "kernelspace")
818
  ])
819
$(THH.makeJSONInstance ''DiskAccessMode)
820

    
821
-- | Local disk status
822
--
823
-- Python code depends on:
824
--   DiskStatusOk < DiskStatusUnknown < DiskStatusFaulty
825
$(THH.declareILADT "LocalDiskStatus"
826
  [ ("DiskStatusFaulty",  3)
827
  , ("DiskStatusOk",      1)
828
  , ("DiskStatusUnknown", 2)
829
  ])
830

    
831
localDiskStatusName :: LocalDiskStatus -> String
832
localDiskStatusName DiskStatusFaulty = "faulty"
833
localDiskStatusName DiskStatusOk = "ok"
834
localDiskStatusName DiskStatusUnknown = "unknown"
835

    
836
-- | Replace disks type.
837
$(THH.declareLADT ''String "ReplaceDisksMode"
838
  [ -- Replace disks on primary
839
    ("ReplaceOnPrimary",    "replace_on_primary")
840
    -- Replace disks on secondary
841
  , ("ReplaceOnSecondary",  "replace_on_secondary")
842
    -- Change secondary node
843
  , ("ReplaceNewSecondary", "replace_new_secondary")
844
  , ("ReplaceAuto",         "replace_auto")
845
  ])
846
$(THH.makeJSONInstance ''ReplaceDisksMode)
847

    
848
-- | Basic timeouts for RPC calls.
849
$(THH.declareILADT "RpcTimeout"
850
  [ ("Urgent",    60)       -- 1 minute
851
  , ("Fast",      5 * 60)   -- 5 minutes
852
  , ("Normal",    15 * 60)  -- 15 minutes
853
  , ("Slow",      3600)     -- 1 hour
854
  , ("FourHours", 4 * 3600) -- 4 hours
855
  , ("OneDay",    86400)    -- 1 day
856
  ])
857

    
858
$(THH.declareLADT ''String "ImportExportCompression"
859
  [ -- No compression
860
    ("None", "none")
861
    -- gzip compression
862
  , ("GZip", "gzip")
863
  ])
864
$(THH.makeJSONInstance ''ImportExportCompression)
865

    
866
instance THH.PyValue ImportExportCompression where
867
  showValue = THH.showValue . importExportCompressionToRaw
868

    
869
-- | Hotplug action.
870

    
871
$(THH.declareLADT ''String "HotplugAction"
872
  [ ("HAAdd", "hotadd")
873
  , ("HARemove",  "hotremove")
874
  , ("HAMod",     "hotmod")
875
  ])
876
$(THH.makeJSONInstance ''HotplugAction)
877

    
878
-- | Hotplug Device Target.
879

    
880
$(THH.declareLADT ''String "HotplugTarget"
881
  [ ("HTDisk", "hotdisk")
882
  , ("HTNic",  "hotnic")
883
  ])
884
$(THH.makeJSONInstance ''HotplugTarget)