Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 9b9e088c

History | View | Annotate | Download (24.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common Ganeti types.
4

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

    
10
-}
11

    
12
{-
13

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

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

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

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

    
31
-}
32

    
33
module Ganeti.Types
34
  ( AllocPolicy(..)
35
  , allocPolicyFromRaw
36
  , allocPolicyToRaw
37
  , InstanceStatus(..)
38
  , instanceStatusFromRaw
39
  , instanceStatusToRaw
40
  , DiskTemplate(..)
41
  , diskTemplateToRaw
42
  , diskTemplateFromRaw
43
  , TagKind(..)
44
  , tagKindToRaw
45
  , tagKindFromRaw
46
  , NonNegative
47
  , fromNonNegative
48
  , mkNonNegative
49
  , Positive
50
  , fromPositive
51
  , mkPositive
52
  , Negative
53
  , fromNegative
54
  , mkNegative
55
  , NonEmpty
56
  , fromNonEmpty
57
  , mkNonEmpty
58
  , NonEmptyString
59
  , QueryResultCode
60
  , IPv4Address
61
  , mkIPv4Address
62
  , IPv4Network
63
  , mkIPv4Network
64
  , IPv6Address
65
  , mkIPv6Address
66
  , IPv6Network
67
  , mkIPv6Network
68
  , MigrationMode(..)
69
  , migrationModeToRaw
70
  , VerifyOptionalChecks(..)
71
  , verifyOptionalChecksToRaw
72
  , DdmSimple(..)
73
  , DdmFull(..)
74
  , ddmFullToRaw
75
  , CVErrorCode(..)
76
  , cVErrorCodeToRaw
77
  , Hypervisor(..)
78
  , hypervisorToRaw
79
  , OobCommand(..)
80
  , oobCommandToRaw
81
  , OobStatus(..)
82
  , oobStatusToRaw
83
  , StorageType(..)
84
  , storageTypeToRaw
85
  , EvacMode(..)
86
  , evacModeToRaw
87
  , FileDriver(..)
88
  , fileDriverToRaw
89
  , InstCreateMode(..)
90
  , instCreateModeToRaw
91
  , RebootType(..)
92
  , rebootTypeToRaw
93
  , ExportMode(..)
94
  , exportModeToRaw
95
  , IAllocatorTestDir(..)
96
  , iAllocatorTestDirToRaw
97
  , IAllocatorMode(..)
98
  , iAllocatorModeToRaw
99
  , NICMode(..)
100
  , nICModeToRaw
101
  , JobStatus(..)
102
  , jobStatusToRaw
103
  , jobStatusFromRaw
104
  , FinalizedJobStatus(..)
105
  , finalizedJobStatusToRaw
106
  , JobId
107
  , fromJobId
108
  , makeJobId
109
  , makeJobIdS
110
  , RelativeJobId
111
  , JobIdDep(..)
112
  , JobDependency(..)
113
  , 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
  ) where
147

    
148
import Control.Monad (liftM)
149
import qualified Text.JSON as JSON
150
import Text.JSON (JSON, readJSON, showJSON)
151
import Data.Ratio (numerator, denominator)
152

    
153
import qualified Ganeti.ConstantUtils as ConstantUtils
154
import Ganeti.JSON
155
import qualified Ganeti.THH as THH
156
import Ganeti.Utils
157

    
158
-- * Generic types
159

    
160
-- | Type that holds a non-negative value.
161
newtype NonNegative a = NonNegative { fromNonNegative :: a }
162
  deriving (Show, Eq)
163

    
164
-- | Smart constructor for 'NonNegative'.
165
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
166
mkNonNegative i | i >= 0 = return (NonNegative i)
167
                | otherwise = fail $ "Invalid value for non-negative type '" ++
168
                              show i ++ "'"
169

    
170
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
171
  showJSON = JSON.showJSON . fromNonNegative
172
  readJSON v = JSON.readJSON v >>= mkNonNegative
173

    
174
-- | Type that holds a positive value.
175
newtype Positive a = Positive { fromPositive :: a }
176
  deriving (Show, Eq)
177

    
178
-- | Smart constructor for 'Positive'.
179
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
180
mkPositive i | i > 0 = return (Positive i)
181
             | otherwise = fail $ "Invalid value for positive type '" ++
182
                           show i ++ "'"
183

    
184
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
185
  showJSON = JSON.showJSON . fromPositive
186
  readJSON v = JSON.readJSON v >>= mkPositive
187

    
188
-- | Type that holds a negative value.
189
newtype Negative a = Negative { fromNegative :: a }
190
  deriving (Show, Eq)
191

    
192
-- | Smart constructor for 'Negative'.
193
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
194
mkNegative i | i < 0 = return (Negative i)
195
             | otherwise = fail $ "Invalid value for negative type '" ++
196
                           show i ++ "'"
197

    
198
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
199
  showJSON = JSON.showJSON . fromNegative
200
  readJSON v = JSON.readJSON v >>= mkNegative
201

    
202
-- | Type that holds a non-null list.
203
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
204
  deriving (Show, Eq)
205

    
206
-- | Smart constructor for 'NonEmpty'.
207
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
208
mkNonEmpty [] = fail "Received empty value for non-empty list"
209
mkNonEmpty xs = return (NonEmpty xs)
210

    
211
instance (Eq a, Ord a) => Ord (NonEmpty a) where
212
  NonEmpty { fromNonEmpty = x1 } `compare` NonEmpty { fromNonEmpty = x2 } =
213
    x1 `compare` x2
214

    
215
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
216
  showJSON = JSON.showJSON . fromNonEmpty
217
  readJSON v = JSON.readJSON v >>= mkNonEmpty
218

    
219
-- | A simple type alias for non-empty strings.
220
type NonEmptyString = NonEmpty Char
221

    
222
type QueryResultCode = Int
223

    
224
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
225
  deriving (Show, Eq)
226

    
227
-- FIXME: this should check that 'address' is a valid ip
228
mkIPv4Address :: Monad m => String -> m IPv4Address
229
mkIPv4Address address =
230
  return IPv4Address { fromIPv4Address = address }
231

    
232
instance JSON.JSON IPv4Address where
233
  showJSON = JSON.showJSON . fromIPv4Address
234
  readJSON v = JSON.readJSON v >>= mkIPv4Address
235

    
236
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
237
  deriving (Show, Eq)
238

    
239
-- FIXME: this should check that 'address' is a valid ip
240
mkIPv4Network :: Monad m => String -> m IPv4Network
241
mkIPv4Network address =
242
  return IPv4Network { fromIPv4Network = address }
243

    
244
instance JSON.JSON IPv4Network where
245
  showJSON = JSON.showJSON . fromIPv4Network
246
  readJSON v = JSON.readJSON v >>= mkIPv4Network
247

    
248
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
249
  deriving (Show, Eq)
250

    
251
-- FIXME: this should check that 'address' is a valid ip
252
mkIPv6Address :: Monad m => String -> m IPv6Address
253
mkIPv6Address address =
254
  return IPv6Address { fromIPv6Address = address }
255

    
256
instance JSON.JSON IPv6Address where
257
  showJSON = JSON.showJSON . fromIPv6Address
258
  readJSON v = JSON.readJSON v >>= mkIPv6Address
259

    
260
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
261
  deriving (Show, Eq)
262

    
263
-- FIXME: this should check that 'address' is a valid ip
264
mkIPv6Network :: Monad m => String -> m IPv6Network
265
mkIPv6Network address =
266
  return IPv6Network { fromIPv6Network = address }
267

    
268
instance JSON.JSON IPv6Network where
269
  showJSON = JSON.showJSON . fromIPv6Network
270
  readJSON v = JSON.readJSON v >>= mkIPv6Network
271

    
272
-- * Ganeti types
273

    
274
-- | Instance disk template type.
275
$(THH.declareLADT ''String "DiskTemplate"
276
       [ ("DTDiskless",   "diskless")
277
       , ("DTFile",       "file")
278
       , ("DTSharedFile", "sharedfile")
279
       , ("DTPlain",      "plain")
280
       , ("DTBlock",      "blockdev")
281
       , ("DTDrbd8",      "drbd")
282
       , ("DTRbd",        "rbd")
283
       , ("DTExt",        "ext")
284
       ])
285
$(THH.makeJSONInstance ''DiskTemplate)
286

    
287
instance THH.PyValue DiskTemplate where
288
  showValue = show . diskTemplateToRaw
289

    
290
instance HasStringRepr DiskTemplate where
291
  fromStringRepr = diskTemplateFromRaw
292
  toStringRepr = diskTemplateToRaw
293

    
294
-- | Data type representing what items the tag operations apply to.
295
$(THH.declareLADT ''String "TagKind"
296
  [ ("TagKindInstance", "instance")
297
  , ("TagKindNode",     "node")
298
  , ("TagKindGroup",    "nodegroup")
299
  , ("TagKindCluster",  "cluster")
300
  , ("TagKindNetwork",  "network")
301
  ])
302
$(THH.makeJSONInstance ''TagKind)
303

    
304
-- | The Group allocation policy type.
305
--
306
-- Note that the order of constructors is important as the automatic
307
-- Ord instance will order them in the order they are defined, so when
308
-- changing this data type be careful about the interaction with the
309
-- desired sorting order.
310
$(THH.declareLADT ''String "AllocPolicy"
311
       [ ("AllocPreferred",   "preferred")
312
       , ("AllocLastResort",  "last_resort")
313
       , ("AllocUnallocable", "unallocable")
314
       ])
315
$(THH.makeJSONInstance ''AllocPolicy)
316

    
317
-- | The Instance real state type. FIXME: this could be improved to
318
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
319
$(THH.declareLADT ''String "InstanceStatus"
320
       [ ("StatusDown",    "ADMIN_down")
321
       , ("StatusOffline", "ADMIN_offline")
322
       , ("ErrorDown",     "ERROR_down")
323
       , ("ErrorUp",       "ERROR_up")
324
       , ("NodeDown",      "ERROR_nodedown")
325
       , ("NodeOffline",   "ERROR_nodeoffline")
326
       , ("Running",       "running")
327
       , ("WrongNode",     "ERROR_wrongnode")
328
       ])
329
$(THH.makeJSONInstance ''InstanceStatus)
330

    
331
-- | Migration mode.
332
$(THH.declareLADT ''String "MigrationMode"
333
     [ ("MigrationLive",    "live")
334
     , ("MigrationNonLive", "non-live")
335
     ])
336
$(THH.makeJSONInstance ''MigrationMode)
337

    
338
-- | Verify optional checks.
339
$(THH.declareLADT ''String "VerifyOptionalChecks"
340
     [ ("VerifyNPlusOneMem", "nplusone_mem")
341
     ])
342
$(THH.makeJSONInstance ''VerifyOptionalChecks)
343

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

    
388
-- | Dynamic device modification, just add\/remove version.
389
$(THH.declareLADT ''String "DdmSimple"
390
     [ ("DdmSimpleAdd",    "add")
391
     , ("DdmSimpleRemove", "remove")
392
     ])
393
$(THH.makeJSONInstance ''DdmSimple)
394

    
395
-- | Dynamic device modification, all operations version.
396
$(THH.declareLADT ''String "DdmFull"
397
     [ ("DdmFullAdd",    "add")
398
     , ("DdmFullRemove", "remove")
399
     , ("DdmFullModify", "modify")
400
     ])
401
$(THH.makeJSONInstance ''DdmFull)
402

    
403
-- | Hypervisor type definitions.
404
$(THH.declareLADT ''String "Hypervisor"
405
  [ ("Kvm",    "kvm")
406
  , ("XenPvm", "xen-pvm")
407
  , ("Chroot", "chroot")
408
  , ("XenHvm", "xen-hvm")
409
  , ("Lxc",    "lxc")
410
  , ("Fake",   "fake")
411
  ])
412
$(THH.makeJSONInstance ''Hypervisor)
413

    
414
instance THH.PyValue Hypervisor where
415
  showValue = show . hypervisorToRaw
416

    
417
-- | Oob command type.
418
$(THH.declareLADT ''String "OobCommand"
419
  [ ("OobHealth",      "health")
420
  , ("OobPowerCycle",  "power-cycle")
421
  , ("OobPowerOff",    "power-off")
422
  , ("OobPowerOn",     "power-on")
423
  , ("OobPowerStatus", "power-status")
424
  ])
425
$(THH.makeJSONInstance ''OobCommand)
426

    
427
-- | Oob command status
428
$(THH.declareLADT ''String "OobStatus"
429
  [ ("OobStatusCritical", "CRITICAL")
430
  , ("OobStatusOk",       "OK")
431
  , ("OobStatusUnknown",  "UNKNOWN")
432
  , ("OobStatusWarning",  "WARNING")
433
  ])
434
$(THH.makeJSONInstance ''OobStatus)
435

    
436
-- | Storage type.
437
$(THH.declareLADT ''String "StorageType"
438
  [ ("StorageFile", "file")
439
  , ("StorageLvmPv", "lvm-pv")
440
  , ("StorageLvmVg", "lvm-vg")
441
  , ("StorageDiskless", "diskless")
442
  , ("StorageBlock", "blockdev")
443
  , ("StorageRados", "rados")
444
  , ("StorageExt", "ext")
445
  ])
446
$(THH.makeJSONInstance ''StorageType)
447

    
448
-- | Storage keys are identifiers for storage units. Their content varies
449
-- depending on the storage type, for example a storage key for LVM storage
450
-- is the volume group name.
451
type StorageKey = String
452

    
453
-- | Storage parameters
454
type SPExclusiveStorage = Bool
455

    
456
-- | Storage units without storage-type-specific parameters
457
data StorageUnitRaw = SURaw StorageType StorageKey
458

    
459
-- | Full storage unit with storage-type-specific parameters
460
data StorageUnit = SUFile StorageKey
461
                 | SULvmPv StorageKey SPExclusiveStorage
462
                 | SULvmVg StorageKey SPExclusiveStorage
463
                 | SUDiskless StorageKey
464
                 | SUBlock StorageKey
465
                 | SURados StorageKey
466
                 | SUExt StorageKey
467
                 deriving (Eq)
468

    
469
instance Show StorageUnit where
470
  show (SUFile key) = showSUSimple StorageFile key
471
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
472
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
473
  show (SUDiskless key) = showSUSimple StorageDiskless key
474
  show (SUBlock key) = showSUSimple StorageBlock key
475
  show (SURados key) = showSUSimple StorageRados key
476
  show (SUExt key) = showSUSimple StorageExt key
477

    
478
instance JSON StorageUnit where
479
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
480
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
481
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
482
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
483
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
484
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
485
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
486
-- FIXME: add readJSON implementation
487
  readJSON = fail "Not implemented"
488

    
489
-- | Composes a string representation of storage types without
490
-- storage parameters
491
showSUSimple :: StorageType -> StorageKey -> String
492
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
493

    
494
-- | Composes a string representation of the LVM storage types
495
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
496
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
497

    
498
-- | Mapping from disk templates to storage types
499
-- FIXME: This is semantically the same as the constant
500
-- C.diskTemplatesStorageType, remove this when python constants
501
-- are generated from haskell constants
502
diskTemplateToStorageType :: DiskTemplate -> StorageType
503
diskTemplateToStorageType DTExt = StorageExt
504
diskTemplateToStorageType DTFile = StorageFile
505
diskTemplateToStorageType DTSharedFile = StorageFile
506
diskTemplateToStorageType DTDrbd8 = StorageLvmVg
507
diskTemplateToStorageType DTPlain = StorageLvmVg
508
diskTemplateToStorageType DTRbd = StorageRados
509
diskTemplateToStorageType DTDiskless = StorageDiskless
510
diskTemplateToStorageType DTBlock = StorageBlock
511

    
512
-- | Equips a raw storage unit with its parameters
513
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
514
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
515
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
516
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
517
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
518
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
519
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
520
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
521

    
522
-- | Node evac modes.
523
--
524
-- This is part of the 'IAllocator' interface and it is used, for
525
-- example, in 'Ganeti.HTools.Loader.RqType'.  However, it must reside
526
-- in this module, and not in 'Ganeti.HTools.Types', because it is
527
-- also used by 'Ganeti.HsConstants'.
528
$(THH.declareLADT ''String "EvacMode"
529
  [ ("ChangePrimary",   "primary-only")
530
  , ("ChangeSecondary", "secondary-only")
531
  , ("ChangeAll",       "all")
532
  ])
533
$(THH.makeJSONInstance ''EvacMode)
534

    
535
-- | The file driver type.
536
$(THH.declareLADT ''String "FileDriver"
537
  [ ("FileLoop",   "loop")
538
  , ("FileBlktap", "blktap")
539
  ])
540
$(THH.makeJSONInstance ''FileDriver)
541

    
542
-- | The instance create mode.
543
$(THH.declareLADT ''String "InstCreateMode"
544
  [ ("InstCreate",       "create")
545
  , ("InstImport",       "import")
546
  , ("InstRemoteImport", "remote-import")
547
  ])
548
$(THH.makeJSONInstance ''InstCreateMode)
549

    
550
-- | Reboot type.
551
$(THH.declareLADT ''String "RebootType"
552
  [ ("RebootSoft", "soft")
553
  , ("RebootHard", "hard")
554
  , ("RebootFull", "full")
555
  ])
556
$(THH.makeJSONInstance ''RebootType)
557

    
558
-- | Export modes.
559
$(THH.declareLADT ''String "ExportMode"
560
  [ ("ExportModeLocal",  "local")
561
  , ("ExportModeRemote", "remote")
562
  ])
563
$(THH.makeJSONInstance ''ExportMode)
564

    
565
-- | IAllocator run types (OpTestIAllocator).
566
$(THH.declareLADT ''String "IAllocatorTestDir"
567
  [ ("IAllocatorDirIn",  "in")
568
  , ("IAllocatorDirOut", "out")
569
  ])
570
$(THH.makeJSONInstance ''IAllocatorTestDir)
571

    
572
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
573
$(THH.declareLADT ''String "IAllocatorMode"
574
  [ ("IAllocatorAlloc",       "allocate")
575
  , ("IAllocatorMultiAlloc",  "multi-allocate")
576
  , ("IAllocatorReloc",       "relocate")
577
  , ("IAllocatorNodeEvac",    "node-evacuate")
578
  , ("IAllocatorChangeGroup", "change-group")
579
  ])
580
$(THH.makeJSONInstance ''IAllocatorMode)
581

    
582
-- | Network mode.
583
$(THH.declareLADT ''String "NICMode"
584
  [ ("NMBridged", "bridged")
585
  , ("NMRouted",  "routed")
586
  , ("NMOvs",     "openvswitch")
587
  , ("NMPool",    "pool")
588
  ])
589
$(THH.makeJSONInstance ''NICMode)
590

    
591
-- | The JobStatus data type. Note that this is ordered especially
592
-- such that greater\/lesser comparison on values of this type makes
593
-- sense.
594
$(THH.declareLADT ''String "JobStatus"
595
  [ ("JOB_STATUS_QUEUED",    "queued")
596
  , ("JOB_STATUS_WAITING",   "waiting")
597
  , ("JOB_STATUS_CANCELING", "canceling")
598
  , ("JOB_STATUS_RUNNING",   "running")
599
  , ("JOB_STATUS_CANCELED",  "canceled")
600
  , ("JOB_STATUS_SUCCESS",   "success")
601
  , ("JOB_STATUS_ERROR",     "error")
602
  ])
603
$(THH.makeJSONInstance ''JobStatus)
604

    
605
-- | Finalized job status.
606
$(THH.declareLADT ''String "FinalizedJobStatus"
607
  [ ("JobStatusCanceled",   "canceled")
608
  , ("JobStatusSuccessful", "success")
609
  , ("JobStatusFailed",     "error")
610
  ])
611
$(THH.makeJSONInstance ''FinalizedJobStatus)
612

    
613
-- | The Ganeti job type.
614
newtype JobId = JobId { fromJobId :: Int }
615
  deriving (Show, Eq)
616

    
617
-- | Builds a job ID.
618
makeJobId :: (Monad m) => Int -> m JobId
619
makeJobId i | i >= 0 = return $ JobId i
620
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
621

    
622
-- | Builds a job ID from a string.
623
makeJobIdS :: (Monad m) => String -> m JobId
624
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
625

    
626
-- | Parses a job ID.
627
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
628
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
629
parseJobId (JSON.JSRational _ x) =
630
  if denominator x /= 1
631
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
632
    -- FIXME: potential integer overflow here on 32-bit platforms
633
    else makeJobId . fromIntegral . numerator $ x
634
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
635

    
636
instance JSON.JSON JobId where
637
  showJSON = JSON.showJSON . fromJobId
638
  readJSON = parseJobId
639

    
640
-- | Relative job ID type alias.
641
type RelativeJobId = Negative Int
642

    
643
-- | Job ID dependency.
644
data JobIdDep = JobDepRelative RelativeJobId
645
              | JobDepAbsolute JobId
646
                deriving (Show, Eq)
647

    
648
instance JSON.JSON JobIdDep where
649
  showJSON (JobDepRelative i) = showJSON i
650
  showJSON (JobDepAbsolute i) = showJSON i
651
  readJSON v =
652
    case JSON.readJSON v::JSON.Result (Negative Int) of
653
      -- first try relative dependency, usually most common
654
      JSON.Ok r -> return $ JobDepRelative r
655
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
656

    
657
-- | Job Dependency type.
658
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
659
                     deriving (Show, Eq)
660

    
661
instance JSON JobDependency where
662
  showJSON (JobDependency dep status) = showJSON (dep, status)
663
  readJSON = liftM (uncurry JobDependency) . readJSON
664

    
665
-- | Valid opcode priorities for submit.
666
$(THH.declareIADT "OpSubmitPriority"
667
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
668
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
669
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
670
  ])
671
$(THH.makeJSONInstance ''OpSubmitPriority)
672

    
673
-- | Parse submit priorities from a string.
674
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
675
parseSubmitPriority "low"    = return OpPrioLow
676
parseSubmitPriority "normal" = return OpPrioNormal
677
parseSubmitPriority "high"   = return OpPrioHigh
678
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
679

    
680
-- | Format a submit priority as string.
681
fmtSubmitPriority :: OpSubmitPriority -> String
682
fmtSubmitPriority OpPrioLow    = "low"
683
fmtSubmitPriority OpPrioNormal = "normal"
684
fmtSubmitPriority OpPrioHigh   = "high"
685

    
686
-- | Our ADT for the OpCode status at runtime (while in a job).
687
$(THH.declareLADT ''String "OpStatus"
688
  [ ("OP_STATUS_QUEUED",    "queued")
689
  , ("OP_STATUS_WAITING",   "waiting")
690
  , ("OP_STATUS_CANCELING", "canceling")
691
  , ("OP_STATUS_RUNNING",   "running")
692
  , ("OP_STATUS_CANCELED",  "canceled")
693
  , ("OP_STATUS_SUCCESS",   "success")
694
  , ("OP_STATUS_ERROR",     "error")
695
  ])
696
$(THH.makeJSONInstance ''OpStatus)
697

    
698
-- | Type for the job message type.
699
$(THH.declareLADT ''String "ELogType"
700
  [ ("ELogMessage",      "message")
701
  , ("ELogRemoteImport", "remote-import")
702
  , ("ELogJqueueTest",   "jqueue-test")
703
  ])
704
$(THH.makeJSONInstance ''ELogType)
705

    
706
-- | Type of one element of a reason trail.
707
type ReasonElem = (String, String, Integer)
708

    
709
-- | Type representing a reason trail.
710
type ReasonTrail = [ReasonElem]
711

    
712
-- | The VTYPES, a mini-type system in Python.
713
$(THH.declareLADT ''String "VType"
714
  [ ("VTypeString",      "string")
715
  , ("VTypeMaybeString", "maybe-string")
716
  , ("VTypeBool",        "bool")
717
  , ("VTypeSize",        "size")
718
  , ("VTypeInt",         "int")
719
  ])
720
$(THH.makeJSONInstance ''VType)
721

    
722
-- * Node role type
723

    
724
$(THH.declareLADT ''String "NodeRole"
725
  [ ("NROffline",   "O")
726
  , ("NRDrained",   "D")
727
  , ("NRRegular",   "R")
728
  , ("NRCandidate", "C")
729
  , ("NRMaster",    "M")
730
  ])
731
$(THH.makeJSONInstance ''NodeRole)
732

    
733
-- | The description of the node role.
734
roleDescription :: NodeRole -> String
735
roleDescription NROffline   = "offline"
736
roleDescription NRDrained   = "drained"
737
roleDescription NRRegular   = "regular"
738
roleDescription NRCandidate = "master candidate"
739
roleDescription NRMaster    = "master"
740

    
741
-- * Disk types
742

    
743
$(THH.declareLADT ''String "DiskMode"
744
  [ ("DiskRdOnly", "ro")
745
  , ("DiskRdWr",   "rw")
746
  ])
747
$(THH.makeJSONInstance ''DiskMode)
748

    
749
-- | The persistent block driver type. Currently only one type is allowed.
750
$(THH.declareLADT ''String "BlockDriver"
751
  [ ("BlockDrvManual", "manual")
752
  ])
753
$(THH.makeJSONInstance ''BlockDriver)
754

    
755
-- * Instance types
756

    
757
$(THH.declareLADT ''String "AdminState"
758
  [ ("AdminOffline", "offline")
759
  , ("AdminDown",    "down")
760
  , ("AdminUp",      "up")
761
  ])
762
$(THH.makeJSONInstance ''AdminState)
763

    
764
-- * Storage field type
765

    
766
$(THH.declareLADT ''String "StorageField"
767
  [ ( "SFUsed",        "used")
768
  , ( "SFName",        "name")
769
  , ( "SFAllocatable", "allocatable")
770
  , ( "SFFree",        "free")
771
  , ( "SFSize",        "size")
772
  ])
773
$(THH.makeJSONInstance ''StorageField)
774

    
775
-- * Disk access protocol
776

    
777
$(THH.declareLADT ''String "DiskAccessMode"
778
  [ ( "DiskUserspace",   "userspace")
779
  , ( "DiskKernelspace", "kernelspace")
780
  ])
781
$(THH.makeJSONInstance ''DiskAccessMode)