Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 015f1517

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
667
instance JSON.JSON JobId where
668
  showJSON = JSON.showJSON . fromJobId
669
  readJSON = parseJobId
670

    
671
-- | Relative job ID type alias.
672
type RelativeJobId = Negative Int
673

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

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

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

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

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

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

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

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

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

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

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

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

    
751
-- | Type representing a reason trail.
752
type ReasonTrail = [ReasonElem]
753

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

    
764
instance THH.PyValue VType where
765
  showValue = THH.showValue . vTypeToRaw
766

    
767
-- * Node role type
768

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

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

    
786
-- * Disk types
787

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

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

    
800
-- * Instance types
801

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

    
809
-- * Storage field type
810

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

    
820
-- * Disk access protocol
821

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

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

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

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

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

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

    
873
instance THH.PyValue ImportExportCompression where
874
  showValue = THH.showValue . importExportCompressionToRaw
875

    
876
-- | Hotplug action.
877

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

    
885
-- | Hotplug Device Target.
886

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