Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ f198cf91

History | View | Annotate | Download (26.7 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
  , ImportExportCompression(..)
156
  , importExportCompressionToRaw
157
  ) where
158

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

    
164
import qualified Ganeti.ConstantUtils as ConstantUtils
165
import Ganeti.JSON
166
import qualified Ganeti.THH as THH
167
import Ganeti.Utils
168

    
169
-- * Generic types
170

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
233
type QueryResultCode = Int
234

    
235
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
236
  deriving (Show, Eq)
237

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

    
243
instance JSON.JSON IPv4Address where
244
  showJSON = JSON.showJSON . fromIPv4Address
245
  readJSON v = JSON.readJSON v >>= mkIPv4Address
246

    
247
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
248
  deriving (Show, Eq)
249

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

    
255
instance JSON.JSON IPv4Network where
256
  showJSON = JSON.showJSON . fromIPv4Network
257
  readJSON v = JSON.readJSON v >>= mkIPv4Network
258

    
259
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
260
  deriving (Show, Eq)
261

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

    
267
instance JSON.JSON IPv6Address where
268
  showJSON = JSON.showJSON . fromIPv6Address
269
  readJSON v = JSON.readJSON v >>= mkIPv6Address
270

    
271
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
272
  deriving (Show, Eq)
273

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

    
279
instance JSON.JSON IPv6Network where
280
  showJSON = JSON.showJSON . fromIPv6Network
281
  readJSON v = JSON.readJSON v >>= mkIPv6Network
282

    
283
-- * Ganeti types
284

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

    
298
instance THH.PyValue DiskTemplate where
299
  showValue = show . diskTemplateToRaw
300

    
301
instance HasStringRepr DiskTemplate where
302
  fromStringRepr = diskTemplateFromRaw
303
  toStringRepr = diskTemplateToRaw
304

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

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

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

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

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

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

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

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

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

    
427
instance THH.PyValue Hypervisor where
428
  showValue = show . hypervisorToRaw
429

    
430
instance HasStringRepr Hypervisor where
431
  fromStringRepr = hypervisorFromRaw
432
  toStringRepr = hypervisorToRaw
433

    
434
-- | Oob command type.
435
$(THH.declareLADT ''String "OobCommand"
436
  [ ("OobHealth",      "health")
437
  , ("OobPowerCycle",  "power-cycle")
438
  , ("OobPowerOff",    "power-off")
439
  , ("OobPowerOn",     "power-on")
440
  , ("OobPowerStatus", "power-status")
441
  ])
442
$(THH.makeJSONInstance ''OobCommand)
443

    
444
-- | Oob command status
445
$(THH.declareLADT ''String "OobStatus"
446
  [ ("OobStatusCritical", "CRITICAL")
447
  , ("OobStatusOk",       "OK")
448
  , ("OobStatusUnknown",  "UNKNOWN")
449
  , ("OobStatusWarning",  "WARNING")
450
  ])
451
$(THH.makeJSONInstance ''OobStatus)
452

    
453
-- | Storage type.
454
$(THH.declareLADT ''String "StorageType"
455
  [ ("StorageFile", "file")
456
  , ("StorageLvmPv", "lvm-pv")
457
  , ("StorageLvmVg", "lvm-vg")
458
  , ("StorageDiskless", "diskless")
459
  , ("StorageBlock", "blockdev")
460
  , ("StorageRados", "rados")
461
  , ("StorageExt", "ext")
462
  ])
463
$(THH.makeJSONInstance ''StorageType)
464

    
465
-- | Storage keys are identifiers for storage units. Their content varies
466
-- depending on the storage type, for example a storage key for LVM storage
467
-- is the volume group name.
468
type StorageKey = String
469

    
470
-- | Storage parameters
471
type SPExclusiveStorage = Bool
472

    
473
-- | Storage units without storage-type-specific parameters
474
data StorageUnitRaw = SURaw StorageType StorageKey
475

    
476
-- | Full storage unit with storage-type-specific parameters
477
data StorageUnit = SUFile StorageKey
478
                 | SULvmPv StorageKey SPExclusiveStorage
479
                 | SULvmVg StorageKey SPExclusiveStorage
480
                 | SUDiskless StorageKey
481
                 | SUBlock StorageKey
482
                 | SURados StorageKey
483
                 | SUExt StorageKey
484
                 deriving (Eq)
485

    
486
instance Show StorageUnit where
487
  show (SUFile key) = showSUSimple StorageFile key
488
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
489
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
490
  show (SUDiskless key) = showSUSimple StorageDiskless key
491
  show (SUBlock key) = showSUSimple StorageBlock key
492
  show (SURados key) = showSUSimple StorageRados key
493
  show (SUExt key) = showSUSimple StorageExt key
494

    
495
instance JSON StorageUnit where
496
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
497
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
498
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
499
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
500
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
501
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
502
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
503
-- FIXME: add readJSON implementation
504
  readJSON = fail "Not implemented"
505

    
506
-- | Composes a string representation of storage types without
507
-- storage parameters
508
showSUSimple :: StorageType -> StorageKey -> String
509
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
510

    
511
-- | Composes a string representation of the LVM storage types
512
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
513
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
514

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

    
529
-- | Equips a raw storage unit with its parameters
530
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
531
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
532
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
533
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
534
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
535
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
536
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
537
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
538

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

    
552
-- | The file driver type.
553
$(THH.declareLADT ''String "FileDriver"
554
  [ ("FileLoop",   "loop")
555
  , ("FileBlktap", "blktap")
556
  ])
557
$(THH.makeJSONInstance ''FileDriver)
558

    
559
-- | The instance create mode.
560
$(THH.declareLADT ''String "InstCreateMode"
561
  [ ("InstCreate",       "create")
562
  , ("InstImport",       "import")
563
  , ("InstRemoteImport", "remote-import")
564
  ])
565
$(THH.makeJSONInstance ''InstCreateMode)
566

    
567
-- | Reboot type.
568
$(THH.declareLADT ''String "RebootType"
569
  [ ("RebootSoft", "soft")
570
  , ("RebootHard", "hard")
571
  , ("RebootFull", "full")
572
  ])
573
$(THH.makeJSONInstance ''RebootType)
574

    
575
-- | Export modes.
576
$(THH.declareLADT ''String "ExportMode"
577
  [ ("ExportModeLocal",  "local")
578
  , ("ExportModeRemote", "remote")
579
  ])
580
$(THH.makeJSONInstance ''ExportMode)
581

    
582
-- | IAllocator run types (OpTestIAllocator).
583
$(THH.declareLADT ''String "IAllocatorTestDir"
584
  [ ("IAllocatorDirIn",  "in")
585
  , ("IAllocatorDirOut", "out")
586
  ])
587
$(THH.makeJSONInstance ''IAllocatorTestDir)
588

    
589
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
590
$(THH.declareLADT ''String "IAllocatorMode"
591
  [ ("IAllocatorAlloc",       "allocate")
592
  , ("IAllocatorMultiAlloc",  "multi-allocate")
593
  , ("IAllocatorReloc",       "relocate")
594
  , ("IAllocatorNodeEvac",    "node-evacuate")
595
  , ("IAllocatorChangeGroup", "change-group")
596
  ])
597
$(THH.makeJSONInstance ''IAllocatorMode)
598

    
599
-- | Network mode.
600
$(THH.declareLADT ''String "NICMode"
601
  [ ("NMBridged", "bridged")
602
  , ("NMRouted",  "routed")
603
  , ("NMOvs",     "openvswitch")
604
  , ("NMPool",    "pool")
605
  ])
606
$(THH.makeJSONInstance ''NICMode)
607

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

    
622
-- | Finalized job status.
623
$(THH.declareLADT ''String "FinalizedJobStatus"
624
  [ ("JobStatusCanceled",   "canceled")
625
  , ("JobStatusSuccessful", "success")
626
  , ("JobStatusFailed",     "error")
627
  ])
628
$(THH.makeJSONInstance ''FinalizedJobStatus)
629

    
630
-- | The Ganeti job type.
631
newtype JobId = JobId { fromJobId :: Int }
632
  deriving (Show, Eq)
633

    
634
-- | Builds a job ID.
635
makeJobId :: (Monad m) => Int -> m JobId
636
makeJobId i | i >= 0 = return $ JobId i
637
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
638

    
639
-- | Builds a job ID from a string.
640
makeJobIdS :: (Monad m) => String -> m JobId
641
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
642

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

    
653
instance JSON.JSON JobId where
654
  showJSON = JSON.showJSON . fromJobId
655
  readJSON = parseJobId
656

    
657
-- | Relative job ID type alias.
658
type RelativeJobId = Negative Int
659

    
660
-- | Job ID dependency.
661
data JobIdDep = JobDepRelative RelativeJobId
662
              | JobDepAbsolute JobId
663
                deriving (Show, Eq)
664

    
665
instance JSON.JSON JobIdDep where
666
  showJSON (JobDepRelative i) = showJSON i
667
  showJSON (JobDepAbsolute i) = showJSON i
668
  readJSON v =
669
    case JSON.readJSON v::JSON.Result (Negative Int) of
670
      -- first try relative dependency, usually most common
671
      JSON.Ok r -> return $ JobDepRelative r
672
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
673

    
674
-- | Job Dependency type.
675
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
676
                     deriving (Show, Eq)
677

    
678
instance JSON JobDependency where
679
  showJSON (JobDependency dep status) = showJSON (dep, status)
680
  readJSON = liftM (uncurry JobDependency) . readJSON
681

    
682
-- | Valid opcode priorities for submit.
683
$(THH.declareIADT "OpSubmitPriority"
684
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
685
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
686
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
687
  ])
688
$(THH.makeJSONInstance ''OpSubmitPriority)
689

    
690
-- | Parse submit priorities from a string.
691
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
692
parseSubmitPriority "low"    = return OpPrioLow
693
parseSubmitPriority "normal" = return OpPrioNormal
694
parseSubmitPriority "high"   = return OpPrioHigh
695
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
696

    
697
-- | Format a submit priority as string.
698
fmtSubmitPriority :: OpSubmitPriority -> String
699
fmtSubmitPriority OpPrioLow    = "low"
700
fmtSubmitPriority OpPrioNormal = "normal"
701
fmtSubmitPriority OpPrioHigh   = "high"
702

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

    
715
-- | Type for the job message type.
716
$(THH.declareLADT ''String "ELogType"
717
  [ ("ELogMessage",      "message")
718
  , ("ELogRemoteImport", "remote-import")
719
  , ("ELogJqueueTest",   "jqueue-test")
720
  ])
721
$(THH.makeJSONInstance ''ELogType)
722

    
723
-- | Type of one element of a reason trail.
724
type ReasonElem = (String, String, Integer)
725

    
726
-- | Type representing a reason trail.
727
type ReasonTrail = [ReasonElem]
728

    
729
-- | The VTYPES, a mini-type system in Python.
730
$(THH.declareLADT ''String "VType"
731
  [ ("VTypeString",      "string")
732
  , ("VTypeMaybeString", "maybe-string")
733
  , ("VTypeBool",        "bool")
734
  , ("VTypeSize",        "size")
735
  , ("VTypeInt",         "int")
736
  ])
737
$(THH.makeJSONInstance ''VType)
738

    
739
instance THH.PyValue VType where
740
  showValue = THH.showValue . vTypeToRaw
741

    
742
-- * Node role type
743

    
744
$(THH.declareLADT ''String "NodeRole"
745
  [ ("NROffline",   "O")
746
  , ("NRDrained",   "D")
747
  , ("NRRegular",   "R")
748
  , ("NRCandidate", "C")
749
  , ("NRMaster",    "M")
750
  ])
751
$(THH.makeJSONInstance ''NodeRole)
752

    
753
-- | The description of the node role.
754
roleDescription :: NodeRole -> String
755
roleDescription NROffline   = "offline"
756
roleDescription NRDrained   = "drained"
757
roleDescription NRRegular   = "regular"
758
roleDescription NRCandidate = "master candidate"
759
roleDescription NRMaster    = "master"
760

    
761
-- * Disk types
762

    
763
$(THH.declareLADT ''String "DiskMode"
764
  [ ("DiskRdOnly", "ro")
765
  , ("DiskRdWr",   "rw")
766
  ])
767
$(THH.makeJSONInstance ''DiskMode)
768

    
769
-- | The persistent block driver type. Currently only one type is allowed.
770
$(THH.declareLADT ''String "BlockDriver"
771
  [ ("BlockDrvManual", "manual")
772
  ])
773
$(THH.makeJSONInstance ''BlockDriver)
774

    
775
-- * Instance types
776

    
777
$(THH.declareLADT ''String "AdminState"
778
  [ ("AdminOffline", "offline")
779
  , ("AdminDown",    "down")
780
  , ("AdminUp",      "up")
781
  ])
782
$(THH.makeJSONInstance ''AdminState)
783

    
784
-- * Storage field type
785

    
786
$(THH.declareLADT ''String "StorageField"
787
  [ ( "SFUsed",        "used")
788
  , ( "SFName",        "name")
789
  , ( "SFAllocatable", "allocatable")
790
  , ( "SFFree",        "free")
791
  , ( "SFSize",        "size")
792
  ])
793
$(THH.makeJSONInstance ''StorageField)
794

    
795
-- * Disk access protocol
796

    
797
$(THH.declareLADT ''String "DiskAccessMode"
798
  [ ( "DiskUserspace",   "userspace")
799
  , ( "DiskKernelspace", "kernelspace")
800
  ])
801
$(THH.makeJSONInstance ''DiskAccessMode)
802

    
803
-- | Local disk status
804
--
805
-- Python code depends on:
806
--   DiskStatusOk < DiskStatusUnknown < DiskStatusFaulty
807
$(THH.declareILADT "LocalDiskStatus"
808
  [ ("DiskStatusFaulty",  3)
809
  , ("DiskStatusOk",      1)
810
  , ("DiskStatusUnknown", 2)
811
  ])
812

    
813
localDiskStatusName :: LocalDiskStatus -> String
814
localDiskStatusName DiskStatusFaulty = "faulty"
815
localDiskStatusName DiskStatusOk = "ok"
816
localDiskStatusName DiskStatusUnknown = "unknown"
817

    
818
-- | Replace disks type.
819
$(THH.declareLADT ''String "ReplaceDisksMode"
820
  [ -- Replace disks on primary
821
    ("ReplaceOnPrimary",    "replace_on_primary")
822
    -- Replace disks on secondary
823
  , ("ReplaceOnSecondary",  "replace_on_secondary")
824
    -- Change secondary node
825
  , ("ReplaceNewSecondary", "replace_new_secondary")
826
  , ("ReplaceAuto",         "replace_auto")
827
  ])
828
$(THH.makeJSONInstance ''ReplaceDisksMode)
829

    
830
-- | Basic timeouts for RPC calls.
831
$(THH.declareILADT "RpcTimeout"
832
  [ ("Urgent",    60)       -- 1 minute
833
  , ("Fast",      5 * 60)   -- 5 minutes
834
  , ("Normal",    15 * 60)  -- 15 minutes
835
  , ("Slow",      3600)     -- 1 hour
836
  , ("FourHours", 4 * 3600) -- 4 hours
837
  , ("OneDay",    86400)    -- 1 day
838
  ])
839

    
840
$(THH.declareLADT ''String "ImportExportCompression"
841
  [ -- No compression
842
    ("None", "none")
843
    -- gzip compression
844
  , ("GZip", "gzip")
845
  ])
846
$(THH.makeJSONInstance ''ImportExportCompression)
847

    
848
instance THH.PyValue ImportExportCompression where
849
  showValue = THH.showValue . importExportCompressionToRaw