Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ a8633d70

History | View | Annotate | Download (21.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
  , 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
  , ("CvENODEDRBD",                    "ENODEDRBD")
338
  , ("CvENODEDRBDHELPER",              "ENODEDRBDHELPER")
339
  , ("CvENODEFILECHECK",               "ENODEFILECHECK")
340
  , ("CvENODEHOOKS",                   "ENODEHOOKS")
341
  , ("CvENODEHV",                      "ENODEHV")
342
  , ("CvENODELVM",                     "ENODELVM")
343
  , ("CvENODEN1",                      "ENODEN1")
344
  , ("CvENODENET",                     "ENODENET")
345
  , ("CvENODEOS",                      "ENODEOS")
346
  , ("CvENODEORPHANINSTANCE",          "ENODEORPHANINSTANCE")
347
  , ("CvENODEORPHANLV",                "ENODEORPHANLV")
348
  , ("CvENODERPC",                     "ENODERPC")
349
  , ("CvENODESSH",                     "ENODESSH")
350
  , ("CvENODEVERSION",                 "ENODEVERSION")
351
  , ("CvENODESETUP",                   "ENODESETUP")
352
  , ("CvENODETIME",                    "ENODETIME")
353
  , ("CvENODEOOBPATH",                 "ENODEOOBPATH")
354
  , ("CvENODEUSERSCRIPTS",             "ENODEUSERSCRIPTS")
355
  , ("CvENODEFILESTORAGEPATHS",        "ENODEFILESTORAGEPATHS")
356
  , ("CvENODEFILESTORAGEPATHUNUSABLE", "ENODEFILESTORAGEPATHUNUSABLE")
357
  , ("CvENODESHAREDFILESTORAGEPATHUNUSABLE",
358
     "ENODESHAREDFILESTORAGEPATHUNUSABLE")
359
  ])
360
$(THH.makeJSONInstance ''CVErrorCode)
361

    
362
-- | Dynamic device modification, just add\/remove version.
363
$(THH.declareLADT ''String "DdmSimple"
364
     [ ("DdmSimpleAdd",    "add")
365
     , ("DdmSimpleRemove", "remove")
366
     ])
367
$(THH.makeJSONInstance ''DdmSimple)
368

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

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

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

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

    
410
-- | Storage keys are identifiers for storage units. Their content varies
411
-- depending on the storage type, for example a storage key for LVM storage
412
-- is the volume group name.
413
type StorageKey = String
414

    
415
-- | Storage parameters
416
type SPExclusiveStorage = Bool
417

    
418
-- | Storage units without storage-type-specific parameters
419
data StorageUnitRaw = SURaw StorageType StorageKey
420

    
421
-- | Full storage unit with storage-type-specific parameters
422
data StorageUnit = SUFile StorageKey
423
                 | SULvmPv StorageKey SPExclusiveStorage
424
                 | SULvmVg StorageKey SPExclusiveStorage
425
                 | SUDiskless StorageKey
426
                 | SUBlock StorageKey
427
                 | SURados StorageKey
428
                 | SUExt StorageKey
429
                 deriving (Eq)
430

    
431
instance Show StorageUnit where
432
  show (SUFile key) = showSUSimple StorageFile key
433
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
434
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
435
  show (SUDiskless key) = showSUSimple StorageDiskless key
436
  show (SUBlock key) = showSUSimple StorageBlock key
437
  show (SURados key) = showSUSimple StorageRados key
438
  show (SUExt key) = showSUSimple StorageExt key
439

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

    
451
-- | Composes a string representation of storage types without
452
-- storage parameters
453
showSUSimple :: StorageType -> StorageKey -> String
454
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
455

    
456
-- | Composes a string representation of the LVM storage types
457
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
458
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
459

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

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

    
484
-- | Node evac modes.
485
$(THH.declareLADT ''String "NodeEvacMode"
486
  [ ("NEvacPrimary",   "primary-only")
487
  , ("NEvacSecondary", "secondary-only")
488
  , ("NEvacAll",       "all")
489
  ])
490
$(THH.makeJSONInstance ''NodeEvacMode)
491

    
492
-- | The file driver type.
493
$(THH.declareLADT ''String "FileDriver"
494
  [ ("FileLoop",   "loop")
495
  , ("FileBlktap", "blktap")
496
  ])
497
$(THH.makeJSONInstance ''FileDriver)
498

    
499
-- | The instance create mode.
500
$(THH.declareLADT ''String "InstCreateMode"
501
  [ ("InstCreate",       "create")
502
  , ("InstImport",       "import")
503
  , ("InstRemoteImport", "remote-import")
504
  ])
505
$(THH.makeJSONInstance ''InstCreateMode)
506

    
507
-- | Reboot type.
508
$(THH.declareLADT ''String "RebootType"
509
  [ ("RebootSoft", "soft")
510
  , ("RebootHard", "hard")
511
  , ("RebootFull", "full")
512
  ])
513
$(THH.makeJSONInstance ''RebootType)
514

    
515
-- | Export modes.
516
$(THH.declareLADT ''String "ExportMode"
517
  [ ("ExportModeLocal",  "local")
518
  , ("ExportModeRemote", "remote")
519
  ])
520
$(THH.makeJSONInstance ''ExportMode)
521

    
522
-- | IAllocator run types (OpTestIAllocator).
523
$(THH.declareLADT ''String "IAllocatorTestDir"
524
  [ ("IAllocatorDirIn",  "in")
525
  , ("IAllocatorDirOut", "out")
526
  ])
527
$(THH.makeJSONInstance ''IAllocatorTestDir)
528

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

    
539
-- | Network mode.
540
$(THH.declareLADT ''String "NICMode"
541
  [ ("NMBridged", "bridged")
542
  , ("NMRouted",  "routed")
543
  , ("NMOvs",     "openvswitch")
544
  , ("NMPool",    "pool")
545
  ])
546
$(THH.makeJSONInstance ''NICMode)
547

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

    
562
-- | Finalized job status.
563
$(THH.declareLADT ''String "FinalizedJobStatus"
564
  [ ("JobStatusCanceled",   "canceled")
565
  , ("JobStatusSuccessful", "success")
566
  , ("JobStatusFailed",     "error")
567
  ])
568
$(THH.makeJSONInstance ''FinalizedJobStatus)
569

    
570
-- | The Ganeti job type.
571
newtype JobId = JobId { fromJobId :: Int }
572
  deriving (Show, Eq)
573

    
574
-- | Builds a job ID.
575
makeJobId :: (Monad m) => Int -> m JobId
576
makeJobId i | i >= 0 = return $ JobId i
577
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
578

    
579
-- | Builds a job ID from a string.
580
makeJobIdS :: (Monad m) => String -> m JobId
581
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
582

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

    
593
instance JSON.JSON JobId where
594
  showJSON = JSON.showJSON . fromJobId
595
  readJSON = parseJobId
596

    
597
-- | Relative job ID type alias.
598
type RelativeJobId = Negative Int
599

    
600
-- | Job ID dependency.
601
data JobIdDep = JobDepRelative RelativeJobId
602
              | JobDepAbsolute JobId
603
                deriving (Show, Eq)
604

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

    
614
-- | Job Dependency type.
615
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
616
                     deriving (Show, Eq)
617

    
618
instance JSON JobDependency where
619
  showJSON (JobDependency dep status) = showJSON (dep, status)
620
  readJSON = liftM (uncurry JobDependency) . readJSON
621

    
622
-- | Valid opcode priorities for submit.
623
$(THH.declareIADT "OpSubmitPriority"
624
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
625
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
626
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
627
  ])
628
$(THH.makeJSONInstance ''OpSubmitPriority)
629

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

    
637
-- | Format a submit priority as string.
638
fmtSubmitPriority :: OpSubmitPriority -> String
639
fmtSubmitPriority OpPrioLow    = "low"
640
fmtSubmitPriority OpPrioNormal = "normal"
641
fmtSubmitPriority OpPrioHigh   = "high"
642

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

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

    
663
-- | Type of one element of a reason trail.
664
type ReasonElem = (String, String, Integer)
665

    
666
-- | Type representing a reason trail.
667
type ReasonTrail = [ReasonElem]