Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 4475d529

History | View | Annotate | Download (22.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Some common Ganeti types.
4

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

    
10
-}
11

    
12
{-
13

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

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

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

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

    
31
-}
32

    
33
module Ganeti.Types
34
  ( AllocPolicy(..)
35
  , allocPolicyFromRaw
36
  , allocPolicyToRaw
37
  , InstanceStatus(..)
38
  , instanceStatusFromRaw
39
  , instanceStatusToRaw
40
  , DiskTemplate(..)
41
  , diskTemplateToRaw
42
  , diskTemplateFromRaw
43
  , TagKind(..)
44
  , tagKindToRaw
45
  , tagKindFromRaw
46
  , NonNegative
47
  , fromNonNegative
48
  , mkNonNegative
49
  , Positive
50
  , fromPositive
51
  , mkPositive
52
  , Negative
53
  , fromNegative
54
  , mkNegative
55
  , NonEmpty
56
  , fromNonEmpty
57
  , mkNonEmpty
58
  , NonEmptyString
59
  , QueryResultCode
60
  , IPv4Address
61
  , mkIPv4Address
62
  , IPv4Network
63
  , mkIPv4Network
64
  , IPv6Address
65
  , mkIPv6Address
66
  , IPv6Network
67
  , mkIPv6Network
68
  , MigrationMode(..)
69
  , migrationModeToRaw
70
  , VerifyOptionalChecks(..)
71
  , verifyOptionalChecksToRaw
72
  , DdmSimple(..)
73
  , DdmFull(..)
74
  , ddmFullToRaw
75
  , CVErrorCode(..)
76
  , cVErrorCodeToRaw
77
  , Hypervisor(..)
78
  , hypervisorToRaw
79
  , OobCommand(..)
80
  , oobCommandToRaw
81
  , StorageType(..)
82
  , storageTypeToRaw
83
  , NodeEvacMode(..)
84
  , nodeEvacModeToRaw
85
  , FileDriver(..)
86
  , fileDriverToRaw
87
  , InstCreateMode(..)
88
  , instCreateModeToRaw
89
  , RebootType(..)
90
  , rebootTypeToRaw
91
  , ExportMode(..)
92
  , exportModeToRaw
93
  , IAllocatorTestDir(..)
94
  , iAllocatorTestDirToRaw
95
  , IAllocatorMode(..)
96
  , iAllocatorModeToRaw
97
  , NICMode(..)
98
  , nICModeToRaw
99
  , JobStatus(..)
100
  , jobStatusToRaw
101
  , jobStatusFromRaw
102
  , FinalizedJobStatus(..)
103
  , finalizedJobStatusToRaw
104
  , JobId
105
  , fromJobId
106
  , makeJobId
107
  , makeJobIdS
108
  , RelativeJobId
109
  , JobIdDep(..)
110
  , JobDependency(..)
111
  , OpSubmitPriority(..)
112
  , opSubmitPriorityToRaw
113
  , parseSubmitPriority
114
  , fmtSubmitPriority
115
  , OpStatus(..)
116
  , opStatusToRaw
117
  , opStatusFromRaw
118
  , ELogType(..)
119
  , eLogTypeToRaw
120
  , ReasonElem
121
  , ReasonTrail
122
  , StorageUnit(..)
123
  , StorageUnitRaw(..)
124
  , StorageKey
125
  , addParamsToStorageUnit
126
  , diskTemplateToStorageType
127
  ) where
128

    
129
import Control.Monad (liftM)
130
import qualified Text.JSON as JSON
131
import Text.JSON (JSON, readJSON, showJSON)
132
import Data.Ratio (numerator, denominator)
133

    
134
import qualified Ganeti.ConstantUtils as ConstantUtils
135
import Ganeti.JSON
136
import qualified Ganeti.THH as THH
137
import Ganeti.Utils
138

    
139
-- * Generic types
140

    
141
-- | Type that holds a non-negative value.
142
newtype NonNegative a = NonNegative { fromNonNegative :: a }
143
  deriving (Show, Eq)
144

    
145
-- | Smart constructor for 'NonNegative'.
146
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
147
mkNonNegative i | i >= 0 = return (NonNegative i)
148
                | otherwise = fail $ "Invalid value for non-negative type '" ++
149
                              show i ++ "'"
150

    
151
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
152
  showJSON = JSON.showJSON . fromNonNegative
153
  readJSON v = JSON.readJSON v >>= mkNonNegative
154

    
155
-- | Type that holds a positive value.
156
newtype Positive a = Positive { fromPositive :: a }
157
  deriving (Show, Eq)
158

    
159
-- | Smart constructor for 'Positive'.
160
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
161
mkPositive i | i > 0 = return (Positive i)
162
             | otherwise = fail $ "Invalid value for positive type '" ++
163
                           show i ++ "'"
164

    
165
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
166
  showJSON = JSON.showJSON . fromPositive
167
  readJSON v = JSON.readJSON v >>= mkPositive
168

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

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

    
179
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
180
  showJSON = JSON.showJSON . fromNegative
181
  readJSON v = JSON.readJSON v >>= mkNegative
182

    
183
-- | Type that holds a non-null list.
184
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
185
  deriving (Show, Eq)
186

    
187
-- | Smart constructor for 'NonEmpty'.
188
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
189
mkNonEmpty [] = fail "Received empty value for non-empty list"
190
mkNonEmpty xs = return (NonEmpty xs)
191

    
192
instance (Eq a, Ord a) => Ord (NonEmpty a) where
193
  NonEmpty { fromNonEmpty = x1 } `compare` NonEmpty { fromNonEmpty = x2 } =
194
    x1 `compare` x2
195

    
196
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
197
  showJSON = JSON.showJSON . fromNonEmpty
198
  readJSON v = JSON.readJSON v >>= mkNonEmpty
199

    
200
-- | A simple type alias for non-empty strings.
201
type NonEmptyString = NonEmpty Char
202

    
203
type QueryResultCode = Int
204

    
205
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
206
  deriving (Show, Eq)
207

    
208
-- FIXME: this should check that 'address' is a valid ip
209
mkIPv4Address :: Monad m => String -> m IPv4Address
210
mkIPv4Address address =
211
  return IPv4Address { fromIPv4Address = address }
212

    
213
instance JSON.JSON IPv4Address where
214
  showJSON = JSON.showJSON . fromIPv4Address
215
  readJSON v = JSON.readJSON v >>= mkIPv4Address
216

    
217
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
218
  deriving (Show, Eq)
219

    
220
-- FIXME: this should check that 'address' is a valid ip
221
mkIPv4Network :: Monad m => String -> m IPv4Network
222
mkIPv4Network address =
223
  return IPv4Network { fromIPv4Network = address }
224

    
225
instance JSON.JSON IPv4Network where
226
  showJSON = JSON.showJSON . fromIPv4Network
227
  readJSON v = JSON.readJSON v >>= mkIPv4Network
228

    
229
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
230
  deriving (Show, Eq)
231

    
232
-- FIXME: this should check that 'address' is a valid ip
233
mkIPv6Address :: Monad m => String -> m IPv6Address
234
mkIPv6Address address =
235
  return IPv6Address { fromIPv6Address = address }
236

    
237
instance JSON.JSON IPv6Address where
238
  showJSON = JSON.showJSON . fromIPv6Address
239
  readJSON v = JSON.readJSON v >>= mkIPv6Address
240

    
241
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
242
  deriving (Show, Eq)
243

    
244
-- FIXME: this should check that 'address' is a valid ip
245
mkIPv6Network :: Monad m => String -> m IPv6Network
246
mkIPv6Network address =
247
  return IPv6Network { fromIPv6Network = address }
248

    
249
instance JSON.JSON IPv6Network where
250
  showJSON = JSON.showJSON . fromIPv6Network
251
  readJSON v = JSON.readJSON v >>= mkIPv6Network
252

    
253
-- * Ganeti types
254

    
255
-- | Instance disk template type.
256
$(THH.declareLADT ''String "DiskTemplate"
257
       [ ("DTDiskless",   "diskless")
258
       , ("DTFile",       "file")
259
       , ("DTSharedFile", "sharedfile")
260
       , ("DTPlain",      "plain")
261
       , ("DTBlock",      "blockdev")
262
       , ("DTDrbd8",      "drbd")
263
       , ("DTRbd",        "rbd")
264
       , ("DTExt",        "ext")
265
       ])
266
$(THH.makeJSONInstance ''DiskTemplate)
267

    
268
instance HasStringRepr DiskTemplate where
269
  fromStringRepr = diskTemplateFromRaw
270
  toStringRepr = diskTemplateToRaw
271

    
272
-- | Data type representing what items the tag operations apply to.
273
$(THH.declareLADT ''String "TagKind"
274
  [ ("TagKindInstance", "instance")
275
  , ("TagKindNode",     "node")
276
  , ("TagKindGroup",    "nodegroup")
277
  , ("TagKindCluster",  "cluster")
278
  , ("TagKindNetwork",  "network")
279
  ])
280
$(THH.makeJSONInstance ''TagKind)
281

    
282
-- | The Group allocation policy type.
283
--
284
-- Note that the order of constructors is important as the automatic
285
-- Ord instance will order them in the order they are defined, so when
286
-- changing this data type be careful about the interaction with the
287
-- desired sorting order.
288
$(THH.declareLADT ''String "AllocPolicy"
289
       [ ("AllocPreferred",   "preferred")
290
       , ("AllocLastResort",  "last_resort")
291
       , ("AllocUnallocable", "unallocable")
292
       ])
293
$(THH.makeJSONInstance ''AllocPolicy)
294

    
295
-- | The Instance real state type. FIXME: this could be improved to
296
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
297
$(THH.declareLADT ''String "InstanceStatus"
298
       [ ("StatusDown",    "ADMIN_down")
299
       , ("StatusOffline", "ADMIN_offline")
300
       , ("ErrorDown",     "ERROR_down")
301
       , ("ErrorUp",       "ERROR_up")
302
       , ("NodeDown",      "ERROR_nodedown")
303
       , ("NodeOffline",   "ERROR_nodeoffline")
304
       , ("Running",       "running")
305
       , ("WrongNode",     "ERROR_wrongnode")
306
       ])
307
$(THH.makeJSONInstance ''InstanceStatus)
308

    
309
-- | Migration mode.
310
$(THH.declareLADT ''String "MigrationMode"
311
     [ ("MigrationLive",    "live")
312
     , ("MigrationNonLive", "non-live")
313
     ])
314
$(THH.makeJSONInstance ''MigrationMode)
315

    
316
-- | Verify optional checks.
317
$(THH.declareLADT ''String "VerifyOptionalChecks"
318
     [ ("VerifyNPlusOneMem", "nplusone_mem")
319
     ])
320
$(THH.makeJSONInstance ''VerifyOptionalChecks)
321

    
322
-- | Cluster verify error codes.
323
$(THH.declareLADT ''String "CVErrorCode"
324
  [ ("CvECLUSTERCFG",                  "ECLUSTERCFG")
325
  , ("CvECLUSTERCERT",                 "ECLUSTERCERT")
326
  , ("CvECLUSTERFILECHECK",            "ECLUSTERFILECHECK")
327
  , ("CvECLUSTERDANGLINGNODES",        "ECLUSTERDANGLINGNODES")
328
  , ("CvECLUSTERDANGLINGINST",         "ECLUSTERDANGLINGINST")
329
  , ("CvEINSTANCEBADNODE",             "EINSTANCEBADNODE")
330
  , ("CvEINSTANCEDOWN",                "EINSTANCEDOWN")
331
  , ("CvEINSTANCELAYOUT",              "EINSTANCELAYOUT")
332
  , ("CvEINSTANCEMISSINGDISK",         "EINSTANCEMISSINGDISK")
333
  , ("CvEINSTANCEFAULTYDISK",          "EINSTANCEFAULTYDISK")
334
  , ("CvEINSTANCEWRONGNODE",           "EINSTANCEWRONGNODE")
335
  , ("CvEINSTANCESPLITGROUPS",         "EINSTANCESPLITGROUPS")
336
  , ("CvEINSTANCEPOLICY",              "EINSTANCEPOLICY")
337
  , ("CvEINSTANCEUNSUITABLENODE",      "EINSTANCEUNSUITABLENODE")
338
  , ("CvEINSTANCEMISSINGCFGPARAMETER", "EINSTANCEMISSINGCFGPARAMETER")
339
  , ("CvENODEDRBD",                    "ENODEDRBD")
340
  , ("CvENODEDRBDVERSION",             "ENODEDRBDVERSION")
341
  , ("CvENODEDRBDHELPER",              "ENODEDRBDHELPER")
342
  , ("CvENODEFILECHECK",               "ENODEFILECHECK")
343
  , ("CvENODEHOOKS",                   "ENODEHOOKS")
344
  , ("CvENODEHV",                      "ENODEHV")
345
  , ("CvENODELVM",                     "ENODELVM")
346
  , ("CvENODEN1",                      "ENODEN1")
347
  , ("CvENODENET",                     "ENODENET")
348
  , ("CvENODEOS",                      "ENODEOS")
349
  , ("CvENODEORPHANINSTANCE",          "ENODEORPHANINSTANCE")
350
  , ("CvENODEORPHANLV",                "ENODEORPHANLV")
351
  , ("CvENODERPC",                     "ENODERPC")
352
  , ("CvENODESSH",                     "ENODESSH")
353
  , ("CvENODEVERSION",                 "ENODEVERSION")
354
  , ("CvENODESETUP",                   "ENODESETUP")
355
  , ("CvENODETIME",                    "ENODETIME")
356
  , ("CvENODEOOBPATH",                 "ENODEOOBPATH")
357
  , ("CvENODEUSERSCRIPTS",             "ENODEUSERSCRIPTS")
358
  , ("CvENODEFILESTORAGEPATHS",        "ENODEFILESTORAGEPATHS")
359
  , ("CvENODEFILESTORAGEPATHUNUSABLE", "ENODEFILESTORAGEPATHUNUSABLE")
360
  , ("CvENODESHAREDFILESTORAGEPATHUNUSABLE",
361
     "ENODESHAREDFILESTORAGEPATHUNUSABLE")
362
  , ("CvEGROUPDIFFERENTPVSIZE",        "EGROUPDIFFERENTPVSIZE")
363
  ])
364
$(THH.makeJSONInstance ''CVErrorCode)
365

    
366
-- | Dynamic device modification, just add\/remove version.
367
$(THH.declareLADT ''String "DdmSimple"
368
     [ ("DdmSimpleAdd",    "add")
369
     , ("DdmSimpleRemove", "remove")
370
     ])
371
$(THH.makeJSONInstance ''DdmSimple)
372

    
373
-- | Dynamic device modification, all operations version.
374
$(THH.declareLADT ''String "DdmFull"
375
     [ ("DdmFullAdd",    "add")
376
     , ("DdmFullRemove", "remove")
377
     , ("DdmFullModify", "modify")
378
     ])
379
$(THH.makeJSONInstance ''DdmFull)
380

    
381
-- | Hypervisor type definitions.
382
$(THH.declareLADT ''String "Hypervisor"
383
  [ ("Kvm",    "kvm")
384
  , ("XenPvm", "xen-pvm")
385
  , ("Chroot", "chroot")
386
  , ("XenHvm", "xen-hvm")
387
  , ("Lxc",    "lxc")
388
  , ("Fake",   "fake")
389
  ])
390
$(THH.makeJSONInstance ''Hypervisor)
391

    
392
-- | Oob command type.
393
$(THH.declareLADT ''String "OobCommand"
394
  [ ("OobHealth",      "health")
395
  , ("OobPowerCycle",  "power-cycle")
396
  , ("OobPowerOff",    "power-off")
397
  , ("OobPowerOn",     "power-on")
398
  , ("OobPowerStatus", "power-status")
399
  ])
400
$(THH.makeJSONInstance ''OobCommand)
401

    
402
-- | Storage type.
403
$(THH.declareLADT ''String "StorageType"
404
  [ ("StorageFile", "file")
405
  , ("StorageLvmPv", "lvm-pv")
406
  , ("StorageLvmVg", "lvm-vg")
407
  , ("StorageDiskless", "diskless")
408
  , ("StorageBlock", "blockdev")
409
  , ("StorageRados", "rados")
410
  , ("StorageExt", "ext")
411
  ])
412
$(THH.makeJSONInstance ''StorageType)
413

    
414
-- | Storage keys are identifiers for storage units. Their content varies
415
-- depending on the storage type, for example a storage key for LVM storage
416
-- is the volume group name.
417
type StorageKey = String
418

    
419
-- | Storage parameters
420
type SPExclusiveStorage = Bool
421

    
422
-- | Storage units without storage-type-specific parameters
423
data StorageUnitRaw = SURaw StorageType StorageKey
424

    
425
-- | Full storage unit with storage-type-specific parameters
426
data StorageUnit = SUFile StorageKey
427
                 | SULvmPv StorageKey SPExclusiveStorage
428
                 | SULvmVg StorageKey SPExclusiveStorage
429
                 | SUDiskless StorageKey
430
                 | SUBlock StorageKey
431
                 | SURados StorageKey
432
                 | SUExt StorageKey
433
                 deriving (Eq)
434

    
435
instance Show StorageUnit where
436
  show (SUFile key) = showSUSimple StorageFile key
437
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
438
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
439
  show (SUDiskless key) = showSUSimple StorageDiskless key
440
  show (SUBlock key) = showSUSimple StorageBlock key
441
  show (SURados key) = showSUSimple StorageRados key
442
  show (SUExt key) = showSUSimple StorageExt key
443

    
444
instance JSON StorageUnit where
445
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
446
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
447
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
448
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
449
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
450
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
451
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
452
-- FIXME: add readJSON implementation
453
  readJSON = fail "Not implemented"
454

    
455
-- | Composes a string representation of storage types without
456
-- storage parameters
457
showSUSimple :: StorageType -> StorageKey -> String
458
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
459

    
460
-- | Composes a string representation of the LVM storage types
461
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
462
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
463

    
464
-- | Mapping from disk templates to storage types
465
-- FIXME: This is semantically the same as the constant
466
-- C.diskTemplatesStorageType, remove this when python constants
467
-- are generated from haskell constants
468
diskTemplateToStorageType :: DiskTemplate -> StorageType
469
diskTemplateToStorageType DTExt = StorageExt
470
diskTemplateToStorageType DTFile = StorageFile
471
diskTemplateToStorageType DTSharedFile = StorageFile
472
diskTemplateToStorageType DTDrbd8 = StorageLvmVg
473
diskTemplateToStorageType DTPlain = StorageLvmVg
474
diskTemplateToStorageType DTRbd = StorageRados
475
diskTemplateToStorageType DTDiskless = StorageDiskless
476
diskTemplateToStorageType DTBlock = StorageBlock
477

    
478
-- | Equips a raw storage unit with its parameters
479
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
480
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
481
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
482
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
483
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
484
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
485
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
486
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
487

    
488
-- | Node evac modes.
489
$(THH.declareLADT ''String "NodeEvacMode"
490
  [ ("NEvacPrimary",   "primary-only")
491
  , ("NEvacSecondary", "secondary-only")
492
  , ("NEvacAll",       "all")
493
  ])
494
$(THH.makeJSONInstance ''NodeEvacMode)
495

    
496
-- | The file driver type.
497
$(THH.declareLADT ''String "FileDriver"
498
  [ ("FileLoop",   "loop")
499
  , ("FileBlktap", "blktap")
500
  ])
501
$(THH.makeJSONInstance ''FileDriver)
502

    
503
-- | The instance create mode.
504
$(THH.declareLADT ''String "InstCreateMode"
505
  [ ("InstCreate",       "create")
506
  , ("InstImport",       "import")
507
  , ("InstRemoteImport", "remote-import")
508
  ])
509
$(THH.makeJSONInstance ''InstCreateMode)
510

    
511
-- | Reboot type.
512
$(THH.declareLADT ''String "RebootType"
513
  [ ("RebootSoft", "soft")
514
  , ("RebootHard", "hard")
515
  , ("RebootFull", "full")
516
  ])
517
$(THH.makeJSONInstance ''RebootType)
518

    
519
-- | Export modes.
520
$(THH.declareLADT ''String "ExportMode"
521
  [ ("ExportModeLocal",  "local")
522
  , ("ExportModeRemote", "remote")
523
  ])
524
$(THH.makeJSONInstance ''ExportMode)
525

    
526
-- | IAllocator run types (OpTestIAllocator).
527
$(THH.declareLADT ''String "IAllocatorTestDir"
528
  [ ("IAllocatorDirIn",  "in")
529
  , ("IAllocatorDirOut", "out")
530
  ])
531
$(THH.makeJSONInstance ''IAllocatorTestDir)
532

    
533
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
534
$(THH.declareLADT ''String "IAllocatorMode"
535
  [ ("IAllocatorAlloc",       "allocate")
536
  , ("IAllocatorMultiAlloc",  "multi-allocate")
537
  , ("IAllocatorReloc",       "relocate")
538
  , ("IAllocatorNodeEvac",    "node-evacuate")
539
  , ("IAllocatorChangeGroup", "change-group")
540
  ])
541
$(THH.makeJSONInstance ''IAllocatorMode)
542

    
543
-- | Network mode.
544
$(THH.declareLADT ''String "NICMode"
545
  [ ("NMBridged", "bridged")
546
  , ("NMRouted",  "routed")
547
  , ("NMOvs",     "openvswitch")
548
  , ("NMPool",    "pool")
549
  ])
550
$(THH.makeJSONInstance ''NICMode)
551

    
552
-- | The JobStatus data type. Note that this is ordered especially
553
-- such that greater\/lesser comparison on values of this type makes
554
-- sense.
555
$(THH.declareLADT ''String "JobStatus"
556
  [ ("JOB_STATUS_QUEUED",    "queued")
557
  , ("JOB_STATUS_WAITING",   "waiting")
558
  , ("JOB_STATUS_CANCELING", "canceling")
559
  , ("JOB_STATUS_RUNNING",   "running")
560
  , ("JOB_STATUS_CANCELED",  "canceled")
561
  , ("JOB_STATUS_SUCCESS",   "success")
562
  , ("JOB_STATUS_ERROR",     "error")
563
  ])
564
$(THH.makeJSONInstance ''JobStatus)
565

    
566
-- | Finalized job status.
567
$(THH.declareLADT ''String "FinalizedJobStatus"
568
  [ ("JobStatusCanceled",   "canceled")
569
  , ("JobStatusSuccessful", "success")
570
  , ("JobStatusFailed",     "error")
571
  ])
572
$(THH.makeJSONInstance ''FinalizedJobStatus)
573

    
574
-- | The Ganeti job type.
575
newtype JobId = JobId { fromJobId :: Int }
576
  deriving (Show, Eq)
577

    
578
-- | Builds a job ID.
579
makeJobId :: (Monad m) => Int -> m JobId
580
makeJobId i | i >= 0 = return $ JobId i
581
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
582

    
583
-- | Builds a job ID from a string.
584
makeJobIdS :: (Monad m) => String -> m JobId
585
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
586

    
587
-- | Parses a job ID.
588
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
589
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
590
parseJobId (JSON.JSRational _ x) =
591
  if denominator x /= 1
592
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
593
    -- FIXME: potential integer overflow here on 32-bit platforms
594
    else makeJobId . fromIntegral . numerator $ x
595
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
596

    
597
instance JSON.JSON JobId where
598
  showJSON = JSON.showJSON . fromJobId
599
  readJSON = parseJobId
600

    
601
-- | Relative job ID type alias.
602
type RelativeJobId = Negative Int
603

    
604
-- | Job ID dependency.
605
data JobIdDep = JobDepRelative RelativeJobId
606
              | JobDepAbsolute JobId
607
                deriving (Show, Eq)
608

    
609
instance JSON.JSON JobIdDep where
610
  showJSON (JobDepRelative i) = showJSON i
611
  showJSON (JobDepAbsolute i) = showJSON i
612
  readJSON v =
613
    case JSON.readJSON v::JSON.Result (Negative Int) of
614
      -- first try relative dependency, usually most common
615
      JSON.Ok r -> return $ JobDepRelative r
616
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
617

    
618
-- | Job Dependency type.
619
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
620
                     deriving (Show, Eq)
621

    
622
instance JSON JobDependency where
623
  showJSON (JobDependency dep status) = showJSON (dep, status)
624
  readJSON = liftM (uncurry JobDependency) . readJSON
625

    
626
-- | Valid opcode priorities for submit.
627
$(THH.declareIADT "OpSubmitPriority"
628
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
629
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
630
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
631
  ])
632
$(THH.makeJSONInstance ''OpSubmitPriority)
633

    
634
-- | Parse submit priorities from a string.
635
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
636
parseSubmitPriority "low"    = return OpPrioLow
637
parseSubmitPriority "normal" = return OpPrioNormal
638
parseSubmitPriority "high"   = return OpPrioHigh
639
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
640

    
641
-- | Format a submit priority as string.
642
fmtSubmitPriority :: OpSubmitPriority -> String
643
fmtSubmitPriority OpPrioLow    = "low"
644
fmtSubmitPriority OpPrioNormal = "normal"
645
fmtSubmitPriority OpPrioHigh   = "high"
646

    
647
-- | Our ADT for the OpCode status at runtime (while in a job).
648
$(THH.declareLADT ''String "OpStatus"
649
  [ ("OP_STATUS_QUEUED",    "queued")
650
  , ("OP_STATUS_WAITING",   "waiting")
651
  , ("OP_STATUS_CANCELING", "canceling")
652
  , ("OP_STATUS_RUNNING",   "running")
653
  , ("OP_STATUS_CANCELED",  "canceled")
654
  , ("OP_STATUS_SUCCESS",   "success")
655
  , ("OP_STATUS_ERROR",     "error")
656
  ])
657
$(THH.makeJSONInstance ''OpStatus)
658

    
659
-- | Type for the job message type.
660
$(THH.declareLADT ''String "ELogType"
661
  [ ("ELogMessage",      "message")
662
  , ("ELogRemoteImport", "remote-import")
663
  , ("ELogJqueueTest",   "jqueue-test")
664
  ])
665
$(THH.makeJSONInstance ''ELogType)
666

    
667
-- | Type of one element of a reason trail.
668
type ReasonElem = (String, String, Integer)
669

    
670
-- | Type representing a reason trail.
671
type ReasonTrail = [ReasonElem]