Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Types.hs @ c67b908a

History | View | Annotate | Download (12.5 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 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
  , OobCommand(..)
64
  , StorageType(..)
65
  , NodeEvacMode(..)
66
  , FileDriver(..)
67
  , InstCreateMode(..)
68
  , RebootType(..)
69
  , ExportMode(..)
70
  , IAllocatorTestDir(..)
71
  , IAllocatorMode(..)
72
  , iAllocatorModeToRaw
73
  , NetworkType(..)
74
  , networkTypeToRaw
75
  , NICMode(..)
76
  , nICModeToRaw
77
  , FinalizedJobStatus(..)
78
  , finalizedJobStatusToRaw
79
  , JobId
80
  , fromJobId
81
  , makeJobId
82
  ) where
83

    
84
import qualified Text.JSON as JSON
85
import Data.Ratio (numerator, denominator)
86

    
87
import qualified Ganeti.Constants as C
88
import qualified Ganeti.THH as THH
89
import Ganeti.JSON
90
import Ganeti.Utils
91

    
92
-- * Generic types
93

    
94
-- | Type that holds a non-negative value.
95
newtype NonNegative a = NonNegative { fromNonNegative :: a }
96
  deriving (Show, Eq)
97

    
98
-- | Smart constructor for 'NonNegative'.
99
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
100
mkNonNegative i | i >= 0 = return (NonNegative i)
101
                | otherwise = fail $ "Invalid value for non-negative type '" ++
102
                              show i ++ "'"
103

    
104
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
105
  showJSON = JSON.showJSON . fromNonNegative
106
  readJSON v = JSON.readJSON v >>= mkNonNegative
107

    
108
-- | Type that holds a positive value.
109
newtype Positive a = Positive { fromPositive :: a }
110
  deriving (Show, Eq)
111

    
112
-- | Smart constructor for 'Positive'.
113
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
114
mkPositive i | i > 0 = return (Positive i)
115
             | otherwise = fail $ "Invalid value for positive type '" ++
116
                           show i ++ "'"
117

    
118
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
119
  showJSON = JSON.showJSON . fromPositive
120
  readJSON v = JSON.readJSON v >>= mkPositive
121

    
122
-- | Type that holds a negative value.
123
newtype Negative a = Negative { fromNegative :: a }
124
  deriving (Show, Eq)
125

    
126
-- | Smart constructor for 'Negative'.
127
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
128
mkNegative i | i < 0 = return (Negative i)
129
             | otherwise = fail $ "Invalid value for negative type '" ++
130
                           show i ++ "'"
131

    
132
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
133
  showJSON = JSON.showJSON . fromNegative
134
  readJSON v = JSON.readJSON v >>= mkNegative
135

    
136
-- | Type that holds a non-null list.
137
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
138
  deriving (Show, Eq)
139

    
140
-- | Smart constructor for 'NonEmpty'.
141
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
142
mkNonEmpty [] = fail "Received empty value for non-empty list"
143
mkNonEmpty xs = return (NonEmpty xs)
144

    
145
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
146
  showJSON = JSON.showJSON . fromNonEmpty
147
  readJSON v = JSON.readJSON v >>= mkNonEmpty
148

    
149
-- | A simple type alias for non-empty strings.
150
type NonEmptyString = NonEmpty Char
151

    
152
-- * Ganeti types
153

    
154
-- | Instance disk template type.
155
$(THH.declareSADT "DiskTemplate"
156
       [ ("DTDiskless",   'C.dtDiskless)
157
       , ("DTFile",       'C.dtFile)
158
       , ("DTSharedFile", 'C.dtSharedFile)
159
       , ("DTPlain",      'C.dtPlain)
160
       , ("DTBlock",      'C.dtBlock)
161
       , ("DTDrbd8",      'C.dtDrbd8)
162
       , ("DTRbd",        'C.dtRbd)
163
       ])
164
$(THH.makeJSONInstance ''DiskTemplate)
165

    
166
instance HasStringRepr DiskTemplate where
167
  fromStringRepr = diskTemplateFromRaw
168
  toStringRepr = diskTemplateToRaw
169

    
170
-- | The Group allocation policy type.
171
--
172
-- Note that the order of constructors is important as the automatic
173
-- Ord instance will order them in the order they are defined, so when
174
-- changing this data type be careful about the interaction with the
175
-- desired sorting order.
176
$(THH.declareSADT "AllocPolicy"
177
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
178
       , ("AllocLastResort",  'C.allocPolicyLastResort)
179
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
180
       ])
181
$(THH.makeJSONInstance ''AllocPolicy)
182

    
183
-- | The Instance real state type. FIXME: this could be improved to
184
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
185
$(THH.declareSADT "InstanceStatus"
186
       [ ("StatusDown",    'C.inststAdmindown)
187
       , ("StatusOffline", 'C.inststAdminoffline)
188
       , ("ErrorDown",     'C.inststErrordown)
189
       , ("ErrorUp",       'C.inststErrorup)
190
       , ("NodeDown",      'C.inststNodedown)
191
       , ("NodeOffline",   'C.inststNodeoffline)
192
       , ("Running",       'C.inststRunning)
193
       , ("WrongNode",     'C.inststWrongnode)
194
       ])
195
$(THH.makeJSONInstance ''InstanceStatus)
196

    
197
-- | Migration mode.
198
$(THH.declareSADT "MigrationMode"
199
     [ ("MigrationLive",    'C.htMigrationLive)
200
     , ("MigrationNonLive", 'C.htMigrationNonlive)
201
     ])
202
$(THH.makeJSONInstance ''MigrationMode)
203

    
204
-- | Verify optional checks.
205
$(THH.declareSADT "VerifyOptionalChecks"
206
     [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
207
     ])
208
$(THH.makeJSONInstance ''VerifyOptionalChecks)
209

    
210
-- | Cluster verify error codes.
211
$(THH.declareSADT "CVErrorCode"
212
  [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
213
  , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
214
  , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
215
  , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
216
  , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
217
  , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
218
  , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
219
  , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
220
  , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
221
  , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
222
  , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
223
  , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
224
  , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
225
  , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
226
  , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
227
  , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
228
  , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
229
  , ("CvENODEHV",               'C.cvEnodehvCode)
230
  , ("CvENODELVM",              'C.cvEnodelvmCode)
231
  , ("CvENODEN1",               'C.cvEnoden1Code)
232
  , ("CvENODENET",              'C.cvEnodenetCode)
233
  , ("CvENODEOS",               'C.cvEnodeosCode)
234
  , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
235
  , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
236
  , ("CvENODERPC",              'C.cvEnoderpcCode)
237
  , ("CvENODESSH",              'C.cvEnodesshCode)
238
  , ("CvENODEVERSION",          'C.cvEnodeversionCode)
239
  , ("CvENODESETUP",            'C.cvEnodesetupCode)
240
  , ("CvENODETIME",             'C.cvEnodetimeCode)
241
  , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
242
  , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
243
  , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
244
  ])
245
$(THH.makeJSONInstance ''CVErrorCode)
246

    
247
-- | Dynamic device modification, just add\/remove version.
248
$(THH.declareSADT "DdmSimple"
249
     [ ("DdmSimpleAdd",    'C.ddmAdd)
250
     , ("DdmSimpleRemove", 'C.ddmRemove)
251
     ])
252
$(THH.makeJSONInstance ''DdmSimple)
253

    
254
-- | Dynamic device modification, all operations version.
255
$(THH.declareSADT "DdmFull"
256
     [ ("DdmFullAdd",    'C.ddmAdd)
257
     , ("DdmFullRemove", 'C.ddmRemove)
258
     , ("DdmFullModify", 'C.ddmModify)
259
     ])
260
$(THH.makeJSONInstance ''DdmFull)
261

    
262
-- | Hypervisor type definitions.
263
$(THH.declareSADT "Hypervisor"
264
  [ ( "Kvm",    'C.htKvm )
265
  , ( "XenPvm", 'C.htXenPvm )
266
  , ( "Chroot", 'C.htChroot )
267
  , ( "XenHvm", 'C.htXenHvm )
268
  , ( "Lxc",    'C.htLxc )
269
  , ( "Fake",   'C.htFake )
270
  ])
271
$(THH.makeJSONInstance ''Hypervisor)
272

    
273
-- | Oob command type.
274
$(THH.declareSADT "OobCommand"
275
  [ ("OobHealth",      'C.oobHealth)
276
  , ("OobPowerCycle",  'C.oobPowerCycle)
277
  , ("OobPowerOff",    'C.oobPowerOff)
278
  , ("OobPowerOn",     'C.oobPowerOn)
279
  , ("OobPowerStatus", 'C.oobPowerStatus)
280
  ])
281
$(THH.makeJSONInstance ''OobCommand)
282

    
283
-- | Storage type.
284
$(THH.declareSADT "StorageType"
285
  [ ("StorageFile", 'C.stFile)
286
  , ("StorageLvmPv", 'C.stLvmPv)
287
  , ("StorageLvmVg", 'C.stLvmVg)
288
  ])
289
$(THH.makeJSONInstance ''StorageType)
290

    
291
-- | Node evac modes.
292
$(THH.declareSADT "NodeEvacMode"
293
  [ ("NEvacPrimary",   'C.iallocatorNevacPri)
294
  , ("NEvacSecondary", 'C.iallocatorNevacSec)
295
  , ("NEvacAll",       'C.iallocatorNevacAll)
296
  ])
297
$(THH.makeJSONInstance ''NodeEvacMode)
298

    
299
-- | The file driver type.
300
$(THH.declareSADT "FileDriver"
301
  [ ("FileLoop",   'C.fdLoop)
302
  , ("FileBlktap", 'C.fdBlktap)
303
  ])
304
$(THH.makeJSONInstance ''FileDriver)
305

    
306
-- | The instance create mode.
307
$(THH.declareSADT "InstCreateMode"
308
  [ ("InstCreate",       'C.instanceCreate)
309
  , ("InstImport",       'C.instanceImport)
310
  , ("InstRemoteImport", 'C.instanceRemoteImport)
311
  ])
312
$(THH.makeJSONInstance ''InstCreateMode)
313

    
314
-- | Reboot type.
315
$(THH.declareSADT "RebootType"
316
  [ ("RebootSoft", 'C.instanceRebootSoft)
317
  , ("RebootHard", 'C.instanceRebootHard)
318
  , ("RebootFull", 'C.instanceRebootFull)
319
  ])
320
$(THH.makeJSONInstance ''RebootType)
321

    
322
-- | Export modes.
323
$(THH.declareSADT "ExportMode"
324
  [ ("ExportModeLocal",  'C.exportModeLocal)
325
  , ("ExportModeRemove", 'C.exportModeRemote)
326
  ])
327
$(THH.makeJSONInstance ''ExportMode)
328

    
329
-- | IAllocator run types (OpTestIAllocator).
330
$(THH.declareSADT "IAllocatorTestDir"
331
  [ ("IAllocatorDirIn",  'C.iallocatorDirIn)
332
  , ("IAllocatorDirOut", 'C.iallocatorDirOut)
333
  ])
334
$(THH.makeJSONInstance ''IAllocatorTestDir)
335

    
336
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
337
$(THH.declareSADT "IAllocatorMode"
338
  [ ("IAllocatorAlloc",       'C.iallocatorModeAlloc)
339
  , ("IAllocatorMultiAlloc",  'C.iallocatorModeMultiAlloc)
340
  , ("IAllocatorReloc",       'C.iallocatorModeReloc)
341
  , ("IAllocatorNodeEvac",    'C.iallocatorModeNodeEvac)
342
  , ("IAllocatorChangeGroup", 'C.iallocatorModeChgGroup)
343
  ])
344
$(THH.makeJSONInstance ''IAllocatorMode)
345

    
346
-- | Network type.
347
$(THH.declareSADT "NetworkType"
348
  [ ("PrivateNetwork", 'C.networkTypePrivate)
349
  , ("PublicNetwork",  'C.networkTypePublic)
350
  ])
351
$(THH.makeJSONInstance ''NetworkType)
352

    
353
-- | Netork mode.
354
$(THH.declareSADT "NICMode"
355
  [ ("NMBridged", 'C.nicModeBridged)
356
  , ("NMRouted",  'C.nicModeRouted)
357
  ])
358
$(THH.makeJSONInstance ''NICMode)
359

    
360
-- | Finalized job status.
361
$(THH.declareSADT "FinalizedJobStatus"
362
  [ ("JobStatusCanceled",   'C.jobStatusCanceled)
363
  , ("JobStatusSuccessful", 'C.jobStatusSuccess)
364
  , ("JobStatusFailed",     'C.jobStatusError)
365
  ])
366
$(THH.makeJSONInstance ''FinalizedJobStatus)
367

    
368
-- | The Ganeti job type.
369
newtype JobId = JobId { fromJobId :: Int }
370
  deriving (Show, Eq)
371

    
372
-- | Builds a job ID.
373
makeJobId :: (Monad m) => Int -> m JobId
374
makeJobId i | i >= 0 = return $ JobId i
375
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
376

    
377
-- | Parses a job ID.
378
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
379
parseJobId (JSON.JSString x) =
380
  tryRead "parsing job id" (JSON.fromJSString x) >>= makeJobId
381
parseJobId (JSON.JSRational _ x) =
382
  if denominator x /= 1
383
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
384
    -- FIXME: potential integer overflow here on 32-bit platforms
385
    else makeJobId . fromIntegral . numerator $ x
386
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
387

    
388
instance JSON.JSON JobId where
389
  showJSON = JSON.showJSON . fromJobId
390
  readJSON = parseJobId