Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 5a904197

History | View | Annotate | Download (28.1 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
  , ("StorageSharedFile", "sharedfile")
463
  , ("StorageLvmPv", "lvm-pv")
464
  , ("StorageLvmVg", "lvm-vg")
465
  , ("StorageDiskless", "diskless")
466
  , ("StorageBlock", "blockdev")
467
  , ("StorageRados", "rados")
468
  , ("StorageExt", "ext")
469
  ])
470
$(THH.makeJSONInstance ''StorageType)
471

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

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

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

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

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

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

    
516
-- | Composes a string representation of storage types without
517
-- storage parameters
518
showSUSimple :: StorageType -> StorageKey -> String
519
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
520

    
521
-- | Composes a string representation of the LVM storage types
522
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
523
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
524

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

    
540
-- | Equips a raw storage unit with its parameters
541
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
542
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
543
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
544
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
545
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
546
addParamsToStorageUnit _ (SURaw StorageSharedFile key) = SUSharedFile key
547
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
548
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
549
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
550

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

    
564
-- | The file driver type.
565
$(THH.declareLADT ''String "FileDriver"
566
  [ ("FileLoop",   "loop")
567
  , ("FileBlktap", "blktap")
568
  ])
569
$(THH.makeJSONInstance ''FileDriver)
570

    
571
-- | The instance create mode.
572
$(THH.declareLADT ''String "InstCreateMode"
573
  [ ("InstCreate",       "create")
574
  , ("InstImport",       "import")
575
  , ("InstRemoteImport", "remote-import")
576
  ])
577
$(THH.makeJSONInstance ''InstCreateMode)
578

    
579
-- | Reboot type.
580
$(THH.declareLADT ''String "RebootType"
581
  [ ("RebootSoft", "soft")
582
  , ("RebootHard", "hard")
583
  , ("RebootFull", "full")
584
  ])
585
$(THH.makeJSONInstance ''RebootType)
586

    
587
-- | Export modes.
588
$(THH.declareLADT ''String "ExportMode"
589
  [ ("ExportModeLocal",  "local")
590
  , ("ExportModeRemote", "remote")
591
  ])
592
$(THH.makeJSONInstance ''ExportMode)
593

    
594
-- | IAllocator run types (OpTestIAllocator).
595
$(THH.declareLADT ''String "IAllocatorTestDir"
596
  [ ("IAllocatorDirIn",  "in")
597
  , ("IAllocatorDirOut", "out")
598
  ])
599
$(THH.makeJSONInstance ''IAllocatorTestDir)
600

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

    
611
-- | Network mode.
612
$(THH.declareLADT ''String "NICMode"
613
  [ ("NMBridged", "bridged")
614
  , ("NMRouted",  "routed")
615
  , ("NMOvs",     "openvswitch")
616
  , ("NMPool",    "pool")
617
  ])
618
$(THH.makeJSONInstance ''NICMode)
619

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

    
634
-- | Finalized job status.
635
$(THH.declareLADT ''String "FinalizedJobStatus"
636
  [ ("JobStatusCanceled",   "canceled")
637
  , ("JobStatusSuccessful", "success")
638
  , ("JobStatusFailed",     "error")
639
  ])
640
$(THH.makeJSONInstance ''FinalizedJobStatus)
641

    
642
-- | The Ganeti job type.
643
newtype JobId = JobId { fromJobId :: Int }
644
  deriving (Show, Eq)
645

    
646
-- | Builds a job ID.
647
makeJobId :: (Monad m) => Int -> m JobId
648
makeJobId i | i >= 0 = return $ JobId i
649
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
650

    
651
-- | Builds a job ID from a string.
652
makeJobIdS :: (Monad m) => String -> m JobId
653
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
654

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

    
665
instance JSON.JSON JobId where
666
  showJSON = JSON.showJSON . fromJobId
667
  readJSON = parseJobId
668

    
669
-- | Relative job ID type alias.
670
type RelativeJobId = Negative Int
671

    
672
-- | Job ID dependency.
673
data JobIdDep = JobDepRelative RelativeJobId
674
              | JobDepAbsolute JobId
675
                deriving (Show, Eq)
676

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

    
686
-- | From job ID dependency and job ID, compute the absolute dependency.
687
absoluteJobIdDep :: (Monad m) => JobIdDep -> JobId -> m JobIdDep
688
absoluteJobIdDep (JobDepAbsolute jid) _ = return $ JobDepAbsolute jid
689
absoluteJobIdDep (JobDepRelative rjid) jid =
690
  liftM JobDepAbsolute . makeJobId $ fromJobId jid + fromNegative rjid 
691

    
692
-- | Job Dependency type.
693
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
694
                     deriving (Show, Eq)
695

    
696
instance JSON JobDependency where
697
  showJSON (JobDependency dep status) = showJSON (dep, status)
698
  readJSON = liftM (uncurry JobDependency) . readJSON
699

    
700
-- | From job dependency and job id compute an absolute job dependency.
701
absoluteJobDependency :: (Monad m) => JobDependency -> JobId -> m JobDependency
702
absoluteJobDependency (JobDependency jdep fstats) jid =
703
  liftM (flip JobDependency fstats) $ absoluteJobIdDep jdep jid 
704

    
705
-- | Valid opcode priorities for submit.
706
$(THH.declareIADT "OpSubmitPriority"
707
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
708
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
709
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
710
  ])
711
$(THH.makeJSONInstance ''OpSubmitPriority)
712

    
713
-- | Parse submit priorities from a string.
714
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
715
parseSubmitPriority "low"    = return OpPrioLow
716
parseSubmitPriority "normal" = return OpPrioNormal
717
parseSubmitPriority "high"   = return OpPrioHigh
718
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
719

    
720
-- | Format a submit priority as string.
721
fmtSubmitPriority :: OpSubmitPriority -> String
722
fmtSubmitPriority OpPrioLow    = "low"
723
fmtSubmitPriority OpPrioNormal = "normal"
724
fmtSubmitPriority OpPrioHigh   = "high"
725

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

    
738
-- | Type for the job message type.
739
$(THH.declareLADT ''String "ELogType"
740
  [ ("ELogMessage",      "message")
741
  , ("ELogRemoteImport", "remote-import")
742
  , ("ELogJqueueTest",   "jqueue-test")
743
  ])
744
$(THH.makeJSONInstance ''ELogType)
745

    
746
-- | Type of one element of a reason trail.
747
type ReasonElem = (String, String, Integer)
748

    
749
-- | Type representing a reason trail.
750
type ReasonTrail = [ReasonElem]
751

    
752
-- | The VTYPES, a mini-type system in Python.
753
$(THH.declareLADT ''String "VType"
754
  [ ("VTypeString",      "string")
755
  , ("VTypeMaybeString", "maybe-string")
756
  , ("VTypeBool",        "bool")
757
  , ("VTypeSize",        "size")
758
  , ("VTypeInt",         "int")
759
  ])
760
$(THH.makeJSONInstance ''VType)
761

    
762
instance THH.PyValue VType where
763
  showValue = THH.showValue . vTypeToRaw
764

    
765
-- * Node role type
766

    
767
$(THH.declareLADT ''String "NodeRole"
768
  [ ("NROffline",   "O")
769
  , ("NRDrained",   "D")
770
  , ("NRRegular",   "R")
771
  , ("NRCandidate", "C")
772
  , ("NRMaster",    "M")
773
  ])
774
$(THH.makeJSONInstance ''NodeRole)
775

    
776
-- | The description of the node role.
777
roleDescription :: NodeRole -> String
778
roleDescription NROffline   = "offline"
779
roleDescription NRDrained   = "drained"
780
roleDescription NRRegular   = "regular"
781
roleDescription NRCandidate = "master candidate"
782
roleDescription NRMaster    = "master"
783

    
784
-- * Disk types
785

    
786
$(THH.declareLADT ''String "DiskMode"
787
  [ ("DiskRdOnly", "ro")
788
  , ("DiskRdWr",   "rw")
789
  ])
790
$(THH.makeJSONInstance ''DiskMode)
791

    
792
-- | The persistent block driver type. Currently only one type is allowed.
793
$(THH.declareLADT ''String "BlockDriver"
794
  [ ("BlockDrvManual", "manual")
795
  ])
796
$(THH.makeJSONInstance ''BlockDriver)
797

    
798
-- * Instance types
799

    
800
$(THH.declareLADT ''String "AdminState"
801
  [ ("AdminOffline", "offline")
802
  , ("AdminDown",    "down")
803
  , ("AdminUp",      "up")
804
  ])
805
$(THH.makeJSONInstance ''AdminState)
806

    
807
-- * Storage field type
808

    
809
$(THH.declareLADT ''String "StorageField"
810
  [ ( "SFUsed",        "used")
811
  , ( "SFName",        "name")
812
  , ( "SFAllocatable", "allocatable")
813
  , ( "SFFree",        "free")
814
  , ( "SFSize",        "size")
815
  ])
816
$(THH.makeJSONInstance ''StorageField)
817

    
818
-- * Disk access protocol
819

    
820
$(THH.declareLADT ''String "DiskAccessMode"
821
  [ ( "DiskUserspace",   "userspace")
822
  , ( "DiskKernelspace", "kernelspace")
823
  ])
824
$(THH.makeJSONInstance ''DiskAccessMode)
825

    
826
-- | Local disk status
827
--
828
-- Python code depends on:
829
--   DiskStatusOk < DiskStatusUnknown < DiskStatusFaulty
830
$(THH.declareILADT "LocalDiskStatus"
831
  [ ("DiskStatusFaulty",  3)
832
  , ("DiskStatusOk",      1)
833
  , ("DiskStatusUnknown", 2)
834
  ])
835

    
836
localDiskStatusName :: LocalDiskStatus -> String
837
localDiskStatusName DiskStatusFaulty = "faulty"
838
localDiskStatusName DiskStatusOk = "ok"
839
localDiskStatusName DiskStatusUnknown = "unknown"
840

    
841
-- | Replace disks type.
842
$(THH.declareLADT ''String "ReplaceDisksMode"
843
  [ -- Replace disks on primary
844
    ("ReplaceOnPrimary",    "replace_on_primary")
845
    -- Replace disks on secondary
846
  , ("ReplaceOnSecondary",  "replace_on_secondary")
847
    -- Change secondary node
848
  , ("ReplaceNewSecondary", "replace_new_secondary")
849
  , ("ReplaceAuto",         "replace_auto")
850
  ])
851
$(THH.makeJSONInstance ''ReplaceDisksMode)
852

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

    
863
$(THH.declareLADT ''String "ImportExportCompression"
864
  [ -- No compression
865
    ("None", "none")
866
    -- gzip compression
867
  , ("GZip", "gzip")
868
  ])
869
$(THH.makeJSONInstance ''ImportExportCompression)
870

    
871
instance THH.PyValue ImportExportCompression where
872
  showValue = THH.showValue . importExportCompressionToRaw
873

    
874
-- | Hotplug action.
875

    
876
$(THH.declareLADT ''String "HotplugAction"
877
  [ ("HAAdd", "hotadd")
878
  , ("HARemove",  "hotremove")
879
  , ("HAMod",     "hotmod")
880
  ])
881
$(THH.makeJSONInstance ''HotplugAction)
882

    
883
-- | Hotplug Device Target.
884

    
885
$(THH.declareLADT ''String "HotplugTarget"
886
  [ ("HTDisk", "hotdisk")
887
  , ("HTNic",  "hotnic")
888
  ])
889
$(THH.makeJSONInstance ''HotplugTarget)