Remove network_type slot (Issue 363)
[ganeti-local] / src / Ganeti / Types.hs
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   , NICMode(..)
74   , nICModeToRaw
75   , JobStatus(..)
76   , jobStatusToRaw
77   , jobStatusFromRaw
78   , FinalizedJobStatus(..)
79   , finalizedJobStatusToRaw
80   , JobId
81   , fromJobId
82   , makeJobId
83   , makeJobIdS
84   , RelativeJobId
85   , JobIdDep(..)
86   , JobDependency(..)
87   , OpSubmitPriority(..)
88   , opSubmitPriorityToRaw
89   , OpStatus(..)
90   , opStatusToRaw
91   , opStatusFromRaw
92   , ELogType(..)
93   ) where
94
95 import Control.Monad (liftM)
96 import qualified Text.JSON as JSON
97 import Text.JSON (JSON, readJSON, showJSON)
98 import Data.Ratio (numerator, denominator)
99
100 import qualified Ganeti.Constants as C
101 import qualified Ganeti.THH as THH
102 import Ganeti.JSON
103 import Ganeti.Utils
104
105 -- * Generic types
106
107 -- | Type that holds a non-negative value.
108 newtype NonNegative a = NonNegative { fromNonNegative :: a }
109   deriving (Show, Eq)
110
111 -- | Smart constructor for 'NonNegative'.
112 mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
113 mkNonNegative i | i >= 0 = return (NonNegative i)
114                 | otherwise = fail $ "Invalid value for non-negative type '" ++
115                               show i ++ "'"
116
117 instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
118   showJSON = JSON.showJSON . fromNonNegative
119   readJSON v = JSON.readJSON v >>= mkNonNegative
120
121 -- | Type that holds a positive value.
122 newtype Positive a = Positive { fromPositive :: a }
123   deriving (Show, Eq)
124
125 -- | Smart constructor for 'Positive'.
126 mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
127 mkPositive i | i > 0 = return (Positive i)
128              | otherwise = fail $ "Invalid value for positive type '" ++
129                            show i ++ "'"
130
131 instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
132   showJSON = JSON.showJSON . fromPositive
133   readJSON v = JSON.readJSON v >>= mkPositive
134
135 -- | Type that holds a negative value.
136 newtype Negative a = Negative { fromNegative :: a }
137   deriving (Show, Eq)
138
139 -- | Smart constructor for 'Negative'.
140 mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
141 mkNegative i | i < 0 = return (Negative i)
142              | otherwise = fail $ "Invalid value for negative type '" ++
143                            show i ++ "'"
144
145 instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
146   showJSON = JSON.showJSON . fromNegative
147   readJSON v = JSON.readJSON v >>= mkNegative
148
149 -- | Type that holds a non-null list.
150 newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
151   deriving (Show, Eq)
152
153 -- | Smart constructor for 'NonEmpty'.
154 mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
155 mkNonEmpty [] = fail "Received empty value for non-empty list"
156 mkNonEmpty xs = return (NonEmpty xs)
157
158 instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
159   showJSON = JSON.showJSON . fromNonEmpty
160   readJSON v = JSON.readJSON v >>= mkNonEmpty
161
162 -- | A simple type alias for non-empty strings.
163 type NonEmptyString = NonEmpty Char
164
165 -- * Ganeti types
166
167 -- | Instance disk template type.
168 $(THH.declareSADT "DiskTemplate"
169        [ ("DTDiskless",   'C.dtDiskless)
170        , ("DTFile",       'C.dtFile)
171        , ("DTSharedFile", 'C.dtSharedFile)
172        , ("DTPlain",      'C.dtPlain)
173        , ("DTBlock",      'C.dtBlock)
174        , ("DTDrbd8",      'C.dtDrbd8)
175        , ("DTRbd",        'C.dtRbd)
176        , ("DTExt",        'C.dtExt)
177        ])
178 $(THH.makeJSONInstance ''DiskTemplate)
179
180 instance HasStringRepr DiskTemplate where
181   fromStringRepr = diskTemplateFromRaw
182   toStringRepr = diskTemplateToRaw
183
184 -- | The Group allocation policy type.
185 --
186 -- Note that the order of constructors is important as the automatic
187 -- Ord instance will order them in the order they are defined, so when
188 -- changing this data type be careful about the interaction with the
189 -- desired sorting order.
190 $(THH.declareSADT "AllocPolicy"
191        [ ("AllocPreferred",   'C.allocPolicyPreferred)
192        , ("AllocLastResort",  'C.allocPolicyLastResort)
193        , ("AllocUnallocable", 'C.allocPolicyUnallocable)
194        ])
195 $(THH.makeJSONInstance ''AllocPolicy)
196
197 -- | The Instance real state type. FIXME: this could be improved to
198 -- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
199 $(THH.declareSADT "InstanceStatus"
200        [ ("StatusDown",    'C.inststAdmindown)
201        , ("StatusOffline", 'C.inststAdminoffline)
202        , ("ErrorDown",     'C.inststErrordown)
203        , ("ErrorUp",       'C.inststErrorup)
204        , ("NodeDown",      'C.inststNodedown)
205        , ("NodeOffline",   'C.inststNodeoffline)
206        , ("Running",       'C.inststRunning)
207        , ("WrongNode",     'C.inststWrongnode)
208        ])
209 $(THH.makeJSONInstance ''InstanceStatus)
210
211 -- | Migration mode.
212 $(THH.declareSADT "MigrationMode"
213      [ ("MigrationLive",    'C.htMigrationLive)
214      , ("MigrationNonLive", 'C.htMigrationNonlive)
215      ])
216 $(THH.makeJSONInstance ''MigrationMode)
217
218 -- | Verify optional checks.
219 $(THH.declareSADT "VerifyOptionalChecks"
220      [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
221      ])
222 $(THH.makeJSONInstance ''VerifyOptionalChecks)
223
224 -- | Cluster verify error codes.
225 $(THH.declareSADT "CVErrorCode"
226   [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
227   , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
228   , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
229   , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
230   , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
231   , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
232   , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
233   , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
234   , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
235   , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
236   , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
237   , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
238   , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
239   , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
240   , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
241   , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
242   , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
243   , ("CvENODEHV",               'C.cvEnodehvCode)
244   , ("CvENODELVM",              'C.cvEnodelvmCode)
245   , ("CvENODEN1",               'C.cvEnoden1Code)
246   , ("CvENODENET",              'C.cvEnodenetCode)
247   , ("CvENODEOS",               'C.cvEnodeosCode)
248   , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
249   , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
250   , ("CvENODERPC",              'C.cvEnoderpcCode)
251   , ("CvENODESSH",              'C.cvEnodesshCode)
252   , ("CvENODEVERSION",          'C.cvEnodeversionCode)
253   , ("CvENODESETUP",            'C.cvEnodesetupCode)
254   , ("CvENODETIME",             'C.cvEnodetimeCode)
255   , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
256   , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
257   , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
258   ])
259 $(THH.makeJSONInstance ''CVErrorCode)
260
261 -- | Dynamic device modification, just add\/remove version.
262 $(THH.declareSADT "DdmSimple"
263      [ ("DdmSimpleAdd",    'C.ddmAdd)
264      , ("DdmSimpleRemove", 'C.ddmRemove)
265      ])
266 $(THH.makeJSONInstance ''DdmSimple)
267
268 -- | Dynamic device modification, all operations version.
269 $(THH.declareSADT "DdmFull"
270      [ ("DdmFullAdd",    'C.ddmAdd)
271      , ("DdmFullRemove", 'C.ddmRemove)
272      , ("DdmFullModify", 'C.ddmModify)
273      ])
274 $(THH.makeJSONInstance ''DdmFull)
275
276 -- | Hypervisor type definitions.
277 $(THH.declareSADT "Hypervisor"
278   [ ( "Kvm",    'C.htKvm )
279   , ( "XenPvm", 'C.htXenPvm )
280   , ( "Chroot", 'C.htChroot )
281   , ( "XenHvm", 'C.htXenHvm )
282   , ( "Lxc",    'C.htLxc )
283   , ( "Fake",   'C.htFake )
284   ])
285 $(THH.makeJSONInstance ''Hypervisor)
286
287 -- | Oob command type.
288 $(THH.declareSADT "OobCommand"
289   [ ("OobHealth",      'C.oobHealth)
290   , ("OobPowerCycle",  'C.oobPowerCycle)
291   , ("OobPowerOff",    'C.oobPowerOff)
292   , ("OobPowerOn",     'C.oobPowerOn)
293   , ("OobPowerStatus", 'C.oobPowerStatus)
294   ])
295 $(THH.makeJSONInstance ''OobCommand)
296
297 -- | Storage type.
298 $(THH.declareSADT "StorageType"
299   [ ("StorageFile", 'C.stFile)
300   , ("StorageLvmPv", 'C.stLvmPv)
301   , ("StorageLvmVg", 'C.stLvmVg)
302   ])
303 $(THH.makeJSONInstance ''StorageType)
304
305 -- | Node evac modes.
306 $(THH.declareSADT "NodeEvacMode"
307   [ ("NEvacPrimary",   'C.iallocatorNevacPri)
308   , ("NEvacSecondary", 'C.iallocatorNevacSec)
309   , ("NEvacAll",       'C.iallocatorNevacAll)
310   ])
311 $(THH.makeJSONInstance ''NodeEvacMode)
312
313 -- | The file driver type.
314 $(THH.declareSADT "FileDriver"
315   [ ("FileLoop",   'C.fdLoop)
316   , ("FileBlktap", 'C.fdBlktap)
317   ])
318 $(THH.makeJSONInstance ''FileDriver)
319
320 -- | The instance create mode.
321 $(THH.declareSADT "InstCreateMode"
322   [ ("InstCreate",       'C.instanceCreate)
323   , ("InstImport",       'C.instanceImport)
324   , ("InstRemoteImport", 'C.instanceRemoteImport)
325   ])
326 $(THH.makeJSONInstance ''InstCreateMode)
327
328 -- | Reboot type.
329 $(THH.declareSADT "RebootType"
330   [ ("RebootSoft", 'C.instanceRebootSoft)
331   , ("RebootHard", 'C.instanceRebootHard)
332   , ("RebootFull", 'C.instanceRebootFull)
333   ])
334 $(THH.makeJSONInstance ''RebootType)
335
336 -- | Export modes.
337 $(THH.declareSADT "ExportMode"
338   [ ("ExportModeLocal",  'C.exportModeLocal)
339   , ("ExportModeRemove", 'C.exportModeRemote)
340   ])
341 $(THH.makeJSONInstance ''ExportMode)
342
343 -- | IAllocator run types (OpTestIAllocator).
344 $(THH.declareSADT "IAllocatorTestDir"
345   [ ("IAllocatorDirIn",  'C.iallocatorDirIn)
346   , ("IAllocatorDirOut", 'C.iallocatorDirOut)
347   ])
348 $(THH.makeJSONInstance ''IAllocatorTestDir)
349
350 -- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
351 $(THH.declareSADT "IAllocatorMode"
352   [ ("IAllocatorAlloc",       'C.iallocatorModeAlloc)
353   , ("IAllocatorMultiAlloc",  'C.iallocatorModeMultiAlloc)
354   , ("IAllocatorReloc",       'C.iallocatorModeReloc)
355   , ("IAllocatorNodeEvac",    'C.iallocatorModeNodeEvac)
356   , ("IAllocatorChangeGroup", 'C.iallocatorModeChgGroup)
357   ])
358 $(THH.makeJSONInstance ''IAllocatorMode)
359
360 -- | Netork mode.
361 $(THH.declareSADT "NICMode"
362   [ ("NMBridged", 'C.nicModeBridged)
363   , ("NMRouted",  'C.nicModeRouted)
364   , ("NMOvs",     'C.nicModeOvs)
365   ])
366 $(THH.makeJSONInstance ''NICMode)
367
368 -- | The JobStatus data type. Note that this is ordered especially
369 -- such that greater\/lesser comparison on values of this type makes
370 -- sense.
371 $(THH.declareSADT "JobStatus"
372        [ ("JOB_STATUS_QUEUED",    'C.jobStatusQueued)
373        , ("JOB_STATUS_WAITING",   'C.jobStatusWaiting)
374        , ("JOB_STATUS_CANCELING", 'C.jobStatusCanceling)
375        , ("JOB_STATUS_RUNNING",   'C.jobStatusRunning)
376        , ("JOB_STATUS_CANCELED",  'C.jobStatusCanceled)
377        , ("JOB_STATUS_SUCCESS",   'C.jobStatusSuccess)
378        , ("JOB_STATUS_ERROR",     'C.jobStatusError)
379        ])
380 $(THH.makeJSONInstance ''JobStatus)
381
382 -- | Finalized job status.
383 $(THH.declareSADT "FinalizedJobStatus"
384   [ ("JobStatusCanceled",   'C.jobStatusCanceled)
385   , ("JobStatusSuccessful", 'C.jobStatusSuccess)
386   , ("JobStatusFailed",     'C.jobStatusError)
387   ])
388 $(THH.makeJSONInstance ''FinalizedJobStatus)
389
390 -- | The Ganeti job type.
391 newtype JobId = JobId { fromJobId :: Int }
392   deriving (Show, Eq)
393
394 -- | Builds a job ID.
395 makeJobId :: (Monad m) => Int -> m JobId
396 makeJobId i | i >= 0 = return $ JobId i
397             | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
398
399 -- | Builds a job ID from a string.
400 makeJobIdS :: (Monad m) => String -> m JobId
401 makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
402
403 -- | Parses a job ID.
404 parseJobId :: (Monad m) => JSON.JSValue -> m JobId
405 parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
406 parseJobId (JSON.JSRational _ x) =
407   if denominator x /= 1
408     then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
409     -- FIXME: potential integer overflow here on 32-bit platforms
410     else makeJobId . fromIntegral . numerator $ x
411 parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
412
413 instance JSON.JSON JobId where
414   showJSON = JSON.showJSON . fromJobId
415   readJSON = parseJobId
416
417 -- | Relative job ID type alias.
418 type RelativeJobId = Negative Int
419
420 -- | Job ID dependency.
421 data JobIdDep = JobDepRelative RelativeJobId
422               | JobDepAbsolute JobId
423                 deriving (Show, Eq)
424
425 instance JSON.JSON JobIdDep where
426   showJSON (JobDepRelative i) = showJSON i
427   showJSON (JobDepAbsolute i) = showJSON i
428   readJSON v =
429     case JSON.readJSON v::JSON.Result (Negative Int) of
430       -- first try relative dependency, usually most common
431       JSON.Ok r -> return $ JobDepRelative r
432       JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
433
434 -- | Job Dependency type.
435 data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
436                      deriving (Show, Eq)
437
438 instance JSON JobDependency where
439   showJSON (JobDependency dep status) = showJSON (dep, status)
440   readJSON = liftM (uncurry JobDependency) . readJSON
441
442 -- | Valid opcode priorities for submit.
443 $(THH.declareIADT "OpSubmitPriority"
444   [ ("OpPrioLow",    'C.opPrioLow)
445   , ("OpPrioNormal", 'C.opPrioNormal)
446   , ("OpPrioHigh",   'C.opPrioHigh)
447   ])
448 $(THH.makeJSONInstance ''OpSubmitPriority)
449
450 -- | Our ADT for the OpCode status at runtime (while in a job).
451 $(THH.declareSADT "OpStatus"
452   [ ("OP_STATUS_QUEUED",    'C.opStatusQueued)
453   , ("OP_STATUS_WAITING",   'C.opStatusWaiting)
454   , ("OP_STATUS_CANCELING", 'C.opStatusCanceling)
455   , ("OP_STATUS_RUNNING",   'C.opStatusRunning)
456   , ("OP_STATUS_CANCELED",  'C.opStatusCanceled)
457   , ("OP_STATUS_SUCCESS",   'C.opStatusSuccess)
458   , ("OP_STATUS_ERROR",     'C.opStatusError)
459   ])
460 $(THH.makeJSONInstance ''OpStatus)
461
462 -- | Type for the job message type.
463 $(THH.declareSADT "ELogType"
464   [ ("ELogMessage",      'C.elogMessage)
465   , ("ELogRemoteImport", 'C.elogRemoteImport)
466   , ("ELogJqueueTest",   'C.elogJqueueTest)
467   ])
468 $(THH.makeJSONInstance ''ELogType)