Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 59bcd180

History | View | Annotate | Download (26.3 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
  , OpSubmitPriority(..)
114
  , opSubmitPriorityToRaw
115
  , parseSubmitPriority
116
  , fmtSubmitPriority
117
  , OpStatus(..)
118
  , opStatusToRaw
119
  , opStatusFromRaw
120
  , ELogType(..)
121
  , eLogTypeToRaw
122
  , ReasonElem
123
  , ReasonTrail
124
  , StorageUnit(..)
125
  , StorageUnitRaw(..)
126
  , StorageKey
127
  , addParamsToStorageUnit
128
  , diskTemplateToStorageType
129
  , VType(..)
130
  , vTypeFromRaw
131
  , vTypeToRaw
132
  , NodeRole(..)
133
  , nodeRoleToRaw
134
  , roleDescription
135
  , DiskMode(..)
136
  , diskModeToRaw
137
  , BlockDriver(..)
138
  , blockDriverToRaw
139
  , AdminState(..)
140
  , adminStateFromRaw
141
  , adminStateToRaw
142
  , StorageField(..)
143
  , storageFieldToRaw
144
  , DiskAccessMode(..)
145
  , diskAccessModeToRaw
146
  , LocalDiskStatus(..)
147
  , localDiskStatusFromRaw
148
  , localDiskStatusToRaw
149
  , localDiskStatusName
150
  , ReplaceDisksMode(..)
151
  , replaceDisksModeToRaw
152
  , RpcTimeout(..)
153
  , rpcTimeoutFromRaw -- FIXME: no used anywhere
154
  , rpcTimeoutToRaw
155
  ) where
156

    
157
import Control.Monad (liftM)
158
import qualified Text.JSON as JSON
159
import Text.JSON (JSON, readJSON, showJSON)
160
import Data.Ratio (numerator, denominator)
161

    
162
import qualified Ganeti.ConstantUtils as ConstantUtils
163
import Ganeti.JSON
164
import qualified Ganeti.THH as THH
165
import Ganeti.Utils
166

    
167
-- * Generic types
168

    
169
-- | Type that holds a non-negative value.
170
newtype NonNegative a = NonNegative { fromNonNegative :: a }
171
  deriving (Show, Eq)
172

    
173
-- | Smart constructor for 'NonNegative'.
174
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
175
mkNonNegative i | i >= 0 = return (NonNegative i)
176
                | otherwise = fail $ "Invalid value for non-negative type '" ++
177
                              show i ++ "'"
178

    
179
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
180
  showJSON = JSON.showJSON . fromNonNegative
181
  readJSON v = JSON.readJSON v >>= mkNonNegative
182

    
183
-- | Type that holds a positive value.
184
newtype Positive a = Positive { fromPositive :: a }
185
  deriving (Show, Eq)
186

    
187
-- | Smart constructor for 'Positive'.
188
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
189
mkPositive i | i > 0 = return (Positive i)
190
             | otherwise = fail $ "Invalid value for positive type '" ++
191
                           show i ++ "'"
192

    
193
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
194
  showJSON = JSON.showJSON . fromPositive
195
  readJSON v = JSON.readJSON v >>= mkPositive
196

    
197
-- | Type that holds a negative value.
198
newtype Negative a = Negative { fromNegative :: a }
199
  deriving (Show, Eq)
200

    
201
-- | Smart constructor for 'Negative'.
202
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
203
mkNegative i | i < 0 = return (Negative i)
204
             | otherwise = fail $ "Invalid value for negative type '" ++
205
                           show i ++ "'"
206

    
207
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
208
  showJSON = JSON.showJSON . fromNegative
209
  readJSON v = JSON.readJSON v >>= mkNegative
210

    
211
-- | Type that holds a non-null list.
212
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
213
  deriving (Show, Eq)
214

    
215
-- | Smart constructor for 'NonEmpty'.
216
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
217
mkNonEmpty [] = fail "Received empty value for non-empty list"
218
mkNonEmpty xs = return (NonEmpty xs)
219

    
220
instance (Eq a, Ord a) => Ord (NonEmpty a) where
221
  NonEmpty { fromNonEmpty = x1 } `compare` NonEmpty { fromNonEmpty = x2 } =
222
    x1 `compare` x2
223

    
224
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
225
  showJSON = JSON.showJSON . fromNonEmpty
226
  readJSON v = JSON.readJSON v >>= mkNonEmpty
227

    
228
-- | A simple type alias for non-empty strings.
229
type NonEmptyString = NonEmpty Char
230

    
231
type QueryResultCode = Int
232

    
233
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
234
  deriving (Show, Eq)
235

    
236
-- FIXME: this should check that 'address' is a valid ip
237
mkIPv4Address :: Monad m => String -> m IPv4Address
238
mkIPv4Address address =
239
  return IPv4Address { fromIPv4Address = address }
240

    
241
instance JSON.JSON IPv4Address where
242
  showJSON = JSON.showJSON . fromIPv4Address
243
  readJSON v = JSON.readJSON v >>= mkIPv4Address
244

    
245
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
246
  deriving (Show, Eq)
247

    
248
-- FIXME: this should check that 'address' is a valid ip
249
mkIPv4Network :: Monad m => String -> m IPv4Network
250
mkIPv4Network address =
251
  return IPv4Network { fromIPv4Network = address }
252

    
253
instance JSON.JSON IPv4Network where
254
  showJSON = JSON.showJSON . fromIPv4Network
255
  readJSON v = JSON.readJSON v >>= mkIPv4Network
256

    
257
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
258
  deriving (Show, Eq)
259

    
260
-- FIXME: this should check that 'address' is a valid ip
261
mkIPv6Address :: Monad m => String -> m IPv6Address
262
mkIPv6Address address =
263
  return IPv6Address { fromIPv6Address = address }
264

    
265
instance JSON.JSON IPv6Address where
266
  showJSON = JSON.showJSON . fromIPv6Address
267
  readJSON v = JSON.readJSON v >>= mkIPv6Address
268

    
269
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
270
  deriving (Show, Eq)
271

    
272
-- FIXME: this should check that 'address' is a valid ip
273
mkIPv6Network :: Monad m => String -> m IPv6Network
274
mkIPv6Network address =
275
  return IPv6Network { fromIPv6Network = address }
276

    
277
instance JSON.JSON IPv6Network where
278
  showJSON = JSON.showJSON . fromIPv6Network
279
  readJSON v = JSON.readJSON v >>= mkIPv6Network
280

    
281
-- * Ganeti types
282

    
283
-- | Instance disk template type.
284
$(THH.declareLADT ''String "DiskTemplate"
285
       [ ("DTDiskless",   "diskless")
286
       , ("DTFile",       "file")
287
       , ("DTSharedFile", "sharedfile")
288
       , ("DTPlain",      "plain")
289
       , ("DTBlock",      "blockdev")
290
       , ("DTDrbd8",      "drbd")
291
       , ("DTRbd",        "rbd")
292
       , ("DTExt",        "ext")
293
       ])
294
$(THH.makeJSONInstance ''DiskTemplate)
295

    
296
instance THH.PyValue DiskTemplate where
297
  showValue = show . diskTemplateToRaw
298

    
299
instance HasStringRepr DiskTemplate where
300
  fromStringRepr = diskTemplateFromRaw
301
  toStringRepr = diskTemplateToRaw
302

    
303
-- | Data type representing what items the tag operations apply to.
304
$(THH.declareLADT ''String "TagKind"
305
  [ ("TagKindInstance", "instance")
306
  , ("TagKindNode",     "node")
307
  , ("TagKindGroup",    "nodegroup")
308
  , ("TagKindCluster",  "cluster")
309
  , ("TagKindNetwork",  "network")
310
  ])
311
$(THH.makeJSONInstance ''TagKind)
312

    
313
-- | The Group allocation policy type.
314
--
315
-- Note that the order of constructors is important as the automatic
316
-- Ord instance will order them in the order they are defined, so when
317
-- changing this data type be careful about the interaction with the
318
-- desired sorting order.
319
$(THH.declareLADT ''String "AllocPolicy"
320
       [ ("AllocPreferred",   "preferred")
321
       , ("AllocLastResort",  "last_resort")
322
       , ("AllocUnallocable", "unallocable")
323
       ])
324
$(THH.makeJSONInstance ''AllocPolicy)
325

    
326
-- | The Instance real state type. FIXME: this could be improved to
327
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
328
$(THH.declareLADT ''String "InstanceStatus"
329
       [ ("StatusDown",    "ADMIN_down")
330
       , ("StatusOffline", "ADMIN_offline")
331
       , ("ErrorDown",     "ERROR_down")
332
       , ("ErrorUp",       "ERROR_up")
333
       , ("NodeDown",      "ERROR_nodedown")
334
       , ("NodeOffline",   "ERROR_nodeoffline")
335
       , ("Running",       "running")
336
       , ("WrongNode",     "ERROR_wrongnode")
337
       ])
338
$(THH.makeJSONInstance ''InstanceStatus)
339

    
340
-- | Migration mode.
341
$(THH.declareLADT ''String "MigrationMode"
342
     [ ("MigrationLive",    "live")
343
     , ("MigrationNonLive", "non-live")
344
     ])
345
$(THH.makeJSONInstance ''MigrationMode)
346

    
347
-- | Verify optional checks.
348
$(THH.declareLADT ''String "VerifyOptionalChecks"
349
     [ ("VerifyNPlusOneMem", "nplusone_mem")
350
     ])
351
$(THH.makeJSONInstance ''VerifyOptionalChecks)
352

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

    
397
-- | Dynamic device modification, just add\/remove version.
398
$(THH.declareLADT ''String "DdmSimple"
399
     [ ("DdmSimpleAdd",    "add")
400
     , ("DdmSimpleRemove", "remove")
401
     ])
402
$(THH.makeJSONInstance ''DdmSimple)
403

    
404
-- | Dynamic device modification, all operations version.
405
--
406
-- TODO: DDM_SWAP, DDM_MOVE?
407
$(THH.declareLADT ''String "DdmFull"
408
     [ ("DdmFullAdd",    "add")
409
     , ("DdmFullRemove", "remove")
410
     , ("DdmFullModify", "modify")
411
     ])
412
$(THH.makeJSONInstance ''DdmFull)
413

    
414
-- | Hypervisor type definitions.
415
$(THH.declareLADT ''String "Hypervisor"
416
  [ ("Kvm",    "kvm")
417
  , ("XenPvm", "xen-pvm")
418
  , ("Chroot", "chroot")
419
  , ("XenHvm", "xen-hvm")
420
  , ("Lxc",    "lxc")
421
  , ("Fake",   "fake")
422
  ])
423
$(THH.makeJSONInstance ''Hypervisor)
424

    
425
instance THH.PyValue Hypervisor where
426
  showValue = show . hypervisorToRaw
427

    
428
-- | Oob command type.
429
$(THH.declareLADT ''String "OobCommand"
430
  [ ("OobHealth",      "health")
431
  , ("OobPowerCycle",  "power-cycle")
432
  , ("OobPowerOff",    "power-off")
433
  , ("OobPowerOn",     "power-on")
434
  , ("OobPowerStatus", "power-status")
435
  ])
436
$(THH.makeJSONInstance ''OobCommand)
437

    
438
-- | Oob command status
439
$(THH.declareLADT ''String "OobStatus"
440
  [ ("OobStatusCritical", "CRITICAL")
441
  , ("OobStatusOk",       "OK")
442
  , ("OobStatusUnknown",  "UNKNOWN")
443
  , ("OobStatusWarning",  "WARNING")
444
  ])
445
$(THH.makeJSONInstance ''OobStatus)
446

    
447
-- | Storage type.
448
$(THH.declareLADT ''String "StorageType"
449
  [ ("StorageFile", "file")
450
  , ("StorageLvmPv", "lvm-pv")
451
  , ("StorageLvmVg", "lvm-vg")
452
  , ("StorageDiskless", "diskless")
453
  , ("StorageBlock", "blockdev")
454
  , ("StorageRados", "rados")
455
  , ("StorageExt", "ext")
456
  ])
457
$(THH.makeJSONInstance ''StorageType)
458

    
459
-- | Storage keys are identifiers for storage units. Their content varies
460
-- depending on the storage type, for example a storage key for LVM storage
461
-- is the volume group name.
462
type StorageKey = String
463

    
464
-- | Storage parameters
465
type SPExclusiveStorage = Bool
466

    
467
-- | Storage units without storage-type-specific parameters
468
data StorageUnitRaw = SURaw StorageType StorageKey
469

    
470
-- | Full storage unit with storage-type-specific parameters
471
data StorageUnit = SUFile StorageKey
472
                 | SULvmPv StorageKey SPExclusiveStorage
473
                 | SULvmVg StorageKey SPExclusiveStorage
474
                 | SUDiskless StorageKey
475
                 | SUBlock StorageKey
476
                 | SURados StorageKey
477
                 | SUExt StorageKey
478
                 deriving (Eq)
479

    
480
instance Show StorageUnit where
481
  show (SUFile key) = showSUSimple StorageFile key
482
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
483
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
484
  show (SUDiskless key) = showSUSimple StorageDiskless key
485
  show (SUBlock key) = showSUSimple StorageBlock key
486
  show (SURados key) = showSUSimple StorageRados key
487
  show (SUExt key) = showSUSimple StorageExt key
488

    
489
instance JSON StorageUnit where
490
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
491
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
492
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
493
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
494
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
495
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
496
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
497
-- FIXME: add readJSON implementation
498
  readJSON = fail "Not implemented"
499

    
500
-- | Composes a string representation of storage types without
501
-- storage parameters
502
showSUSimple :: StorageType -> StorageKey -> String
503
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
504

    
505
-- | Composes a string representation of the LVM storage types
506
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
507
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
508

    
509
-- | Mapping from disk templates to storage types
510
-- FIXME: This is semantically the same as the constant
511
-- C.diskTemplatesStorageType, remove this when python constants
512
-- are generated from haskell constants
513
diskTemplateToStorageType :: DiskTemplate -> StorageType
514
diskTemplateToStorageType DTExt = StorageExt
515
diskTemplateToStorageType DTFile = StorageFile
516
diskTemplateToStorageType DTSharedFile = StorageFile
517
diskTemplateToStorageType DTDrbd8 = StorageLvmVg
518
diskTemplateToStorageType DTPlain = StorageLvmVg
519
diskTemplateToStorageType DTRbd = StorageRados
520
diskTemplateToStorageType DTDiskless = StorageDiskless
521
diskTemplateToStorageType DTBlock = StorageBlock
522

    
523
-- | Equips a raw storage unit with its parameters
524
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
525
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
526
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
527
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
528
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
529
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
530
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
531
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
532

    
533
-- | Node evac modes.
534
--
535
-- This is part of the 'IAllocator' interface and it is used, for
536
-- example, in 'Ganeti.HTools.Loader.RqType'.  However, it must reside
537
-- in this module, and not in 'Ganeti.HTools.Types', because it is
538
-- also used by 'Ganeti.HsConstants'.
539
$(THH.declareLADT ''String "EvacMode"
540
  [ ("ChangePrimary",   "primary-only")
541
  , ("ChangeSecondary", "secondary-only")
542
  , ("ChangeAll",       "all")
543
  ])
544
$(THH.makeJSONInstance ''EvacMode)
545

    
546
-- | The file driver type.
547
$(THH.declareLADT ''String "FileDriver"
548
  [ ("FileLoop",   "loop")
549
  , ("FileBlktap", "blktap")
550
  ])
551
$(THH.makeJSONInstance ''FileDriver)
552

    
553
-- | The instance create mode.
554
$(THH.declareLADT ''String "InstCreateMode"
555
  [ ("InstCreate",       "create")
556
  , ("InstImport",       "import")
557
  , ("InstRemoteImport", "remote-import")
558
  ])
559
$(THH.makeJSONInstance ''InstCreateMode)
560

    
561
-- | Reboot type.
562
$(THH.declareLADT ''String "RebootType"
563
  [ ("RebootSoft", "soft")
564
  , ("RebootHard", "hard")
565
  , ("RebootFull", "full")
566
  ])
567
$(THH.makeJSONInstance ''RebootType)
568

    
569
-- | Export modes.
570
$(THH.declareLADT ''String "ExportMode"
571
  [ ("ExportModeLocal",  "local")
572
  , ("ExportModeRemote", "remote")
573
  ])
574
$(THH.makeJSONInstance ''ExportMode)
575

    
576
-- | IAllocator run types (OpTestIAllocator).
577
$(THH.declareLADT ''String "IAllocatorTestDir"
578
  [ ("IAllocatorDirIn",  "in")
579
  , ("IAllocatorDirOut", "out")
580
  ])
581
$(THH.makeJSONInstance ''IAllocatorTestDir)
582

    
583
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
584
$(THH.declareLADT ''String "IAllocatorMode"
585
  [ ("IAllocatorAlloc",       "allocate")
586
  , ("IAllocatorMultiAlloc",  "multi-allocate")
587
  , ("IAllocatorReloc",       "relocate")
588
  , ("IAllocatorNodeEvac",    "node-evacuate")
589
  , ("IAllocatorChangeGroup", "change-group")
590
  ])
591
$(THH.makeJSONInstance ''IAllocatorMode)
592

    
593
-- | Network mode.
594
$(THH.declareLADT ''String "NICMode"
595
  [ ("NMBridged", "bridged")
596
  , ("NMRouted",  "routed")
597
  , ("NMOvs",     "openvswitch")
598
  , ("NMPool",    "pool")
599
  ])
600
$(THH.makeJSONInstance ''NICMode)
601

    
602
-- | The JobStatus data type. Note that this is ordered especially
603
-- such that greater\/lesser comparison on values of this type makes
604
-- sense.
605
$(THH.declareLADT ''String "JobStatus"
606
  [ ("JOB_STATUS_QUEUED",    "queued")
607
  , ("JOB_STATUS_WAITING",   "waiting")
608
  , ("JOB_STATUS_CANCELING", "canceling")
609
  , ("JOB_STATUS_RUNNING",   "running")
610
  , ("JOB_STATUS_CANCELED",  "canceled")
611
  , ("JOB_STATUS_SUCCESS",   "success")
612
  , ("JOB_STATUS_ERROR",     "error")
613
  ])
614
$(THH.makeJSONInstance ''JobStatus)
615

    
616
-- | Finalized job status.
617
$(THH.declareLADT ''String "FinalizedJobStatus"
618
  [ ("JobStatusCanceled",   "canceled")
619
  , ("JobStatusSuccessful", "success")
620
  , ("JobStatusFailed",     "error")
621
  ])
622
$(THH.makeJSONInstance ''FinalizedJobStatus)
623

    
624
-- | The Ganeti job type.
625
newtype JobId = JobId { fromJobId :: Int }
626
  deriving (Show, Eq)
627

    
628
-- | Builds a job ID.
629
makeJobId :: (Monad m) => Int -> m JobId
630
makeJobId i | i >= 0 = return $ JobId i
631
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
632

    
633
-- | Builds a job ID from a string.
634
makeJobIdS :: (Monad m) => String -> m JobId
635
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
636

    
637
-- | Parses a job ID.
638
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
639
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
640
parseJobId (JSON.JSRational _ x) =
641
  if denominator x /= 1
642
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
643
    -- FIXME: potential integer overflow here on 32-bit platforms
644
    else makeJobId . fromIntegral . numerator $ x
645
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
646

    
647
instance JSON.JSON JobId where
648
  showJSON = JSON.showJSON . fromJobId
649
  readJSON = parseJobId
650

    
651
-- | Relative job ID type alias.
652
type RelativeJobId = Negative Int
653

    
654
-- | Job ID dependency.
655
data JobIdDep = JobDepRelative RelativeJobId
656
              | JobDepAbsolute JobId
657
                deriving (Show, Eq)
658

    
659
instance JSON.JSON JobIdDep where
660
  showJSON (JobDepRelative i) = showJSON i
661
  showJSON (JobDepAbsolute i) = showJSON i
662
  readJSON v =
663
    case JSON.readJSON v::JSON.Result (Negative Int) of
664
      -- first try relative dependency, usually most common
665
      JSON.Ok r -> return $ JobDepRelative r
666
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
667

    
668
-- | Job Dependency type.
669
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
670
                     deriving (Show, Eq)
671

    
672
instance JSON JobDependency where
673
  showJSON (JobDependency dep status) = showJSON (dep, status)
674
  readJSON = liftM (uncurry JobDependency) . readJSON
675

    
676
-- | Valid opcode priorities for submit.
677
$(THH.declareIADT "OpSubmitPriority"
678
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
679
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
680
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
681
  ])
682
$(THH.makeJSONInstance ''OpSubmitPriority)
683

    
684
-- | Parse submit priorities from a string.
685
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
686
parseSubmitPriority "low"    = return OpPrioLow
687
parseSubmitPriority "normal" = return OpPrioNormal
688
parseSubmitPriority "high"   = return OpPrioHigh
689
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
690

    
691
-- | Format a submit priority as string.
692
fmtSubmitPriority :: OpSubmitPriority -> String
693
fmtSubmitPriority OpPrioLow    = "low"
694
fmtSubmitPriority OpPrioNormal = "normal"
695
fmtSubmitPriority OpPrioHigh   = "high"
696

    
697
-- | Our ADT for the OpCode status at runtime (while in a job).
698
$(THH.declareLADT ''String "OpStatus"
699
  [ ("OP_STATUS_QUEUED",    "queued")
700
  , ("OP_STATUS_WAITING",   "waiting")
701
  , ("OP_STATUS_CANCELING", "canceling")
702
  , ("OP_STATUS_RUNNING",   "running")
703
  , ("OP_STATUS_CANCELED",  "canceled")
704
  , ("OP_STATUS_SUCCESS",   "success")
705
  , ("OP_STATUS_ERROR",     "error")
706
  ])
707
$(THH.makeJSONInstance ''OpStatus)
708

    
709
-- | Type for the job message type.
710
$(THH.declareLADT ''String "ELogType"
711
  [ ("ELogMessage",      "message")
712
  , ("ELogRemoteImport", "remote-import")
713
  , ("ELogJqueueTest",   "jqueue-test")
714
  ])
715
$(THH.makeJSONInstance ''ELogType)
716

    
717
-- | Type of one element of a reason trail.
718
type ReasonElem = (String, String, Integer)
719

    
720
-- | Type representing a reason trail.
721
type ReasonTrail = [ReasonElem]
722

    
723
-- | The VTYPES, a mini-type system in Python.
724
$(THH.declareLADT ''String "VType"
725
  [ ("VTypeString",      "string")
726
  , ("VTypeMaybeString", "maybe-string")
727
  , ("VTypeBool",        "bool")
728
  , ("VTypeSize",        "size")
729
  , ("VTypeInt",         "int")
730
  ])
731
$(THH.makeJSONInstance ''VType)
732

    
733
instance THH.PyValue VType where
734
  showValue = THH.showValue . vTypeToRaw
735

    
736
-- * Node role type
737

    
738
$(THH.declareLADT ''String "NodeRole"
739
  [ ("NROffline",   "O")
740
  , ("NRDrained",   "D")
741
  , ("NRRegular",   "R")
742
  , ("NRCandidate", "C")
743
  , ("NRMaster",    "M")
744
  ])
745
$(THH.makeJSONInstance ''NodeRole)
746

    
747
-- | The description of the node role.
748
roleDescription :: NodeRole -> String
749
roleDescription NROffline   = "offline"
750
roleDescription NRDrained   = "drained"
751
roleDescription NRRegular   = "regular"
752
roleDescription NRCandidate = "master candidate"
753
roleDescription NRMaster    = "master"
754

    
755
-- * Disk types
756

    
757
$(THH.declareLADT ''String "DiskMode"
758
  [ ("DiskRdOnly", "ro")
759
  , ("DiskRdWr",   "rw")
760
  ])
761
$(THH.makeJSONInstance ''DiskMode)
762

    
763
-- | The persistent block driver type. Currently only one type is allowed.
764
$(THH.declareLADT ''String "BlockDriver"
765
  [ ("BlockDrvManual", "manual")
766
  ])
767
$(THH.makeJSONInstance ''BlockDriver)
768

    
769
-- * Instance types
770

    
771
$(THH.declareLADT ''String "AdminState"
772
  [ ("AdminOffline", "offline")
773
  , ("AdminDown",    "down")
774
  , ("AdminUp",      "up")
775
  ])
776
$(THH.makeJSONInstance ''AdminState)
777

    
778
-- * Storage field type
779

    
780
$(THH.declareLADT ''String "StorageField"
781
  [ ( "SFUsed",        "used")
782
  , ( "SFName",        "name")
783
  , ( "SFAllocatable", "allocatable")
784
  , ( "SFFree",        "free")
785
  , ( "SFSize",        "size")
786
  ])
787
$(THH.makeJSONInstance ''StorageField)
788

    
789
-- * Disk access protocol
790

    
791
$(THH.declareLADT ''String "DiskAccessMode"
792
  [ ( "DiskUserspace",   "userspace")
793
  , ( "DiskKernelspace", "kernelspace")
794
  ])
795
$(THH.makeJSONInstance ''DiskAccessMode)
796

    
797
-- | Local disk status
798
--
799
-- Python code depends on:
800
--   DiskStatusOk < DiskStatusUnknown < DiskStatusFaulty
801
$(THH.declareILADT "LocalDiskStatus"
802
  [ ("DiskStatusFaulty",  3)
803
  , ("DiskStatusOk",      1)
804
  , ("DiskStatusUnknown", 2)
805
  ])
806

    
807
localDiskStatusName :: LocalDiskStatus -> String
808
localDiskStatusName DiskStatusFaulty = "faulty"
809
localDiskStatusName DiskStatusOk = "ok"
810
localDiskStatusName DiskStatusUnknown = "unknown"
811

    
812
-- | Replace disks type.
813
$(THH.declareLADT ''String "ReplaceDisksMode"
814
  [ -- Replace disks on primary
815
    ("ReplaceOnPrimary",    "replace_on_primary")
816
    -- Replace disks on secondary
817
  , ("ReplaceOnSecondary",  "replace_on_secondary")
818
    -- Change secondary node
819
  , ("ReplaceNewSecondary", "replace_new_secondary")
820
  , ("ReplaceAuto",         "replace_auto")
821
  ])
822
$(THH.makeJSONInstance ''ReplaceDisksMode)
823

    
824
-- | Basic timeouts for RPC calls.
825
$(THH.declareILADT "RpcTimeout"
826
  [ ("Urgent",    60)       -- 1 minute
827
  , ("Fast",      5 * 60)   -- 5 minutes
828
  , ("Normal",    15 * 60)  -- 15 minutes
829
  , ("Slow",      3600)     -- 1 hour
830
  , ("FourHours", 4 * 3600) -- 4 hours
831
  , ("OneDay",    86400)    -- 1 day
832
  ])