Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 68af861c

History | View | Annotate | Download (16 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
  , NonNegative
44
  , fromNonNegative
45
  , mkNonNegative
46
  , Positive
47
  , fromPositive
48
  , mkPositive
49
  , Negative
50
  , fromNegative
51
  , mkNegative
52
  , NonEmpty
53
  , fromNonEmpty
54
  , mkNonEmpty
55
  , NonEmptyString
56
  , MigrationMode(..)
57
  , VerifyOptionalChecks(..)
58
  , DdmSimple(..)
59
  , DdmFull(..)
60
  , CVErrorCode(..)
61
  , cVErrorCodeToRaw
62
  , Hypervisor(..)
63
  , hypervisorToRaw
64
  , OobCommand(..)
65
  , StorageType(..)
66
  , NodeEvacMode(..)
67
  , FileDriver(..)
68
  , InstCreateMode(..)
69
  , RebootType(..)
70
  , ExportMode(..)
71
  , IAllocatorTestDir(..)
72
  , IAllocatorMode(..)
73
  , iAllocatorModeToRaw
74
  , NICMode(..)
75
  , nICModeToRaw
76
  , JobStatus(..)
77
  , jobStatusToRaw
78
  , jobStatusFromRaw
79
  , FinalizedJobStatus(..)
80
  , finalizedJobStatusToRaw
81
  , JobId
82
  , fromJobId
83
  , makeJobId
84
  , makeJobIdS
85
  , RelativeJobId
86
  , JobIdDep(..)
87
  , JobDependency(..)
88
  , OpSubmitPriority(..)
89
  , opSubmitPriorityToRaw
90
  , parseSubmitPriority
91
  , fmtSubmitPriority
92
  , OpStatus(..)
93
  , opStatusToRaw
94
  , opStatusFromRaw
95
  , ELogType(..)
96
  , ReasonElem
97
  , ReasonTrail
98
  ) where
99

    
100
import Control.Monad (liftM)
101
import qualified Text.JSON as JSON
102
import Text.JSON (JSON, readJSON, showJSON)
103
import Data.Ratio (numerator, denominator)
104

    
105
import qualified Ganeti.Constants as C
106
import qualified Ganeti.THH as THH
107
import Ganeti.JSON
108
import Ganeti.Utils
109

    
110
-- * Generic types
111

    
112
-- | Type that holds a non-negative value.
113
newtype NonNegative a = NonNegative { fromNonNegative :: a }
114
  deriving (Show, Eq)
115

    
116
-- | Smart constructor for 'NonNegative'.
117
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
118
mkNonNegative i | i >= 0 = return (NonNegative i)
119
                | otherwise = fail $ "Invalid value for non-negative type '" ++
120
                              show i ++ "'"
121

    
122
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
123
  showJSON = JSON.showJSON . fromNonNegative
124
  readJSON v = JSON.readJSON v >>= mkNonNegative
125

    
126
-- | Type that holds a positive value.
127
newtype Positive a = Positive { fromPositive :: a }
128
  deriving (Show, Eq)
129

    
130
-- | Smart constructor for 'Positive'.
131
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
132
mkPositive i | i > 0 = return (Positive i)
133
             | otherwise = fail $ "Invalid value for positive type '" ++
134
                           show i ++ "'"
135

    
136
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
137
  showJSON = JSON.showJSON . fromPositive
138
  readJSON v = JSON.readJSON v >>= mkPositive
139

    
140
-- | Type that holds a negative value.
141
newtype Negative a = Negative { fromNegative :: a }
142
  deriving (Show, Eq)
143

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

    
150
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
151
  showJSON = JSON.showJSON . fromNegative
152
  readJSON v = JSON.readJSON v >>= mkNegative
153

    
154
-- | Type that holds a non-null list.
155
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
156
  deriving (Show, Eq)
157

    
158
-- | Smart constructor for 'NonEmpty'.
159
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
160
mkNonEmpty [] = fail "Received empty value for non-empty list"
161
mkNonEmpty xs = return (NonEmpty xs)
162

    
163
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
164
  showJSON = JSON.showJSON . fromNonEmpty
165
  readJSON v = JSON.readJSON v >>= mkNonEmpty
166

    
167
-- | A simple type alias for non-empty strings.
168
type NonEmptyString = NonEmpty Char
169

    
170
-- * Ganeti types
171

    
172
-- | Instance disk template type.
173
$(THH.declareSADT "DiskTemplate"
174
       [ ("DTDiskless",   'C.dtDiskless)
175
       , ("DTFile",       'C.dtFile)
176
       , ("DTSharedFile", 'C.dtSharedFile)
177
       , ("DTPlain",      'C.dtPlain)
178
       , ("DTBlock",      'C.dtBlock)
179
       , ("DTDrbd8",      'C.dtDrbd8)
180
       , ("DTRbd",        'C.dtRbd)
181
       , ("DTExt",        'C.dtExt)
182
       ])
183
$(THH.makeJSONInstance ''DiskTemplate)
184

    
185
instance HasStringRepr DiskTemplate where
186
  fromStringRepr = diskTemplateFromRaw
187
  toStringRepr = diskTemplateToRaw
188

    
189
-- | The Group allocation policy type.
190
--
191
-- Note that the order of constructors is important as the automatic
192
-- Ord instance will order them in the order they are defined, so when
193
-- changing this data type be careful about the interaction with the
194
-- desired sorting order.
195
$(THH.declareSADT "AllocPolicy"
196
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
197
       , ("AllocLastResort",  'C.allocPolicyLastResort)
198
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
199
       ])
200
$(THH.makeJSONInstance ''AllocPolicy)
201

    
202
-- | The Instance real state type. FIXME: this could be improved to
203
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
204
$(THH.declareSADT "InstanceStatus"
205
       [ ("StatusDown",    'C.inststAdmindown)
206
       , ("StatusOffline", 'C.inststAdminoffline)
207
       , ("ErrorDown",     'C.inststErrordown)
208
       , ("ErrorUp",       'C.inststErrorup)
209
       , ("NodeDown",      'C.inststNodedown)
210
       , ("NodeOffline",   'C.inststNodeoffline)
211
       , ("Running",       'C.inststRunning)
212
       , ("WrongNode",     'C.inststWrongnode)
213
       ])
214
$(THH.makeJSONInstance ''InstanceStatus)
215

    
216
-- | Migration mode.
217
$(THH.declareSADT "MigrationMode"
218
     [ ("MigrationLive",    'C.htMigrationLive)
219
     , ("MigrationNonLive", 'C.htMigrationNonlive)
220
     ])
221
$(THH.makeJSONInstance ''MigrationMode)
222

    
223
-- | Verify optional checks.
224
$(THH.declareSADT "VerifyOptionalChecks"
225
     [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
226
     ])
227
$(THH.makeJSONInstance ''VerifyOptionalChecks)
228

    
229
-- | Cluster verify error codes.
230
$(THH.declareSADT "CVErrorCode"
231
  [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
232
  , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
233
  , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
234
  , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
235
  , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
236
  , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
237
  , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
238
  , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
239
  , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
240
  , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
241
  , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
242
  , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
243
  , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
244
  , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
245
  , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
246
  , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
247
  , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
248
  , ("CvENODEHV",               'C.cvEnodehvCode)
249
  , ("CvENODELVM",              'C.cvEnodelvmCode)
250
  , ("CvENODEN1",               'C.cvEnoden1Code)
251
  , ("CvENODENET",              'C.cvEnodenetCode)
252
  , ("CvENODEOS",               'C.cvEnodeosCode)
253
  , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
254
  , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
255
  , ("CvENODERPC",              'C.cvEnoderpcCode)
256
  , ("CvENODESSH",              'C.cvEnodesshCode)
257
  , ("CvENODEVERSION",          'C.cvEnodeversionCode)
258
  , ("CvENODESETUP",            'C.cvEnodesetupCode)
259
  , ("CvENODETIME",             'C.cvEnodetimeCode)
260
  , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
261
  , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
262
  , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
263
  ])
264
$(THH.makeJSONInstance ''CVErrorCode)
265

    
266
-- | Dynamic device modification, just add\/remove version.
267
$(THH.declareSADT "DdmSimple"
268
     [ ("DdmSimpleAdd",    'C.ddmAdd)
269
     , ("DdmSimpleRemove", 'C.ddmRemove)
270
     ])
271
$(THH.makeJSONInstance ''DdmSimple)
272

    
273
-- | Dynamic device modification, all operations version.
274
$(THH.declareSADT "DdmFull"
275
     [ ("DdmFullAdd",    'C.ddmAdd)
276
     , ("DdmFullRemove", 'C.ddmRemove)
277
     , ("DdmFullModify", 'C.ddmModify)
278
     ])
279
$(THH.makeJSONInstance ''DdmFull)
280

    
281
-- | Hypervisor type definitions.
282
$(THH.declareSADT "Hypervisor"
283
  [ ( "Kvm",    'C.htKvm )
284
  , ( "XenPvm", 'C.htXenPvm )
285
  , ( "Chroot", 'C.htChroot )
286
  , ( "XenHvm", 'C.htXenHvm )
287
  , ( "Lxc",    'C.htLxc )
288
  , ( "Fake",   'C.htFake )
289
  ])
290
$(THH.makeJSONInstance ''Hypervisor)
291

    
292
-- | Oob command type.
293
$(THH.declareSADT "OobCommand"
294
  [ ("OobHealth",      'C.oobHealth)
295
  , ("OobPowerCycle",  'C.oobPowerCycle)
296
  , ("OobPowerOff",    'C.oobPowerOff)
297
  , ("OobPowerOn",     'C.oobPowerOn)
298
  , ("OobPowerStatus", 'C.oobPowerStatus)
299
  ])
300
$(THH.makeJSONInstance ''OobCommand)
301

    
302
-- | Storage type.
303
$(THH.declareSADT "StorageType"
304
  [ ("StorageFile", 'C.stFile)
305
  , ("StorageLvmPv", 'C.stLvmPv)
306
  , ("StorageLvmVg", 'C.stLvmVg)
307
  , ("StorageDiskless", 'C.stDiskless)
308
  , ("StorageBlock", 'C.stBlock)
309
  , ("StorageRados", 'C.stRados)
310
  , ("StorageExt", 'C.stExt)
311
  ])
312
$(THH.makeJSONInstance ''StorageType)
313

    
314
-- | Node evac modes.
315
$(THH.declareSADT "NodeEvacMode"
316
  [ ("NEvacPrimary",   'C.iallocatorNevacPri)
317
  , ("NEvacSecondary", 'C.iallocatorNevacSec)
318
  , ("NEvacAll",       'C.iallocatorNevacAll)
319
  ])
320
$(THH.makeJSONInstance ''NodeEvacMode)
321

    
322
-- | The file driver type.
323
$(THH.declareSADT "FileDriver"
324
  [ ("FileLoop",   'C.fdLoop)
325
  , ("FileBlktap", 'C.fdBlktap)
326
  ])
327
$(THH.makeJSONInstance ''FileDriver)
328

    
329
-- | The instance create mode.
330
$(THH.declareSADT "InstCreateMode"
331
  [ ("InstCreate",       'C.instanceCreate)
332
  , ("InstImport",       'C.instanceImport)
333
  , ("InstRemoteImport", 'C.instanceRemoteImport)
334
  ])
335
$(THH.makeJSONInstance ''InstCreateMode)
336

    
337
-- | Reboot type.
338
$(THH.declareSADT "RebootType"
339
  [ ("RebootSoft", 'C.instanceRebootSoft)
340
  , ("RebootHard", 'C.instanceRebootHard)
341
  , ("RebootFull", 'C.instanceRebootFull)
342
  ])
343
$(THH.makeJSONInstance ''RebootType)
344

    
345
-- | Export modes.
346
$(THH.declareSADT "ExportMode"
347
  [ ("ExportModeLocal",  'C.exportModeLocal)
348
  , ("ExportModeRemove", 'C.exportModeRemote)
349
  ])
350
$(THH.makeJSONInstance ''ExportMode)
351

    
352
-- | IAllocator run types (OpTestIAllocator).
353
$(THH.declareSADT "IAllocatorTestDir"
354
  [ ("IAllocatorDirIn",  'C.iallocatorDirIn)
355
  , ("IAllocatorDirOut", 'C.iallocatorDirOut)
356
  ])
357
$(THH.makeJSONInstance ''IAllocatorTestDir)
358

    
359
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
360
$(THH.declareSADT "IAllocatorMode"
361
  [ ("IAllocatorAlloc",       'C.iallocatorModeAlloc)
362
  , ("IAllocatorMultiAlloc",  'C.iallocatorModeMultiAlloc)
363
  , ("IAllocatorReloc",       'C.iallocatorModeReloc)
364
  , ("IAllocatorNodeEvac",    'C.iallocatorModeNodeEvac)
365
  , ("IAllocatorChangeGroup", 'C.iallocatorModeChgGroup)
366
  ])
367
$(THH.makeJSONInstance ''IAllocatorMode)
368

    
369
-- | Network mode.
370
$(THH.declareSADT "NICMode"
371
  [ ("NMBridged", 'C.nicModeBridged)
372
  , ("NMRouted",  'C.nicModeRouted)
373
  , ("NMOvs",     'C.nicModeOvs)
374
  ])
375
$(THH.makeJSONInstance ''NICMode)
376

    
377
-- | The JobStatus data type. Note that this is ordered especially
378
-- such that greater\/lesser comparison on values of this type makes
379
-- sense.
380
$(THH.declareSADT "JobStatus"
381
       [ ("JOB_STATUS_QUEUED",    'C.jobStatusQueued)
382
       , ("JOB_STATUS_WAITING",   'C.jobStatusWaiting)
383
       , ("JOB_STATUS_CANCELING", 'C.jobStatusCanceling)
384
       , ("JOB_STATUS_RUNNING",   'C.jobStatusRunning)
385
       , ("JOB_STATUS_CANCELED",  'C.jobStatusCanceled)
386
       , ("JOB_STATUS_SUCCESS",   'C.jobStatusSuccess)
387
       , ("JOB_STATUS_ERROR",     'C.jobStatusError)
388
       ])
389
$(THH.makeJSONInstance ''JobStatus)
390

    
391
-- | Finalized job status.
392
$(THH.declareSADT "FinalizedJobStatus"
393
  [ ("JobStatusCanceled",   'C.jobStatusCanceled)
394
  , ("JobStatusSuccessful", 'C.jobStatusSuccess)
395
  , ("JobStatusFailed",     'C.jobStatusError)
396
  ])
397
$(THH.makeJSONInstance ''FinalizedJobStatus)
398

    
399
-- | The Ganeti job type.
400
newtype JobId = JobId { fromJobId :: Int }
401
  deriving (Show, Eq)
402

    
403
-- | Builds a job ID.
404
makeJobId :: (Monad m) => Int -> m JobId
405
makeJobId i | i >= 0 = return $ JobId i
406
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
407

    
408
-- | Builds a job ID from a string.
409
makeJobIdS :: (Monad m) => String -> m JobId
410
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
411

    
412
-- | Parses a job ID.
413
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
414
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
415
parseJobId (JSON.JSRational _ x) =
416
  if denominator x /= 1
417
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
418
    -- FIXME: potential integer overflow here on 32-bit platforms
419
    else makeJobId . fromIntegral . numerator $ x
420
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
421

    
422
instance JSON.JSON JobId where
423
  showJSON = JSON.showJSON . fromJobId
424
  readJSON = parseJobId
425

    
426
-- | Relative job ID type alias.
427
type RelativeJobId = Negative Int
428

    
429
-- | Job ID dependency.
430
data JobIdDep = JobDepRelative RelativeJobId
431
              | JobDepAbsolute JobId
432
                deriving (Show, Eq)
433

    
434
instance JSON.JSON JobIdDep where
435
  showJSON (JobDepRelative i) = showJSON i
436
  showJSON (JobDepAbsolute i) = showJSON i
437
  readJSON v =
438
    case JSON.readJSON v::JSON.Result (Negative Int) of
439
      -- first try relative dependency, usually most common
440
      JSON.Ok r -> return $ JobDepRelative r
441
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
442

    
443
-- | Job Dependency type.
444
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
445
                     deriving (Show, Eq)
446

    
447
instance JSON JobDependency where
448
  showJSON (JobDependency dep status) = showJSON (dep, status)
449
  readJSON = liftM (uncurry JobDependency) . readJSON
450

    
451
-- | Valid opcode priorities for submit.
452
$(THH.declareIADT "OpSubmitPriority"
453
  [ ("OpPrioLow",    'C.opPrioLow)
454
  , ("OpPrioNormal", 'C.opPrioNormal)
455
  , ("OpPrioHigh",   'C.opPrioHigh)
456
  ])
457
$(THH.makeJSONInstance ''OpSubmitPriority)
458

    
459
-- | Parse submit priorities from a string.
460
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
461
parseSubmitPriority "low"    = return OpPrioLow
462
parseSubmitPriority "normal" = return OpPrioNormal
463
parseSubmitPriority "high"   = return OpPrioHigh
464
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
465

    
466
-- | Format a submit priority as string.
467
fmtSubmitPriority :: OpSubmitPriority -> String
468
fmtSubmitPriority OpPrioLow    = "low"
469
fmtSubmitPriority OpPrioNormal = "normal"
470
fmtSubmitPriority OpPrioHigh   = "high"
471

    
472
-- | Our ADT for the OpCode status at runtime (while in a job).
473
$(THH.declareSADT "OpStatus"
474
  [ ("OP_STATUS_QUEUED",    'C.opStatusQueued)
475
  , ("OP_STATUS_WAITING",   'C.opStatusWaiting)
476
  , ("OP_STATUS_CANCELING", 'C.opStatusCanceling)
477
  , ("OP_STATUS_RUNNING",   'C.opStatusRunning)
478
  , ("OP_STATUS_CANCELED",  'C.opStatusCanceled)
479
  , ("OP_STATUS_SUCCESS",   'C.opStatusSuccess)
480
  , ("OP_STATUS_ERROR",     'C.opStatusError)
481
  ])
482
$(THH.makeJSONInstance ''OpStatus)
483

    
484
-- | Type for the job message type.
485
$(THH.declareSADT "ELogType"
486
  [ ("ELogMessage",      'C.elogMessage)
487
  , ("ELogRemoteImport", 'C.elogRemoteImport)
488
  , ("ELogJqueueTest",   'C.elogJqueueTest)
489
  ])
490
$(THH.makeJSONInstance ''ELogType)
491

    
492
-- | Type of one element of a reason trail.
493
type ReasonElem = (String, String, Integer)
494

    
495
-- | Type representing a reason trail.
496
type ReasonTrail = [ReasonElem]