Complete the instance OpCodes and parameters
[ganeti-local] / htools / 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   , NonEmpty
50   , fromNonEmpty
51   , mkNonEmpty
52   , NonEmptyString
53   , MigrationMode(..)
54   , VerifyOptionalChecks(..)
55   , DdmSimple(..)
56   , DdmFull(..)
57   , CVErrorCode(..)
58   , cVErrorCodeToRaw
59   , Hypervisor(..)
60   , OobCommand(..)
61   , StorageType(..)
62   , NodeEvacMode(..)
63   , FileDriver(..)
64   , InstCreateMode(..)
65   , RebootType(..)
66   ) where
67
68 import qualified Text.JSON as JSON
69
70 import qualified Ganeti.Constants as C
71 import qualified Ganeti.THH as THH
72 import Ganeti.JSON
73
74 -- * Generic types
75
76 -- | Type that holds a non-negative value.
77 newtype NonNegative a = NonNegative { fromNonNegative :: a }
78   deriving (Show, Read, Eq)
79
80 -- | Smart constructor for 'NonNegative'.
81 mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
82 mkNonNegative i | i >= 0 = return (NonNegative i)
83                 | otherwise = fail $ "Invalid value for non-negative type '" ++
84                               show i ++ "'"
85
86 instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
87   showJSON = JSON.showJSON . fromNonNegative
88   readJSON v = JSON.readJSON v >>= mkNonNegative
89
90 -- | Type that holds a positive value.
91 newtype Positive a = Positive { fromPositive :: a }
92   deriving (Show, Read, Eq)
93
94 -- | Smart constructor for 'Positive'.
95 mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
96 mkPositive i | i > 0 = return (Positive i)
97              | otherwise = fail $ "Invalid value for positive type '" ++
98                            show i ++ "'"
99
100 instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
101   showJSON = JSON.showJSON . fromPositive
102   readJSON v = JSON.readJSON v >>= mkPositive
103
104 -- | Type that holds a non-null list.
105 newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
106   deriving (Show, Read, Eq)
107
108 -- | Smart constructor for 'NonEmpty'.
109 mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
110 mkNonEmpty [] = fail "Received empty value for non-empty list"
111 mkNonEmpty xs = return (NonEmpty xs)
112
113 instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
114   showJSON = JSON.showJSON . fromNonEmpty
115   readJSON v = JSON.readJSON v >>= mkNonEmpty
116
117 -- | A simple type alias for non-empty strings.
118 type NonEmptyString = NonEmpty Char
119
120 -- * Ganeti types
121
122 -- | Instance disk template type.
123 $(THH.declareSADT "DiskTemplate"
124        [ ("DTDiskless",   'C.dtDiskless)
125        , ("DTFile",       'C.dtFile)
126        , ("DTSharedFile", 'C.dtSharedFile)
127        , ("DTPlain",      'C.dtPlain)
128        , ("DTBlock",      'C.dtBlock)
129        , ("DTDrbd8",      'C.dtDrbd8)
130        , ("DTRbd",        'C.dtRbd)
131        ])
132 $(THH.makeJSONInstance ''DiskTemplate)
133
134 instance HasStringRepr DiskTemplate where
135   fromStringRepr = diskTemplateFromRaw
136   toStringRepr = diskTemplateToRaw
137
138 -- | The Group allocation policy type.
139 --
140 -- Note that the order of constructors is important as the automatic
141 -- Ord instance will order them in the order they are defined, so when
142 -- changing this data type be careful about the interaction with the
143 -- desired sorting order.
144 $(THH.declareSADT "AllocPolicy"
145        [ ("AllocPreferred",   'C.allocPolicyPreferred)
146        , ("AllocLastResort",  'C.allocPolicyLastResort)
147        , ("AllocUnallocable", 'C.allocPolicyUnallocable)
148        ])
149 $(THH.makeJSONInstance ''AllocPolicy)
150
151 -- | The Instance real state type. FIXME: this could be improved to
152 -- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
153 $(THH.declareSADT "InstanceStatus"
154        [ ("StatusDown",    'C.inststAdmindown)
155        , ("StatusOffline", 'C.inststAdminoffline)
156        , ("ErrorDown",     'C.inststErrordown)
157        , ("ErrorUp",       'C.inststErrorup)
158        , ("NodeDown",      'C.inststNodedown)
159        , ("NodeOffline",   'C.inststNodeoffline)
160        , ("Running",       'C.inststRunning)
161        , ("WrongNode",     'C.inststWrongnode)
162        ])
163 $(THH.makeJSONInstance ''InstanceStatus)
164
165 -- | Migration mode.
166 $(THH.declareSADT "MigrationMode"
167      [ ("MigrationLive",    'C.htMigrationLive)
168      , ("MigrationNonLive", 'C.htMigrationNonlive)
169      ])
170 $(THH.makeJSONInstance ''MigrationMode)
171
172 -- | Verify optional checks.
173 $(THH.declareSADT "VerifyOptionalChecks"
174      [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
175      ])
176 $(THH.makeJSONInstance ''VerifyOptionalChecks)
177
178 -- | Cluster verify error codes.
179 $(THH.declareSADT "CVErrorCode"
180   [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
181   , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
182   , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
183   , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
184   , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
185   , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
186   , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
187   , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
188   , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
189   , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
190   , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
191   , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
192   , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
193   , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
194   , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
195   , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
196   , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
197   , ("CvENODEHV",               'C.cvEnodehvCode)
198   , ("CvENODELVM",              'C.cvEnodelvmCode)
199   , ("CvENODEN1",               'C.cvEnoden1Code)
200   , ("CvENODENET",              'C.cvEnodenetCode)
201   , ("CvENODEOS",               'C.cvEnodeosCode)
202   , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
203   , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
204   , ("CvENODERPC",              'C.cvEnoderpcCode)
205   , ("CvENODESSH",              'C.cvEnodesshCode)
206   , ("CvENODEVERSION",          'C.cvEnodeversionCode)
207   , ("CvENODESETUP",            'C.cvEnodesetupCode)
208   , ("CvENODETIME",             'C.cvEnodetimeCode)
209   , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
210   , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
211   , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
212   ])
213 $(THH.makeJSONInstance ''CVErrorCode)
214
215 -- | Dynamic device modification, just add\/remove version.
216 $(THH.declareSADT "DdmSimple"
217      [ ("DdmSimpleAdd",    'C.ddmAdd)
218      , ("DdmSimpleRemove", 'C.ddmRemove)
219      ])
220 $(THH.makeJSONInstance ''DdmSimple)
221
222 -- | Dynamic device modification, all operations version.
223 $(THH.declareSADT "DdmFull"
224      [ ("DdmFullAdd",    'C.ddmAdd)
225      , ("DdmFullRemove", 'C.ddmRemove)
226      , ("DdmFullModify", 'C.ddmModify)
227      ])
228 $(THH.makeJSONInstance ''DdmFull)
229
230 -- | Hypervisor type definitions.
231 $(THH.declareSADT "Hypervisor"
232   [ ( "Kvm",    'C.htKvm )
233   , ( "XenPvm", 'C.htXenPvm )
234   , ( "Chroot", 'C.htChroot )
235   , ( "XenHvm", 'C.htXenHvm )
236   , ( "Lxc",    'C.htLxc )
237   , ( "Fake",   'C.htFake )
238   ])
239 $(THH.makeJSONInstance ''Hypervisor)
240
241 -- | Oob command type.
242 $(THH.declareSADT "OobCommand"
243   [ ("OobHealth",      'C.oobHealth)
244   , ("OobPowerCycle",  'C.oobPowerCycle)
245   , ("OobPowerOff",    'C.oobPowerOff)
246   , ("OobPowerOn",     'C.oobPowerOn)
247   , ("OobPowerStatus", 'C.oobPowerStatus)
248   ])
249 $(THH.makeJSONInstance ''OobCommand)
250
251 -- | Storage type.
252 $(THH.declareSADT "StorageType"
253   [ ("StorageFile", 'C.stFile)
254   , ("StorageLvmPv", 'C.stLvmPv)
255   , ("StorageLvmVg", 'C.stLvmVg)
256   ])
257 $(THH.makeJSONInstance ''StorageType)
258
259 -- | Node evac modes.
260 $(THH.declareSADT "NodeEvacMode"
261   [ ("NEvacPrimary",   'C.iallocatorNevacPri)
262   , ("NEvacSecondary", 'C.iallocatorNevacSec)
263   , ("NEvacAll",       'C.iallocatorNevacAll)
264   ])
265 $(THH.makeJSONInstance ''NodeEvacMode)
266
267 -- | The file driver type.
268 $(THH.declareSADT "FileDriver"
269   [ ("FileLoop",   'C.fdLoop)
270   , ("FileBlktap", 'C.fdBlktap)
271   ])
272 $(THH.makeJSONInstance ''FileDriver)
273
274 -- | The instance create mode.
275 $(THH.declareSADT "InstCreateMode"
276   [ ("InstCreate",       'C.instanceCreate)
277   , ("InstImport",       'C.instanceImport)
278   , ("InstRemoteImport", 'C.instanceRemoteImport)
279   ])
280 $(THH.makeJSONInstance ''InstCreateMode)
281
282 -- | Reboot type.
283 $(THH.declareSADT "RebootType"
284   [ ("RebootSoft", 'C.instanceRebootSoft)
285   , ("RebootHard", 'C.instanceRebootHard)
286   , ("RebootFull", 'C.instanceRebootFull)
287   ])
288 $(THH.makeJSONInstance ''RebootType)