Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Types.hs @ c67b908a

History | View | Annotate | Download (12.5 kB)

1 5e9deac0 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 5e9deac0 Iustin Pop
3 5e9deac0 Iustin Pop
{-| Some common Ganeti types.
4 5e9deac0 Iustin Pop
5 5e9deac0 Iustin Pop
This holds types common to both core work, and to htools. Types that
6 5e9deac0 Iustin Pop
are very core specific (e.g. configuration objects) should go in
7 5e9deac0 Iustin Pop
'Ganeti.Objects', while types that are specific to htools in-memory
8 5e9deac0 Iustin Pop
representation should go into 'Ganeti.HTools.Types'.
9 5e9deac0 Iustin Pop
10 5e9deac0 Iustin Pop
-}
11 5e9deac0 Iustin Pop
12 5e9deac0 Iustin Pop
{-
13 5e9deac0 Iustin Pop
14 5e9deac0 Iustin Pop
Copyright (C) 2012 Google Inc.
15 5e9deac0 Iustin Pop
16 5e9deac0 Iustin Pop
This program is free software; you can redistribute it and/or modify
17 5e9deac0 Iustin Pop
it under the terms of the GNU General Public License as published by
18 5e9deac0 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
19 5e9deac0 Iustin Pop
(at your option) any later version.
20 5e9deac0 Iustin Pop
21 5e9deac0 Iustin Pop
This program is distributed in the hope that it will be useful, but
22 5e9deac0 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
23 5e9deac0 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
24 5e9deac0 Iustin Pop
General Public License for more details.
25 5e9deac0 Iustin Pop
26 5e9deac0 Iustin Pop
You should have received a copy of the GNU General Public License
27 5e9deac0 Iustin Pop
along with this program; if not, write to the Free Software
28 5e9deac0 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
29 5e9deac0 Iustin Pop
02110-1301, USA.
30 5e9deac0 Iustin Pop
31 5e9deac0 Iustin Pop
-}
32 5e9deac0 Iustin Pop
33 5e9deac0 Iustin Pop
module Ganeti.Types
34 5e9deac0 Iustin Pop
  ( AllocPolicy(..)
35 5e9deac0 Iustin Pop
  , allocPolicyFromRaw
36 5e9deac0 Iustin Pop
  , allocPolicyToRaw
37 5e9deac0 Iustin Pop
  , InstanceStatus(..)
38 5e9deac0 Iustin Pop
  , instanceStatusFromRaw
39 5e9deac0 Iustin Pop
  , instanceStatusToRaw
40 5e9deac0 Iustin Pop
  , DiskTemplate(..)
41 5e9deac0 Iustin Pop
  , diskTemplateToRaw
42 5e9deac0 Iustin Pop
  , diskTemplateFromRaw
43 edb5a1c8 Iustin Pop
  , NonNegative
44 edb5a1c8 Iustin Pop
  , fromNonNegative
45 edb5a1c8 Iustin Pop
  , mkNonNegative
46 edb5a1c8 Iustin Pop
  , Positive
47 edb5a1c8 Iustin Pop
  , fromPositive
48 edb5a1c8 Iustin Pop
  , mkPositive
49 c67b908a Iustin Pop
  , Negative
50 c67b908a Iustin Pop
  , fromNegative
51 c67b908a Iustin Pop
  , mkNegative
52 edb5a1c8 Iustin Pop
  , NonEmpty
53 edb5a1c8 Iustin Pop
  , fromNonEmpty
54 edb5a1c8 Iustin Pop
  , mkNonEmpty
55 6a28e02c Iustin Pop
  , NonEmptyString
56 d696bbef Iustin Pop
  , MigrationMode(..)
57 d696bbef Iustin Pop
  , VerifyOptionalChecks(..)
58 d696bbef Iustin Pop
  , DdmSimple(..)
59 c2d3219b Iustin Pop
  , DdmFull(..)
60 d696bbef Iustin Pop
  , CVErrorCode(..)
61 d696bbef Iustin Pop
  , cVErrorCodeToRaw
62 22381768 Iustin Pop
  , Hypervisor(..)
63 6a28e02c Iustin Pop
  , OobCommand(..)
64 48755fac Iustin Pop
  , StorageType(..)
65 6a28e02c Iustin Pop
  , NodeEvacMode(..)
66 c65621d7 Iustin Pop
  , FileDriver(..)
67 6d558717 Iustin Pop
  , InstCreateMode(..)
68 c2d3219b Iustin Pop
  , RebootType(..)
69 398e9066 Iustin Pop
  , ExportMode(..)
70 a3f02317 Iustin Pop
  , IAllocatorTestDir(..)
71 a3f02317 Iustin Pop
  , IAllocatorMode(..)
72 a3f02317 Iustin Pop
  , iAllocatorModeToRaw
73 8d239fa4 Iustin Pop
  , NetworkType(..)
74 8d239fa4 Iustin Pop
  , networkTypeToRaw
75 497beee2 Iustin Pop
  , NICMode(..)
76 497beee2 Iustin Pop
  , nICModeToRaw
77 6903fea0 Iustin Pop
  , FinalizedJobStatus(..)
78 6903fea0 Iustin Pop
  , finalizedJobStatusToRaw
79 c48711d5 Iustin Pop
  , JobId
80 c48711d5 Iustin Pop
  , fromJobId
81 c48711d5 Iustin Pop
  , makeJobId
82 5e9deac0 Iustin Pop
  ) where
83 5e9deac0 Iustin Pop
84 edb5a1c8 Iustin Pop
import qualified Text.JSON as JSON
85 c48711d5 Iustin Pop
import Data.Ratio (numerator, denominator)
86 edb5a1c8 Iustin Pop
87 5e9deac0 Iustin Pop
import qualified Ganeti.Constants as C
88 5e9deac0 Iustin Pop
import qualified Ganeti.THH as THH
89 edc1acde Iustin Pop
import Ganeti.JSON
90 c48711d5 Iustin Pop
import Ganeti.Utils
91 5e9deac0 Iustin Pop
92 edb5a1c8 Iustin Pop
-- * Generic types
93 edb5a1c8 Iustin Pop
94 edb5a1c8 Iustin Pop
-- | Type that holds a non-negative value.
95 edb5a1c8 Iustin Pop
newtype NonNegative a = NonNegative { fromNonNegative :: a }
96 139c0683 Iustin Pop
  deriving (Show, Eq)
97 edb5a1c8 Iustin Pop
98 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonNegative'.
99 edb5a1c8 Iustin Pop
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
100 edb5a1c8 Iustin Pop
mkNonNegative i | i >= 0 = return (NonNegative i)
101 edb5a1c8 Iustin Pop
                | otherwise = fail $ "Invalid value for non-negative type '" ++
102 edb5a1c8 Iustin Pop
                              show i ++ "'"
103 edb5a1c8 Iustin Pop
104 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
105 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonNegative
106 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonNegative
107 edb5a1c8 Iustin Pop
108 edb5a1c8 Iustin Pop
-- | Type that holds a positive value.
109 edb5a1c8 Iustin Pop
newtype Positive a = Positive { fromPositive :: a }
110 139c0683 Iustin Pop
  deriving (Show, Eq)
111 edb5a1c8 Iustin Pop
112 edb5a1c8 Iustin Pop
-- | Smart constructor for 'Positive'.
113 edb5a1c8 Iustin Pop
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
114 edb5a1c8 Iustin Pop
mkPositive i | i > 0 = return (Positive i)
115 edb5a1c8 Iustin Pop
             | otherwise = fail $ "Invalid value for positive type '" ++
116 edb5a1c8 Iustin Pop
                           show i ++ "'"
117 edb5a1c8 Iustin Pop
118 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
119 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromPositive
120 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkPositive
121 edb5a1c8 Iustin Pop
122 c67b908a Iustin Pop
-- | Type that holds a negative value.
123 c67b908a Iustin Pop
newtype Negative a = Negative { fromNegative :: a }
124 c67b908a Iustin Pop
  deriving (Show, Eq)
125 c67b908a Iustin Pop
126 c67b908a Iustin Pop
-- | Smart constructor for 'Negative'.
127 c67b908a Iustin Pop
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
128 c67b908a Iustin Pop
mkNegative i | i < 0 = return (Negative i)
129 c67b908a Iustin Pop
             | otherwise = fail $ "Invalid value for negative type '" ++
130 c67b908a Iustin Pop
                           show i ++ "'"
131 c67b908a Iustin Pop
132 c67b908a Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
133 c67b908a Iustin Pop
  showJSON = JSON.showJSON . fromNegative
134 c67b908a Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNegative
135 c67b908a Iustin Pop
136 edb5a1c8 Iustin Pop
-- | Type that holds a non-null list.
137 edb5a1c8 Iustin Pop
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
138 139c0683 Iustin Pop
  deriving (Show, Eq)
139 edb5a1c8 Iustin Pop
140 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonEmpty'.
141 edb5a1c8 Iustin Pop
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
142 edb5a1c8 Iustin Pop
mkNonEmpty [] = fail "Received empty value for non-empty list"
143 edb5a1c8 Iustin Pop
mkNonEmpty xs = return (NonEmpty xs)
144 edb5a1c8 Iustin Pop
145 edb5a1c8 Iustin Pop
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
146 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonEmpty
147 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonEmpty
148 edb5a1c8 Iustin Pop
149 6a28e02c Iustin Pop
-- | A simple type alias for non-empty strings.
150 6a28e02c Iustin Pop
type NonEmptyString = NonEmpty Char
151 6a28e02c Iustin Pop
152 edb5a1c8 Iustin Pop
-- * Ganeti types
153 edb5a1c8 Iustin Pop
154 5e9deac0 Iustin Pop
-- | Instance disk template type.
155 5e9deac0 Iustin Pop
$(THH.declareSADT "DiskTemplate"
156 5e9deac0 Iustin Pop
       [ ("DTDiskless",   'C.dtDiskless)
157 5e9deac0 Iustin Pop
       , ("DTFile",       'C.dtFile)
158 5e9deac0 Iustin Pop
       , ("DTSharedFile", 'C.dtSharedFile)
159 5e9deac0 Iustin Pop
       , ("DTPlain",      'C.dtPlain)
160 5e9deac0 Iustin Pop
       , ("DTBlock",      'C.dtBlock)
161 5e9deac0 Iustin Pop
       , ("DTDrbd8",      'C.dtDrbd8)
162 5e9deac0 Iustin Pop
       , ("DTRbd",        'C.dtRbd)
163 5e9deac0 Iustin Pop
       ])
164 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''DiskTemplate)
165 5e9deac0 Iustin Pop
166 edc1acde Iustin Pop
instance HasStringRepr DiskTemplate where
167 edc1acde Iustin Pop
  fromStringRepr = diskTemplateFromRaw
168 edc1acde Iustin Pop
  toStringRepr = diskTemplateToRaw
169 edc1acde Iustin Pop
170 5e9deac0 Iustin Pop
-- | The Group allocation policy type.
171 5e9deac0 Iustin Pop
--
172 5e9deac0 Iustin Pop
-- Note that the order of constructors is important as the automatic
173 5e9deac0 Iustin Pop
-- Ord instance will order them in the order they are defined, so when
174 5e9deac0 Iustin Pop
-- changing this data type be careful about the interaction with the
175 5e9deac0 Iustin Pop
-- desired sorting order.
176 5e9deac0 Iustin Pop
$(THH.declareSADT "AllocPolicy"
177 5e9deac0 Iustin Pop
       [ ("AllocPreferred",   'C.allocPolicyPreferred)
178 5e9deac0 Iustin Pop
       , ("AllocLastResort",  'C.allocPolicyLastResort)
179 5e9deac0 Iustin Pop
       , ("AllocUnallocable", 'C.allocPolicyUnallocable)
180 5e9deac0 Iustin Pop
       ])
181 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''AllocPolicy)
182 5e9deac0 Iustin Pop
183 5e9deac0 Iustin Pop
-- | The Instance real state type. FIXME: this could be improved to
184 5e9deac0 Iustin Pop
-- just wrap a /NormalState AdminStatus | ErrorState ErrorCondition/.
185 5e9deac0 Iustin Pop
$(THH.declareSADT "InstanceStatus"
186 5e9deac0 Iustin Pop
       [ ("StatusDown",    'C.inststAdmindown)
187 5e9deac0 Iustin Pop
       , ("StatusOffline", 'C.inststAdminoffline)
188 5e9deac0 Iustin Pop
       , ("ErrorDown",     'C.inststErrordown)
189 5e9deac0 Iustin Pop
       , ("ErrorUp",       'C.inststErrorup)
190 5e9deac0 Iustin Pop
       , ("NodeDown",      'C.inststNodedown)
191 5e9deac0 Iustin Pop
       , ("NodeOffline",   'C.inststNodeoffline)
192 5e9deac0 Iustin Pop
       , ("Running",       'C.inststRunning)
193 5e9deac0 Iustin Pop
       , ("WrongNode",     'C.inststWrongnode)
194 5e9deac0 Iustin Pop
       ])
195 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''InstanceStatus)
196 d696bbef Iustin Pop
197 d696bbef Iustin Pop
-- | Migration mode.
198 d696bbef Iustin Pop
$(THH.declareSADT "MigrationMode"
199 d696bbef Iustin Pop
     [ ("MigrationLive",    'C.htMigrationLive)
200 d696bbef Iustin Pop
     , ("MigrationNonLive", 'C.htMigrationNonlive)
201 d696bbef Iustin Pop
     ])
202 d696bbef Iustin Pop
$(THH.makeJSONInstance ''MigrationMode)
203 d696bbef Iustin Pop
204 d696bbef Iustin Pop
-- | Verify optional checks.
205 d696bbef Iustin Pop
$(THH.declareSADT "VerifyOptionalChecks"
206 d696bbef Iustin Pop
     [ ("VerifyNPlusOneMem", 'C.verifyNplusoneMem)
207 d696bbef Iustin Pop
     ])
208 d696bbef Iustin Pop
$(THH.makeJSONInstance ''VerifyOptionalChecks)
209 d696bbef Iustin Pop
210 d696bbef Iustin Pop
-- | Cluster verify error codes.
211 d696bbef Iustin Pop
$(THH.declareSADT "CVErrorCode"
212 d696bbef Iustin Pop
  [ ("CvECLUSTERCFG",           'C.cvEclustercfgCode)
213 d696bbef Iustin Pop
  , ("CvECLUSTERCERT",          'C.cvEclustercertCode)
214 d696bbef Iustin Pop
  , ("CvECLUSTERFILECHECK",     'C.cvEclusterfilecheckCode)
215 d696bbef Iustin Pop
  , ("CvECLUSTERDANGLINGNODES", 'C.cvEclusterdanglingnodesCode)
216 d696bbef Iustin Pop
  , ("CvECLUSTERDANGLINGINST",  'C.cvEclusterdanglinginstCode)
217 d696bbef Iustin Pop
  , ("CvEINSTANCEBADNODE",      'C.cvEinstancebadnodeCode)
218 d696bbef Iustin Pop
  , ("CvEINSTANCEDOWN",         'C.cvEinstancedownCode)
219 d696bbef Iustin Pop
  , ("CvEINSTANCELAYOUT",       'C.cvEinstancelayoutCode)
220 d696bbef Iustin Pop
  , ("CvEINSTANCEMISSINGDISK",  'C.cvEinstancemissingdiskCode)
221 d696bbef Iustin Pop
  , ("CvEINSTANCEFAULTYDISK",   'C.cvEinstancefaultydiskCode)
222 d696bbef Iustin Pop
  , ("CvEINSTANCEWRONGNODE",    'C.cvEinstancewrongnodeCode)
223 d696bbef Iustin Pop
  , ("CvEINSTANCESPLITGROUPS",  'C.cvEinstancesplitgroupsCode)
224 d696bbef Iustin Pop
  , ("CvEINSTANCEPOLICY",       'C.cvEinstancepolicyCode)
225 d696bbef Iustin Pop
  , ("CvENODEDRBD",             'C.cvEnodedrbdCode)
226 d696bbef Iustin Pop
  , ("CvENODEDRBDHELPER",       'C.cvEnodedrbdhelperCode)
227 d696bbef Iustin Pop
  , ("CvENODEFILECHECK",        'C.cvEnodefilecheckCode)
228 d696bbef Iustin Pop
  , ("CvENODEHOOKS",            'C.cvEnodehooksCode)
229 d696bbef Iustin Pop
  , ("CvENODEHV",               'C.cvEnodehvCode)
230 d696bbef Iustin Pop
  , ("CvENODELVM",              'C.cvEnodelvmCode)
231 d696bbef Iustin Pop
  , ("CvENODEN1",               'C.cvEnoden1Code)
232 d696bbef Iustin Pop
  , ("CvENODENET",              'C.cvEnodenetCode)
233 d696bbef Iustin Pop
  , ("CvENODEOS",               'C.cvEnodeosCode)
234 d696bbef Iustin Pop
  , ("CvENODEORPHANINSTANCE",   'C.cvEnodeorphaninstanceCode)
235 d696bbef Iustin Pop
  , ("CvENODEORPHANLV",         'C.cvEnodeorphanlvCode)
236 d696bbef Iustin Pop
  , ("CvENODERPC",              'C.cvEnoderpcCode)
237 d696bbef Iustin Pop
  , ("CvENODESSH",              'C.cvEnodesshCode)
238 d696bbef Iustin Pop
  , ("CvENODEVERSION",          'C.cvEnodeversionCode)
239 d696bbef Iustin Pop
  , ("CvENODESETUP",            'C.cvEnodesetupCode)
240 d696bbef Iustin Pop
  , ("CvENODETIME",             'C.cvEnodetimeCode)
241 d696bbef Iustin Pop
  , ("CvENODEOOBPATH",          'C.cvEnodeoobpathCode)
242 d696bbef Iustin Pop
  , ("CvENODEUSERSCRIPTS",      'C.cvEnodeuserscriptsCode)
243 d696bbef Iustin Pop
  , ("CvENODEFILESTORAGEPATHS", 'C.cvEnodefilestoragepathsCode)
244 d696bbef Iustin Pop
  ])
245 d696bbef Iustin Pop
$(THH.makeJSONInstance ''CVErrorCode)
246 d696bbef Iustin Pop
247 d696bbef Iustin Pop
-- | Dynamic device modification, just add\/remove version.
248 d696bbef Iustin Pop
$(THH.declareSADT "DdmSimple"
249 d696bbef Iustin Pop
     [ ("DdmSimpleAdd",    'C.ddmAdd)
250 d696bbef Iustin Pop
     , ("DdmSimpleRemove", 'C.ddmRemove)
251 d696bbef Iustin Pop
     ])
252 d696bbef Iustin Pop
$(THH.makeJSONInstance ''DdmSimple)
253 22381768 Iustin Pop
254 c2d3219b Iustin Pop
-- | Dynamic device modification, all operations version.
255 c2d3219b Iustin Pop
$(THH.declareSADT "DdmFull"
256 c2d3219b Iustin Pop
     [ ("DdmFullAdd",    'C.ddmAdd)
257 c2d3219b Iustin Pop
     , ("DdmFullRemove", 'C.ddmRemove)
258 c2d3219b Iustin Pop
     , ("DdmFullModify", 'C.ddmModify)
259 c2d3219b Iustin Pop
     ])
260 c2d3219b Iustin Pop
$(THH.makeJSONInstance ''DdmFull)
261 c2d3219b Iustin Pop
262 22381768 Iustin Pop
-- | Hypervisor type definitions.
263 22381768 Iustin Pop
$(THH.declareSADT "Hypervisor"
264 22381768 Iustin Pop
  [ ( "Kvm",    'C.htKvm )
265 22381768 Iustin Pop
  , ( "XenPvm", 'C.htXenPvm )
266 22381768 Iustin Pop
  , ( "Chroot", 'C.htChroot )
267 22381768 Iustin Pop
  , ( "XenHvm", 'C.htXenHvm )
268 22381768 Iustin Pop
  , ( "Lxc",    'C.htLxc )
269 22381768 Iustin Pop
  , ( "Fake",   'C.htFake )
270 22381768 Iustin Pop
  ])
271 22381768 Iustin Pop
$(THH.makeJSONInstance ''Hypervisor)
272 48755fac Iustin Pop
273 6a28e02c Iustin Pop
-- | Oob command type.
274 6a28e02c Iustin Pop
$(THH.declareSADT "OobCommand"
275 6a28e02c Iustin Pop
  [ ("OobHealth",      'C.oobHealth)
276 6a28e02c Iustin Pop
  , ("OobPowerCycle",  'C.oobPowerCycle)
277 6a28e02c Iustin Pop
  , ("OobPowerOff",    'C.oobPowerOff)
278 6a28e02c Iustin Pop
  , ("OobPowerOn",     'C.oobPowerOn)
279 6a28e02c Iustin Pop
  , ("OobPowerStatus", 'C.oobPowerStatus)
280 6a28e02c Iustin Pop
  ])
281 6a28e02c Iustin Pop
$(THH.makeJSONInstance ''OobCommand)
282 6a28e02c Iustin Pop
283 48755fac Iustin Pop
-- | Storage type.
284 48755fac Iustin Pop
$(THH.declareSADT "StorageType"
285 48755fac Iustin Pop
  [ ("StorageFile", 'C.stFile)
286 48755fac Iustin Pop
  , ("StorageLvmPv", 'C.stLvmPv)
287 48755fac Iustin Pop
  , ("StorageLvmVg", 'C.stLvmVg)
288 48755fac Iustin Pop
  ])
289 48755fac Iustin Pop
$(THH.makeJSONInstance ''StorageType)
290 6a28e02c Iustin Pop
291 6a28e02c Iustin Pop
-- | Node evac modes.
292 6a28e02c Iustin Pop
$(THH.declareSADT "NodeEvacMode"
293 6a28e02c Iustin Pop
  [ ("NEvacPrimary",   'C.iallocatorNevacPri)
294 6a28e02c Iustin Pop
  , ("NEvacSecondary", 'C.iallocatorNevacSec)
295 6a28e02c Iustin Pop
  , ("NEvacAll",       'C.iallocatorNevacAll)
296 6a28e02c Iustin Pop
  ])
297 6a28e02c Iustin Pop
$(THH.makeJSONInstance ''NodeEvacMode)
298 c65621d7 Iustin Pop
299 c65621d7 Iustin Pop
-- | The file driver type.
300 c65621d7 Iustin Pop
$(THH.declareSADT "FileDriver"
301 c65621d7 Iustin Pop
  [ ("FileLoop",   'C.fdLoop)
302 c65621d7 Iustin Pop
  , ("FileBlktap", 'C.fdBlktap)
303 c65621d7 Iustin Pop
  ])
304 c65621d7 Iustin Pop
$(THH.makeJSONInstance ''FileDriver)
305 6d558717 Iustin Pop
306 6d558717 Iustin Pop
-- | The instance create mode.
307 6d558717 Iustin Pop
$(THH.declareSADT "InstCreateMode"
308 6d558717 Iustin Pop
  [ ("InstCreate",       'C.instanceCreate)
309 6d558717 Iustin Pop
  , ("InstImport",       'C.instanceImport)
310 6d558717 Iustin Pop
  , ("InstRemoteImport", 'C.instanceRemoteImport)
311 6d558717 Iustin Pop
  ])
312 6d558717 Iustin Pop
$(THH.makeJSONInstance ''InstCreateMode)
313 c2d3219b Iustin Pop
314 c2d3219b Iustin Pop
-- | Reboot type.
315 c2d3219b Iustin Pop
$(THH.declareSADT "RebootType"
316 c2d3219b Iustin Pop
  [ ("RebootSoft", 'C.instanceRebootSoft)
317 c2d3219b Iustin Pop
  , ("RebootHard", 'C.instanceRebootHard)
318 c2d3219b Iustin Pop
  , ("RebootFull", 'C.instanceRebootFull)
319 c2d3219b Iustin Pop
  ])
320 c2d3219b Iustin Pop
$(THH.makeJSONInstance ''RebootType)
321 398e9066 Iustin Pop
322 398e9066 Iustin Pop
-- | Export modes.
323 398e9066 Iustin Pop
$(THH.declareSADT "ExportMode"
324 398e9066 Iustin Pop
  [ ("ExportModeLocal",  'C.exportModeLocal)
325 398e9066 Iustin Pop
  , ("ExportModeRemove", 'C.exportModeRemote)
326 398e9066 Iustin Pop
  ])
327 398e9066 Iustin Pop
$(THH.makeJSONInstance ''ExportMode)
328 a3f02317 Iustin Pop
329 a3f02317 Iustin Pop
-- | IAllocator run types (OpTestIAllocator).
330 a3f02317 Iustin Pop
$(THH.declareSADT "IAllocatorTestDir"
331 a3f02317 Iustin Pop
  [ ("IAllocatorDirIn",  'C.iallocatorDirIn)
332 a3f02317 Iustin Pop
  , ("IAllocatorDirOut", 'C.iallocatorDirOut)
333 a3f02317 Iustin Pop
  ])
334 a3f02317 Iustin Pop
$(THH.makeJSONInstance ''IAllocatorTestDir)
335 a3f02317 Iustin Pop
336 a3f02317 Iustin Pop
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
337 a3f02317 Iustin Pop
$(THH.declareSADT "IAllocatorMode"
338 a3f02317 Iustin Pop
  [ ("IAllocatorAlloc",       'C.iallocatorModeAlloc)
339 a3f02317 Iustin Pop
  , ("IAllocatorMultiAlloc",  'C.iallocatorModeMultiAlloc)
340 a3f02317 Iustin Pop
  , ("IAllocatorReloc",       'C.iallocatorModeReloc)
341 a3f02317 Iustin Pop
  , ("IAllocatorNodeEvac",    'C.iallocatorModeNodeEvac)
342 a3f02317 Iustin Pop
  , ("IAllocatorChangeGroup", 'C.iallocatorModeChgGroup)
343 a3f02317 Iustin Pop
  ])
344 a3f02317 Iustin Pop
$(THH.makeJSONInstance ''IAllocatorMode)
345 497beee2 Iustin Pop
346 8d239fa4 Iustin Pop
-- | Network type.
347 8d239fa4 Iustin Pop
$(THH.declareSADT "NetworkType"
348 8d239fa4 Iustin Pop
  [ ("PrivateNetwork", 'C.networkTypePrivate)
349 8d239fa4 Iustin Pop
  , ("PublicNetwork",  'C.networkTypePublic)
350 8d239fa4 Iustin Pop
  ])
351 8d239fa4 Iustin Pop
$(THH.makeJSONInstance ''NetworkType)
352 8d239fa4 Iustin Pop
353 497beee2 Iustin Pop
-- | Netork mode.
354 497beee2 Iustin Pop
$(THH.declareSADT "NICMode"
355 497beee2 Iustin Pop
  [ ("NMBridged", 'C.nicModeBridged)
356 497beee2 Iustin Pop
  , ("NMRouted",  'C.nicModeRouted)
357 497beee2 Iustin Pop
  ])
358 497beee2 Iustin Pop
$(THH.makeJSONInstance ''NICMode)
359 6903fea0 Iustin Pop
360 6903fea0 Iustin Pop
-- | Finalized job status.
361 6903fea0 Iustin Pop
$(THH.declareSADT "FinalizedJobStatus"
362 6903fea0 Iustin Pop
  [ ("JobStatusCanceled",   'C.jobStatusCanceled)
363 6903fea0 Iustin Pop
  , ("JobStatusSuccessful", 'C.jobStatusSuccess)
364 6903fea0 Iustin Pop
  , ("JobStatusFailed",     'C.jobStatusError)
365 6903fea0 Iustin Pop
  ])
366 6903fea0 Iustin Pop
$(THH.makeJSONInstance ''FinalizedJobStatus)
367 c48711d5 Iustin Pop
368 c48711d5 Iustin Pop
-- | The Ganeti job type.
369 c48711d5 Iustin Pop
newtype JobId = JobId { fromJobId :: Int }
370 c48711d5 Iustin Pop
  deriving (Show, Eq)
371 c48711d5 Iustin Pop
372 c48711d5 Iustin Pop
-- | Builds a job ID.
373 c48711d5 Iustin Pop
makeJobId :: (Monad m) => Int -> m JobId
374 c48711d5 Iustin Pop
makeJobId i | i >= 0 = return $ JobId i
375 c48711d5 Iustin Pop
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
376 c48711d5 Iustin Pop
377 c48711d5 Iustin Pop
-- | Parses a job ID.
378 c48711d5 Iustin Pop
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
379 c48711d5 Iustin Pop
parseJobId (JSON.JSString x) =
380 c48711d5 Iustin Pop
  tryRead "parsing job id" (JSON.fromJSString x) >>= makeJobId
381 c48711d5 Iustin Pop
parseJobId (JSON.JSRational _ x) =
382 c48711d5 Iustin Pop
  if denominator x /= 1
383 c48711d5 Iustin Pop
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
384 c48711d5 Iustin Pop
    -- FIXME: potential integer overflow here on 32-bit platforms
385 c48711d5 Iustin Pop
    else makeJobId . fromIntegral . numerator $ x
386 c48711d5 Iustin Pop
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
387 c48711d5 Iustin Pop
388 c48711d5 Iustin Pop
instance JSON.JSON JobId where
389 c48711d5 Iustin Pop
  showJSON = JSON.showJSON . fromJobId
390 c48711d5 Iustin Pop
  readJSON = parseJobId