Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ c92b4671

History | View | Annotate | Download (28.2 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 37fe56e0 Iustin Pop
Copyright (C) 2012, 2013 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 44c15fa3 Jose A. Lopes
  , TagKind(..)
44 44c15fa3 Jose A. Lopes
  , tagKindToRaw
45 44c15fa3 Jose A. Lopes
  , tagKindFromRaw
46 edb5a1c8 Iustin Pop
  , NonNegative
47 edb5a1c8 Iustin Pop
  , fromNonNegative
48 edb5a1c8 Iustin Pop
  , mkNonNegative
49 edb5a1c8 Iustin Pop
  , Positive
50 edb5a1c8 Iustin Pop
  , fromPositive
51 edb5a1c8 Iustin Pop
  , mkPositive
52 c67b908a Iustin Pop
  , Negative
53 c67b908a Iustin Pop
  , fromNegative
54 c67b908a Iustin Pop
  , mkNegative
55 edb5a1c8 Iustin Pop
  , NonEmpty
56 edb5a1c8 Iustin Pop
  , fromNonEmpty
57 edb5a1c8 Iustin Pop
  , mkNonEmpty
58 6a28e02c Iustin Pop
  , NonEmptyString
59 44c15fa3 Jose A. Lopes
  , QueryResultCode
60 44c15fa3 Jose A. Lopes
  , IPv4Address
61 44c15fa3 Jose A. Lopes
  , mkIPv4Address
62 44c15fa3 Jose A. Lopes
  , IPv4Network
63 44c15fa3 Jose A. Lopes
  , mkIPv4Network
64 44c15fa3 Jose A. Lopes
  , IPv6Address
65 44c15fa3 Jose A. Lopes
  , mkIPv6Address
66 44c15fa3 Jose A. Lopes
  , IPv6Network
67 44c15fa3 Jose A. Lopes
  , mkIPv6Network
68 d696bbef Iustin Pop
  , MigrationMode(..)
69 9ee75f25 Jose A. Lopes
  , migrationModeToRaw
70 d696bbef Iustin Pop
  , VerifyOptionalChecks(..)
71 44c15fa3 Jose A. Lopes
  , verifyOptionalChecksToRaw
72 d696bbef Iustin Pop
  , DdmSimple(..)
73 c2d3219b Iustin Pop
  , DdmFull(..)
74 9ee75f25 Jose A. Lopes
  , ddmFullToRaw
75 d696bbef Iustin Pop
  , CVErrorCode(..)
76 d696bbef Iustin Pop
  , cVErrorCodeToRaw
77 22381768 Iustin Pop
  , Hypervisor(..)
78 68af861c Helga Velroyen
  , hypervisorToRaw
79 6a28e02c Iustin Pop
  , OobCommand(..)
80 9ee75f25 Jose A. Lopes
  , oobCommandToRaw
81 774867f2 Jose A. Lopes
  , OobStatus(..)
82 774867f2 Jose A. Lopes
  , oobStatusToRaw
83 48755fac Iustin Pop
  , StorageType(..)
84 212b66c3 Helga Velroyen
  , storageTypeToRaw
85 d067f40b Jose A. Lopes
  , EvacMode(..)
86 d067f40b Jose A. Lopes
  , evacModeToRaw
87 c65621d7 Iustin Pop
  , FileDriver(..)
88 9ee75f25 Jose A. Lopes
  , fileDriverToRaw
89 6d558717 Iustin Pop
  , InstCreateMode(..)
90 9ee75f25 Jose A. Lopes
  , instCreateModeToRaw
91 c2d3219b Iustin Pop
  , RebootType(..)
92 9ee75f25 Jose A. Lopes
  , rebootTypeToRaw
93 398e9066 Iustin Pop
  , ExportMode(..)
94 9ee75f25 Jose A. Lopes
  , exportModeToRaw
95 a3f02317 Iustin Pop
  , IAllocatorTestDir(..)
96 9ee75f25 Jose A. Lopes
  , iAllocatorTestDirToRaw
97 a3f02317 Iustin Pop
  , IAllocatorMode(..)
98 a3f02317 Iustin Pop
  , iAllocatorModeToRaw
99 497beee2 Iustin Pop
  , NICMode(..)
100 497beee2 Iustin Pop
  , nICModeToRaw
101 3bdbe4b3 Dato Simó
  , JobStatus(..)
102 3bdbe4b3 Dato Simó
  , jobStatusToRaw
103 3bdbe4b3 Dato Simó
  , jobStatusFromRaw
104 6903fea0 Iustin Pop
  , FinalizedJobStatus(..)
105 6903fea0 Iustin Pop
  , finalizedJobStatusToRaw
106 c48711d5 Iustin Pop
  , JobId
107 c48711d5 Iustin Pop
  , fromJobId
108 c48711d5 Iustin Pop
  , makeJobId
109 fd958a3d Iustin Pop
  , makeJobIdS
110 b46ba79c Iustin Pop
  , RelativeJobId
111 b46ba79c Iustin Pop
  , JobIdDep(..)
112 b46ba79c Iustin Pop
  , JobDependency(..)
113 966ea086 Klaus Aehlig
  , absoluteJobDependency
114 b46ba79c Iustin Pop
  , OpSubmitPriority(..)
115 fd958a3d Iustin Pop
  , opSubmitPriorityToRaw
116 37fe56e0 Iustin Pop
  , parseSubmitPriority
117 37fe56e0 Iustin Pop
  , fmtSubmitPriority
118 3bdbe4b3 Dato Simó
  , OpStatus(..)
119 3bdbe4b3 Dato Simó
  , opStatusToRaw
120 3bdbe4b3 Dato Simó
  , opStatusFromRaw
121 5cd95d46 Iustin Pop
  , ELogType(..)
122 9ee75f25 Jose A. Lopes
  , eLogTypeToRaw
123 3ff890a1 Michele Tartara
  , ReasonElem
124 3ff890a1 Michele Tartara
  , ReasonTrail
125 212b66c3 Helga Velroyen
  , StorageUnit(..)
126 212b66c3 Helga Velroyen
  , StorageUnitRaw(..)
127 212b66c3 Helga Velroyen
  , StorageKey
128 212b66c3 Helga Velroyen
  , addParamsToStorageUnit
129 212b66c3 Helga Velroyen
  , diskTemplateToStorageType
130 8e6ef316 Jose A. Lopes
  , VType(..)
131 8e6ef316 Jose A. Lopes
  , vTypeFromRaw
132 8e6ef316 Jose A. Lopes
  , vTypeToRaw
133 8e6ef316 Jose A. Lopes
  , NodeRole(..)
134 8e6ef316 Jose A. Lopes
  , nodeRoleToRaw
135 8e6ef316 Jose A. Lopes
  , roleDescription
136 8e6ef316 Jose A. Lopes
  , DiskMode(..)
137 8e6ef316 Jose A. Lopes
  , diskModeToRaw
138 8e6ef316 Jose A. Lopes
  , BlockDriver(..)
139 8e6ef316 Jose A. Lopes
  , blockDriverToRaw
140 8e6ef316 Jose A. Lopes
  , AdminState(..)
141 8e6ef316 Jose A. Lopes
  , adminStateFromRaw
142 8e6ef316 Jose A. Lopes
  , adminStateToRaw
143 ccf17aa3 Jose A. Lopes
  , StorageField(..)
144 ccf17aa3 Jose A. Lopes
  , storageFieldToRaw
145 9b9e088c Raffa Santi
  , DiskAccessMode(..)
146 9b9e088c Raffa Santi
  , diskAccessModeToRaw
147 59bcd180 Jose A. Lopes
  , LocalDiskStatus(..)
148 59bcd180 Jose A. Lopes
  , localDiskStatusFromRaw
149 59bcd180 Jose A. Lopes
  , localDiskStatusToRaw
150 59bcd180 Jose A. Lopes
  , localDiskStatusName
151 a5450d2a Jose A. Lopes
  , ReplaceDisksMode(..)
152 a5450d2a Jose A. Lopes
  , replaceDisksModeToRaw
153 c03224f6 Jose A. Lopes
  , RpcTimeout(..)
154 c03224f6 Jose A. Lopes
  , rpcTimeoutFromRaw -- FIXME: no used anywhere
155 c03224f6 Jose A. Lopes
  , rpcTimeoutToRaw
156 f198cf91 Thomas Thrainer
  , ImportExportCompression(..)
157 f198cf91 Thomas Thrainer
  , importExportCompressionToRaw
158 9569d877 Dimitris Aragiorgis
  , HotplugTarget(..)
159 9569d877 Dimitris Aragiorgis
  , hotplugTargetToRaw
160 9569d877 Dimitris Aragiorgis
  , HotplugAction(..)
161 9569d877 Dimitris Aragiorgis
  , hotplugActionToRaw
162 5e9deac0 Iustin Pop
  ) where
163 5e9deac0 Iustin Pop
164 b46ba79c Iustin Pop
import Control.Monad (liftM)
165 edb5a1c8 Iustin Pop
import qualified Text.JSON as JSON
166 b46ba79c Iustin Pop
import Text.JSON (JSON, readJSON, showJSON)
167 c48711d5 Iustin Pop
import Data.Ratio (numerator, denominator)
168 edb5a1c8 Iustin Pop
169 72e18df1 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
170 edc1acde Iustin Pop
import Ganeti.JSON
171 72e18df1 Jose A. Lopes
import qualified Ganeti.THH as THH
172 c48711d5 Iustin Pop
import Ganeti.Utils
173 5e9deac0 Iustin Pop
174 edb5a1c8 Iustin Pop
-- * Generic types
175 edb5a1c8 Iustin Pop
176 edb5a1c8 Iustin Pop
-- | Type that holds a non-negative value.
177 edb5a1c8 Iustin Pop
newtype NonNegative a = NonNegative { fromNonNegative :: a }
178 139c0683 Iustin Pop
  deriving (Show, Eq)
179 edb5a1c8 Iustin Pop
180 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonNegative'.
181 edb5a1c8 Iustin Pop
mkNonNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (NonNegative a)
182 edb5a1c8 Iustin Pop
mkNonNegative i | i >= 0 = return (NonNegative i)
183 edb5a1c8 Iustin Pop
                | otherwise = fail $ "Invalid value for non-negative type '" ++
184 edb5a1c8 Iustin Pop
                              show i ++ "'"
185 edb5a1c8 Iustin Pop
186 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (NonNegative a) where
187 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonNegative
188 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonNegative
189 edb5a1c8 Iustin Pop
190 edb5a1c8 Iustin Pop
-- | Type that holds a positive value.
191 edb5a1c8 Iustin Pop
newtype Positive a = Positive { fromPositive :: a }
192 139c0683 Iustin Pop
  deriving (Show, Eq)
193 edb5a1c8 Iustin Pop
194 edb5a1c8 Iustin Pop
-- | Smart constructor for 'Positive'.
195 edb5a1c8 Iustin Pop
mkPositive :: (Monad m, Num a, Ord a, Show a) => a -> m (Positive a)
196 edb5a1c8 Iustin Pop
mkPositive i | i > 0 = return (Positive i)
197 edb5a1c8 Iustin Pop
             | otherwise = fail $ "Invalid value for positive type '" ++
198 edb5a1c8 Iustin Pop
                           show i ++ "'"
199 edb5a1c8 Iustin Pop
200 edb5a1c8 Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Positive a) where
201 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromPositive
202 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkPositive
203 edb5a1c8 Iustin Pop
204 c67b908a Iustin Pop
-- | Type that holds a negative value.
205 c67b908a Iustin Pop
newtype Negative a = Negative { fromNegative :: a }
206 c67b908a Iustin Pop
  deriving (Show, Eq)
207 c67b908a Iustin Pop
208 c67b908a Iustin Pop
-- | Smart constructor for 'Negative'.
209 c67b908a Iustin Pop
mkNegative :: (Monad m, Num a, Ord a, Show a) => a -> m (Negative a)
210 c67b908a Iustin Pop
mkNegative i | i < 0 = return (Negative i)
211 c67b908a Iustin Pop
             | otherwise = fail $ "Invalid value for negative type '" ++
212 c67b908a Iustin Pop
                           show i ++ "'"
213 c67b908a Iustin Pop
214 c67b908a Iustin Pop
instance (JSON.JSON a, Num a, Ord a, Show a) => JSON.JSON (Negative a) where
215 c67b908a Iustin Pop
  showJSON = JSON.showJSON . fromNegative
216 c67b908a Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNegative
217 c67b908a Iustin Pop
218 edb5a1c8 Iustin Pop
-- | Type that holds a non-null list.
219 edb5a1c8 Iustin Pop
newtype NonEmpty a = NonEmpty { fromNonEmpty :: [a] }
220 139c0683 Iustin Pop
  deriving (Show, Eq)
221 edb5a1c8 Iustin Pop
222 edb5a1c8 Iustin Pop
-- | Smart constructor for 'NonEmpty'.
223 edb5a1c8 Iustin Pop
mkNonEmpty :: (Monad m) => [a] -> m (NonEmpty a)
224 edb5a1c8 Iustin Pop
mkNonEmpty [] = fail "Received empty value for non-empty list"
225 edb5a1c8 Iustin Pop
mkNonEmpty xs = return (NonEmpty xs)
226 edb5a1c8 Iustin Pop
227 44c15fa3 Jose A. Lopes
instance (Eq a, Ord a) => Ord (NonEmpty a) where
228 44c15fa3 Jose A. Lopes
  NonEmpty { fromNonEmpty = x1 } `compare` NonEmpty { fromNonEmpty = x2 } =
229 44c15fa3 Jose A. Lopes
    x1 `compare` x2
230 44c15fa3 Jose A. Lopes
231 edb5a1c8 Iustin Pop
instance (JSON.JSON a) => JSON.JSON (NonEmpty a) where
232 edb5a1c8 Iustin Pop
  showJSON = JSON.showJSON . fromNonEmpty
233 edb5a1c8 Iustin Pop
  readJSON v = JSON.readJSON v >>= mkNonEmpty
234 edb5a1c8 Iustin Pop
235 6a28e02c Iustin Pop
-- | A simple type alias for non-empty strings.
236 6a28e02c Iustin Pop
type NonEmptyString = NonEmpty Char
237 6a28e02c Iustin Pop
238 44c15fa3 Jose A. Lopes
type QueryResultCode = Int
239 44c15fa3 Jose A. Lopes
240 44c15fa3 Jose A. Lopes
newtype IPv4Address = IPv4Address { fromIPv4Address :: String }
241 44c15fa3 Jose A. Lopes
  deriving (Show, Eq)
242 44c15fa3 Jose A. Lopes
243 44c15fa3 Jose A. Lopes
-- FIXME: this should check that 'address' is a valid ip
244 44c15fa3 Jose A. Lopes
mkIPv4Address :: Monad m => String -> m IPv4Address
245 44c15fa3 Jose A. Lopes
mkIPv4Address address =
246 44c15fa3 Jose A. Lopes
  return IPv4Address { fromIPv4Address = address }
247 44c15fa3 Jose A. Lopes
248 44c15fa3 Jose A. Lopes
instance JSON.JSON IPv4Address where
249 44c15fa3 Jose A. Lopes
  showJSON = JSON.showJSON . fromIPv4Address
250 44c15fa3 Jose A. Lopes
  readJSON v = JSON.readJSON v >>= mkIPv4Address
251 44c15fa3 Jose A. Lopes
252 44c15fa3 Jose A. Lopes
newtype IPv4Network = IPv4Network { fromIPv4Network :: String }
253 44c15fa3 Jose A. Lopes
  deriving (Show, Eq)
254 44c15fa3 Jose A. Lopes
255 44c15fa3 Jose A. Lopes
-- FIXME: this should check that 'address' is a valid ip
256 44c15fa3 Jose A. Lopes
mkIPv4Network :: Monad m => String -> m IPv4Network
257 44c15fa3 Jose A. Lopes
mkIPv4Network address =
258 44c15fa3 Jose A. Lopes
  return IPv4Network { fromIPv4Network = address }
259 44c15fa3 Jose A. Lopes
260 44c15fa3 Jose A. Lopes
instance JSON.JSON IPv4Network where
261 44c15fa3 Jose A. Lopes
  showJSON = JSON.showJSON . fromIPv4Network
262 44c15fa3 Jose A. Lopes
  readJSON v = JSON.readJSON v >>= mkIPv4Network
263 44c15fa3 Jose A. Lopes
264 44c15fa3 Jose A. Lopes
newtype IPv6Address = IPv6Address { fromIPv6Address :: String }
265 44c15fa3 Jose A. Lopes
  deriving (Show, Eq)
266 44c15fa3 Jose A. Lopes
267 44c15fa3 Jose A. Lopes
-- FIXME: this should check that 'address' is a valid ip
268 44c15fa3 Jose A. Lopes
mkIPv6Address :: Monad m => String -> m IPv6Address
269 44c15fa3 Jose A. Lopes
mkIPv6Address address =
270 44c15fa3 Jose A. Lopes
  return IPv6Address { fromIPv6Address = address }
271 44c15fa3 Jose A. Lopes
272 44c15fa3 Jose A. Lopes
instance JSON.JSON IPv6Address where
273 44c15fa3 Jose A. Lopes
  showJSON = JSON.showJSON . fromIPv6Address
274 44c15fa3 Jose A. Lopes
  readJSON v = JSON.readJSON v >>= mkIPv6Address
275 44c15fa3 Jose A. Lopes
276 44c15fa3 Jose A. Lopes
newtype IPv6Network = IPv6Network { fromIPv6Network :: String }
277 44c15fa3 Jose A. Lopes
  deriving (Show, Eq)
278 44c15fa3 Jose A. Lopes
279 44c15fa3 Jose A. Lopes
-- FIXME: this should check that 'address' is a valid ip
280 44c15fa3 Jose A. Lopes
mkIPv6Network :: Monad m => String -> m IPv6Network
281 44c15fa3 Jose A. Lopes
mkIPv6Network address =
282 44c15fa3 Jose A. Lopes
  return IPv6Network { fromIPv6Network = address }
283 44c15fa3 Jose A. Lopes
284 44c15fa3 Jose A. Lopes
instance JSON.JSON IPv6Network where
285 44c15fa3 Jose A. Lopes
  showJSON = JSON.showJSON . fromIPv6Network
286 44c15fa3 Jose A. Lopes
  readJSON v = JSON.readJSON v >>= mkIPv6Network
287 44c15fa3 Jose A. Lopes
288 edb5a1c8 Iustin Pop
-- * Ganeti types
289 edb5a1c8 Iustin Pop
290 5e9deac0 Iustin Pop
-- | Instance disk template type.
291 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "DiskTemplate"
292 72e18df1 Jose A. Lopes
       [ ("DTDiskless",   "diskless")
293 72e18df1 Jose A. Lopes
       , ("DTFile",       "file")
294 72e18df1 Jose A. Lopes
       , ("DTSharedFile", "sharedfile")
295 72e18df1 Jose A. Lopes
       , ("DTPlain",      "plain")
296 72e18df1 Jose A. Lopes
       , ("DTBlock",      "blockdev")
297 72e18df1 Jose A. Lopes
       , ("DTDrbd8",      "drbd")
298 72e18df1 Jose A. Lopes
       , ("DTRbd",        "rbd")
299 72e18df1 Jose A. Lopes
       , ("DTExt",        "ext")
300 8106dd64 Santi Raffa
       , ("DTGluster",    "gluster")
301 5e9deac0 Iustin Pop
       ])
302 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''DiskTemplate)
303 5e9deac0 Iustin Pop
304 9b9e088c Raffa Santi
instance THH.PyValue DiskTemplate where
305 9b9e088c Raffa Santi
  showValue = show . diskTemplateToRaw
306 9b9e088c Raffa Santi
307 edc1acde Iustin Pop
instance HasStringRepr DiskTemplate where
308 edc1acde Iustin Pop
  fromStringRepr = diskTemplateFromRaw
309 edc1acde Iustin Pop
  toStringRepr = diskTemplateToRaw
310 edc1acde Iustin Pop
311 44c15fa3 Jose A. Lopes
-- | Data type representing what items the tag operations apply to.
312 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "TagKind"
313 72e18df1 Jose A. Lopes
  [ ("TagKindInstance", "instance")
314 72e18df1 Jose A. Lopes
  , ("TagKindNode",     "node")
315 72e18df1 Jose A. Lopes
  , ("TagKindGroup",    "nodegroup")
316 72e18df1 Jose A. Lopes
  , ("TagKindCluster",  "cluster")
317 a8633d70 Jose A. Lopes
  , ("TagKindNetwork",  "network")
318 44c15fa3 Jose A. Lopes
  ])
319 44c15fa3 Jose A. Lopes
$(THH.makeJSONInstance ''TagKind)
320 44c15fa3 Jose A. Lopes
321 5e9deac0 Iustin Pop
-- | The Group allocation policy type.
322 5e9deac0 Iustin Pop
--
323 5e9deac0 Iustin Pop
-- Note that the order of constructors is important as the automatic
324 5e9deac0 Iustin Pop
-- Ord instance will order them in the order they are defined, so when
325 5e9deac0 Iustin Pop
-- changing this data type be careful about the interaction with the
326 5e9deac0 Iustin Pop
-- desired sorting order.
327 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "AllocPolicy"
328 72e18df1 Jose A. Lopes
       [ ("AllocPreferred",   "preferred")
329 72e18df1 Jose A. Lopes
       , ("AllocLastResort",  "last_resort")
330 72e18df1 Jose A. Lopes
       , ("AllocUnallocable", "unallocable")
331 5e9deac0 Iustin Pop
       ])
332 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''AllocPolicy)
333 5e9deac0 Iustin Pop
334 9158a1dd Jose A. Lopes
-- | The Instance real state type.
335 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "InstanceStatus"
336 72e18df1 Jose A. Lopes
       [ ("StatusDown",    "ADMIN_down")
337 72e18df1 Jose A. Lopes
       , ("StatusOffline", "ADMIN_offline")
338 72e18df1 Jose A. Lopes
       , ("ErrorDown",     "ERROR_down")
339 72e18df1 Jose A. Lopes
       , ("ErrorUp",       "ERROR_up")
340 72e18df1 Jose A. Lopes
       , ("NodeDown",      "ERROR_nodedown")
341 72e18df1 Jose A. Lopes
       , ("NodeOffline",   "ERROR_nodeoffline")
342 72e18df1 Jose A. Lopes
       , ("Running",       "running")
343 9158a1dd Jose A. Lopes
       , ("UserDown",      "USER_down")
344 72e18df1 Jose A. Lopes
       , ("WrongNode",     "ERROR_wrongnode")
345 5e9deac0 Iustin Pop
       ])
346 5e9deac0 Iustin Pop
$(THH.makeJSONInstance ''InstanceStatus)
347 d696bbef Iustin Pop
348 d696bbef Iustin Pop
-- | Migration mode.
349 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "MigrationMode"
350 72e18df1 Jose A. Lopes
     [ ("MigrationLive",    "live")
351 72e18df1 Jose A. Lopes
     , ("MigrationNonLive", "non-live")
352 d696bbef Iustin Pop
     ])
353 d696bbef Iustin Pop
$(THH.makeJSONInstance ''MigrationMode)
354 d696bbef Iustin Pop
355 d696bbef Iustin Pop
-- | Verify optional checks.
356 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "VerifyOptionalChecks"
357 72e18df1 Jose A. Lopes
     [ ("VerifyNPlusOneMem", "nplusone_mem")
358 d696bbef Iustin Pop
     ])
359 d696bbef Iustin Pop
$(THH.makeJSONInstance ''VerifyOptionalChecks)
360 d696bbef Iustin Pop
361 d696bbef Iustin Pop
-- | Cluster verify error codes.
362 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "CVErrorCode"
363 72e18df1 Jose A. Lopes
  [ ("CvECLUSTERCFG",                  "ECLUSTERCFG")
364 72e18df1 Jose A. Lopes
  , ("CvECLUSTERCERT",                 "ECLUSTERCERT")
365 a6c43c02 Helga Velroyen
  , ("CvECLUSTERCLIENTCERT",           "ECLUSTERCLIENTCERT")
366 72e18df1 Jose A. Lopes
  , ("CvECLUSTERFILECHECK",            "ECLUSTERFILECHECK")
367 72e18df1 Jose A. Lopes
  , ("CvECLUSTERDANGLINGNODES",        "ECLUSTERDANGLINGNODES")
368 72e18df1 Jose A. Lopes
  , ("CvECLUSTERDANGLINGINST",         "ECLUSTERDANGLINGINST")
369 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEBADNODE",             "EINSTANCEBADNODE")
370 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEDOWN",                "EINSTANCEDOWN")
371 72e18df1 Jose A. Lopes
  , ("CvEINSTANCELAYOUT",              "EINSTANCELAYOUT")
372 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEMISSINGDISK",         "EINSTANCEMISSINGDISK")
373 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEFAULTYDISK",          "EINSTANCEFAULTYDISK")
374 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEWRONGNODE",           "EINSTANCEWRONGNODE")
375 72e18df1 Jose A. Lopes
  , ("CvEINSTANCESPLITGROUPS",         "EINSTANCESPLITGROUPS")
376 72e18df1 Jose A. Lopes
  , ("CvEINSTANCEPOLICY",              "EINSTANCEPOLICY")
377 d91750e9 Jose A. Lopes
  , ("CvEINSTANCEUNSUITABLENODE",      "EINSTANCEUNSUITABLENODE")
378 d91750e9 Jose A. Lopes
  , ("CvEINSTANCEMISSINGCFGPARAMETER", "EINSTANCEMISSINGCFGPARAMETER")
379 72e18df1 Jose A. Lopes
  , ("CvENODEDRBD",                    "ENODEDRBD")
380 d91750e9 Jose A. Lopes
  , ("CvENODEDRBDVERSION",             "ENODEDRBDVERSION")
381 72e18df1 Jose A. Lopes
  , ("CvENODEDRBDHELPER",              "ENODEDRBDHELPER")
382 72e18df1 Jose A. Lopes
  , ("CvENODEFILECHECK",               "ENODEFILECHECK")
383 72e18df1 Jose A. Lopes
  , ("CvENODEHOOKS",                   "ENODEHOOKS")
384 72e18df1 Jose A. Lopes
  , ("CvENODEHV",                      "ENODEHV")
385 72e18df1 Jose A. Lopes
  , ("CvENODELVM",                     "ENODELVM")
386 72e18df1 Jose A. Lopes
  , ("CvENODEN1",                      "ENODEN1")
387 72e18df1 Jose A. Lopes
  , ("CvENODENET",                     "ENODENET")
388 72e18df1 Jose A. Lopes
  , ("CvENODEOS",                      "ENODEOS")
389 72e18df1 Jose A. Lopes
  , ("CvENODEORPHANINSTANCE",          "ENODEORPHANINSTANCE")
390 72e18df1 Jose A. Lopes
  , ("CvENODEORPHANLV",                "ENODEORPHANLV")
391 72e18df1 Jose A. Lopes
  , ("CvENODERPC",                     "ENODERPC")
392 72e18df1 Jose A. Lopes
  , ("CvENODESSH",                     "ENODESSH")
393 72e18df1 Jose A. Lopes
  , ("CvENODEVERSION",                 "ENODEVERSION")
394 72e18df1 Jose A. Lopes
  , ("CvENODESETUP",                   "ENODESETUP")
395 72e18df1 Jose A. Lopes
  , ("CvENODETIME",                    "ENODETIME")
396 72e18df1 Jose A. Lopes
  , ("CvENODEOOBPATH",                 "ENODEOOBPATH")
397 72e18df1 Jose A. Lopes
  , ("CvENODEUSERSCRIPTS",             "ENODEUSERSCRIPTS")
398 72e18df1 Jose A. Lopes
  , ("CvENODEFILESTORAGEPATHS",        "ENODEFILESTORAGEPATHS")
399 72e18df1 Jose A. Lopes
  , ("CvENODEFILESTORAGEPATHUNUSABLE", "ENODEFILESTORAGEPATHUNUSABLE")
400 4b322a76 Helga Velroyen
  , ("CvENODESHAREDFILESTORAGEPATHUNUSABLE",
401 72e18df1 Jose A. Lopes
     "ENODESHAREDFILESTORAGEPATHUNUSABLE")
402 d91750e9 Jose A. Lopes
  , ("CvEGROUPDIFFERENTPVSIZE",        "EGROUPDIFFERENTPVSIZE")
403 d696bbef Iustin Pop
  ])
404 d696bbef Iustin Pop
$(THH.makeJSONInstance ''CVErrorCode)
405 d696bbef Iustin Pop
406 d696bbef Iustin Pop
-- | Dynamic device modification, just add\/remove version.
407 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "DdmSimple"
408 72e18df1 Jose A. Lopes
     [ ("DdmSimpleAdd",    "add")
409 72e18df1 Jose A. Lopes
     , ("DdmSimpleRemove", "remove")
410 d696bbef Iustin Pop
     ])
411 d696bbef Iustin Pop
$(THH.makeJSONInstance ''DdmSimple)
412 22381768 Iustin Pop
413 c2d3219b Iustin Pop
-- | Dynamic device modification, all operations version.
414 59bcd180 Jose A. Lopes
--
415 59bcd180 Jose A. Lopes
-- TODO: DDM_SWAP, DDM_MOVE?
416 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "DdmFull"
417 72e18df1 Jose A. Lopes
     [ ("DdmFullAdd",    "add")
418 72e18df1 Jose A. Lopes
     , ("DdmFullRemove", "remove")
419 72e18df1 Jose A. Lopes
     , ("DdmFullModify", "modify")
420 c2d3219b Iustin Pop
     ])
421 c2d3219b Iustin Pop
$(THH.makeJSONInstance ''DdmFull)
422 c2d3219b Iustin Pop
423 22381768 Iustin Pop
-- | Hypervisor type definitions.
424 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "Hypervisor"
425 72e18df1 Jose A. Lopes
  [ ("Kvm",    "kvm")
426 72e18df1 Jose A. Lopes
  , ("XenPvm", "xen-pvm")
427 72e18df1 Jose A. Lopes
  , ("Chroot", "chroot")
428 72e18df1 Jose A. Lopes
  , ("XenHvm", "xen-hvm")
429 72e18df1 Jose A. Lopes
  , ("Lxc",    "lxc")
430 72e18df1 Jose A. Lopes
  , ("Fake",   "fake")
431 22381768 Iustin Pop
  ])
432 22381768 Iustin Pop
$(THH.makeJSONInstance ''Hypervisor)
433 48755fac Iustin Pop
434 9b9e088c Raffa Santi
instance THH.PyValue Hypervisor where
435 9b9e088c Raffa Santi
  showValue = show . hypervisorToRaw
436 9b9e088c Raffa Santi
437 c14ba680 Hrvoje Ribicic
instance HasStringRepr Hypervisor where
438 c14ba680 Hrvoje Ribicic
  fromStringRepr = hypervisorFromRaw
439 c14ba680 Hrvoje Ribicic
  toStringRepr = hypervisorToRaw
440 c14ba680 Hrvoje Ribicic
441 6a28e02c Iustin Pop
-- | Oob command type.
442 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "OobCommand"
443 72e18df1 Jose A. Lopes
  [ ("OobHealth",      "health")
444 72e18df1 Jose A. Lopes
  , ("OobPowerCycle",  "power-cycle")
445 72e18df1 Jose A. Lopes
  , ("OobPowerOff",    "power-off")
446 72e18df1 Jose A. Lopes
  , ("OobPowerOn",     "power-on")
447 72e18df1 Jose A. Lopes
  , ("OobPowerStatus", "power-status")
448 6a28e02c Iustin Pop
  ])
449 6a28e02c Iustin Pop
$(THH.makeJSONInstance ''OobCommand)
450 6a28e02c Iustin Pop
451 774867f2 Jose A. Lopes
-- | Oob command status
452 774867f2 Jose A. Lopes
$(THH.declareLADT ''String "OobStatus"
453 774867f2 Jose A. Lopes
  [ ("OobStatusCritical", "CRITICAL")
454 774867f2 Jose A. Lopes
  , ("OobStatusOk",       "OK")
455 774867f2 Jose A. Lopes
  , ("OobStatusUnknown",  "UNKNOWN")
456 774867f2 Jose A. Lopes
  , ("OobStatusWarning",  "WARNING")
457 774867f2 Jose A. Lopes
  ])
458 774867f2 Jose A. Lopes
$(THH.makeJSONInstance ''OobStatus)
459 774867f2 Jose A. Lopes
460 48755fac Iustin Pop
-- | Storage type.
461 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "StorageType"
462 72e18df1 Jose A. Lopes
  [ ("StorageFile", "file")
463 5a904197 Santi Raffa
  , ("StorageSharedFile", "sharedfile")
464 72e18df1 Jose A. Lopes
  , ("StorageLvmPv", "lvm-pv")
465 72e18df1 Jose A. Lopes
  , ("StorageLvmVg", "lvm-vg")
466 72e18df1 Jose A. Lopes
  , ("StorageDiskless", "diskless")
467 72e18df1 Jose A. Lopes
  , ("StorageBlock", "blockdev")
468 72e18df1 Jose A. Lopes
  , ("StorageRados", "rados")
469 72e18df1 Jose A. Lopes
  , ("StorageExt", "ext")
470 48755fac Iustin Pop
  ])
471 48755fac Iustin Pop
$(THH.makeJSONInstance ''StorageType)
472 6a28e02c Iustin Pop
473 212b66c3 Helga Velroyen
-- | Storage keys are identifiers for storage units. Their content varies
474 212b66c3 Helga Velroyen
-- depending on the storage type, for example a storage key for LVM storage
475 212b66c3 Helga Velroyen
-- is the volume group name.
476 212b66c3 Helga Velroyen
type StorageKey = String
477 212b66c3 Helga Velroyen
478 212b66c3 Helga Velroyen
-- | Storage parameters
479 212b66c3 Helga Velroyen
type SPExclusiveStorage = Bool
480 212b66c3 Helga Velroyen
481 212b66c3 Helga Velroyen
-- | Storage units without storage-type-specific parameters
482 212b66c3 Helga Velroyen
data StorageUnitRaw = SURaw StorageType StorageKey
483 212b66c3 Helga Velroyen
484 212b66c3 Helga Velroyen
-- | Full storage unit with storage-type-specific parameters
485 212b66c3 Helga Velroyen
data StorageUnit = SUFile StorageKey
486 5a904197 Santi Raffa
                 | SUSharedFile StorageKey
487 212b66c3 Helga Velroyen
                 | SULvmPv StorageKey SPExclusiveStorage
488 212b66c3 Helga Velroyen
                 | SULvmVg StorageKey SPExclusiveStorage
489 212b66c3 Helga Velroyen
                 | SUDiskless StorageKey
490 212b66c3 Helga Velroyen
                 | SUBlock StorageKey
491 212b66c3 Helga Velroyen
                 | SURados StorageKey
492 212b66c3 Helga Velroyen
                 | SUExt StorageKey
493 212b66c3 Helga Velroyen
                 deriving (Eq)
494 212b66c3 Helga Velroyen
495 212b66c3 Helga Velroyen
instance Show StorageUnit where
496 212b66c3 Helga Velroyen
  show (SUFile key) = showSUSimple StorageFile key
497 5a904197 Santi Raffa
  show (SUSharedFile key) = showSUSimple StorageSharedFile key
498 212b66c3 Helga Velroyen
  show (SULvmPv key es) = showSULvm StorageLvmPv key es
499 212b66c3 Helga Velroyen
  show (SULvmVg key es) = showSULvm StorageLvmVg key es
500 212b66c3 Helga Velroyen
  show (SUDiskless key) = showSUSimple StorageDiskless key
501 212b66c3 Helga Velroyen
  show (SUBlock key) = showSUSimple StorageBlock key
502 212b66c3 Helga Velroyen
  show (SURados key) = showSUSimple StorageRados key
503 212b66c3 Helga Velroyen
  show (SUExt key) = showSUSimple StorageExt key
504 212b66c3 Helga Velroyen
505 212b66c3 Helga Velroyen
instance JSON StorageUnit where
506 212b66c3 Helga Velroyen
  showJSON (SUFile key) = showJSON (StorageFile, key, []::[String])
507 5a904197 Santi Raffa
  showJSON (SUSharedFile key) = showJSON (StorageSharedFile, key, []::[String])
508 212b66c3 Helga Velroyen
  showJSON (SULvmPv key es) = showJSON (StorageLvmPv, key, [es])
509 212b66c3 Helga Velroyen
  showJSON (SULvmVg key es) = showJSON (StorageLvmVg, key, [es])
510 212b66c3 Helga Velroyen
  showJSON (SUDiskless key) = showJSON (StorageDiskless, key, []::[String])
511 212b66c3 Helga Velroyen
  showJSON (SUBlock key) = showJSON (StorageBlock, key, []::[String])
512 212b66c3 Helga Velroyen
  showJSON (SURados key) = showJSON (StorageRados, key, []::[String])
513 212b66c3 Helga Velroyen
  showJSON (SUExt key) = showJSON (StorageExt, key, []::[String])
514 212b66c3 Helga Velroyen
-- FIXME: add readJSON implementation
515 212b66c3 Helga Velroyen
  readJSON = fail "Not implemented"
516 212b66c3 Helga Velroyen
517 212b66c3 Helga Velroyen
-- | Composes a string representation of storage types without
518 212b66c3 Helga Velroyen
-- storage parameters
519 212b66c3 Helga Velroyen
showSUSimple :: StorageType -> StorageKey -> String
520 212b66c3 Helga Velroyen
showSUSimple st sk = show (storageTypeToRaw st, sk, []::[String])
521 212b66c3 Helga Velroyen
522 212b66c3 Helga Velroyen
-- | Composes a string representation of the LVM storage types
523 212b66c3 Helga Velroyen
showSULvm :: StorageType -> StorageKey -> SPExclusiveStorage -> String
524 212b66c3 Helga Velroyen
showSULvm st sk es = show (storageTypeToRaw st, sk, [es])
525 212b66c3 Helga Velroyen
526 72e18df1 Jose A. Lopes
-- | Mapping from disk templates to storage types
527 212b66c3 Helga Velroyen
-- FIXME: This is semantically the same as the constant
528 212b66c3 Helga Velroyen
-- C.diskTemplatesStorageType, remove this when python constants
529 212b66c3 Helga Velroyen
-- are generated from haskell constants
530 212b66c3 Helga Velroyen
diskTemplateToStorageType :: DiskTemplate -> StorageType
531 212b66c3 Helga Velroyen
diskTemplateToStorageType DTExt = StorageExt
532 212b66c3 Helga Velroyen
diskTemplateToStorageType DTFile = StorageFile
533 5a904197 Santi Raffa
diskTemplateToStorageType DTSharedFile = StorageSharedFile
534 212b66c3 Helga Velroyen
diskTemplateToStorageType DTDrbd8 = StorageLvmVg
535 212b66c3 Helga Velroyen
diskTemplateToStorageType DTPlain = StorageLvmVg
536 212b66c3 Helga Velroyen
diskTemplateToStorageType DTRbd = StorageRados
537 212b66c3 Helga Velroyen
diskTemplateToStorageType DTDiskless = StorageDiskless
538 212b66c3 Helga Velroyen
diskTemplateToStorageType DTBlock = StorageBlock
539 5a904197 Santi Raffa
diskTemplateToStorageType DTGluster = StorageSharedFile
540 212b66c3 Helga Velroyen
541 212b66c3 Helga Velroyen
-- | Equips a raw storage unit with its parameters
542 212b66c3 Helga Velroyen
addParamsToStorageUnit :: SPExclusiveStorage -> StorageUnitRaw -> StorageUnit
543 212b66c3 Helga Velroyen
addParamsToStorageUnit _ (SURaw StorageBlock key) = SUBlock key
544 212b66c3 Helga Velroyen
addParamsToStorageUnit _ (SURaw StorageDiskless key) = SUDiskless key
545 212b66c3 Helga Velroyen
addParamsToStorageUnit _ (SURaw StorageExt key) = SUExt key
546 212b66c3 Helga Velroyen
addParamsToStorageUnit _ (SURaw StorageFile key) = SUFile key
547 5a904197 Santi Raffa
addParamsToStorageUnit _ (SURaw StorageSharedFile key) = SUSharedFile key
548 212b66c3 Helga Velroyen
addParamsToStorageUnit es (SURaw StorageLvmPv key) = SULvmPv key es
549 212b66c3 Helga Velroyen
addParamsToStorageUnit es (SURaw StorageLvmVg key) = SULvmVg key es
550 212b66c3 Helga Velroyen
addParamsToStorageUnit _ (SURaw StorageRados key) = SURados key
551 212b66c3 Helga Velroyen
552 6a28e02c Iustin Pop
-- | Node evac modes.
553 d067f40b Jose A. Lopes
--
554 d067f40b Jose A. Lopes
-- This is part of the 'IAllocator' interface and it is used, for
555 d067f40b Jose A. Lopes
-- example, in 'Ganeti.HTools.Loader.RqType'.  However, it must reside
556 d067f40b Jose A. Lopes
-- in this module, and not in 'Ganeti.HTools.Types', because it is
557 e1235448 Jose A. Lopes
-- also used by 'Ganeti.Constants'.
558 d067f40b Jose A. Lopes
$(THH.declareLADT ''String "EvacMode"
559 d067f40b Jose A. Lopes
  [ ("ChangePrimary",   "primary-only")
560 d067f40b Jose A. Lopes
  , ("ChangeSecondary", "secondary-only")
561 d067f40b Jose A. Lopes
  , ("ChangeAll",       "all")
562 6a28e02c Iustin Pop
  ])
563 d067f40b Jose A. Lopes
$(THH.makeJSONInstance ''EvacMode)
564 c65621d7 Iustin Pop
565 c65621d7 Iustin Pop
-- | The file driver type.
566 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "FileDriver"
567 72e18df1 Jose A. Lopes
  [ ("FileLoop",   "loop")
568 72e18df1 Jose A. Lopes
  , ("FileBlktap", "blktap")
569 c65621d7 Iustin Pop
  ])
570 c65621d7 Iustin Pop
$(THH.makeJSONInstance ''FileDriver)
571 6d558717 Iustin Pop
572 6d558717 Iustin Pop
-- | The instance create mode.
573 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "InstCreateMode"
574 72e18df1 Jose A. Lopes
  [ ("InstCreate",       "create")
575 72e18df1 Jose A. Lopes
  , ("InstImport",       "import")
576 72e18df1 Jose A. Lopes
  , ("InstRemoteImport", "remote-import")
577 6d558717 Iustin Pop
  ])
578 6d558717 Iustin Pop
$(THH.makeJSONInstance ''InstCreateMode)
579 c2d3219b Iustin Pop
580 c2d3219b Iustin Pop
-- | Reboot type.
581 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "RebootType"
582 72e18df1 Jose A. Lopes
  [ ("RebootSoft", "soft")
583 72e18df1 Jose A. Lopes
  , ("RebootHard", "hard")
584 72e18df1 Jose A. Lopes
  , ("RebootFull", "full")
585 c2d3219b Iustin Pop
  ])
586 c2d3219b Iustin Pop
$(THH.makeJSONInstance ''RebootType)
587 398e9066 Iustin Pop
588 398e9066 Iustin Pop
-- | Export modes.
589 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "ExportMode"
590 72e18df1 Jose A. Lopes
  [ ("ExportModeLocal",  "local")
591 661c765b Jose A. Lopes
  , ("ExportModeRemote", "remote")
592 398e9066 Iustin Pop
  ])
593 398e9066 Iustin Pop
$(THH.makeJSONInstance ''ExportMode)
594 a3f02317 Iustin Pop
595 a3f02317 Iustin Pop
-- | IAllocator run types (OpTestIAllocator).
596 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "IAllocatorTestDir"
597 72e18df1 Jose A. Lopes
  [ ("IAllocatorDirIn",  "in")
598 72e18df1 Jose A. Lopes
  , ("IAllocatorDirOut", "out")
599 a3f02317 Iustin Pop
  ])
600 a3f02317 Iustin Pop
$(THH.makeJSONInstance ''IAllocatorTestDir)
601 a3f02317 Iustin Pop
602 a3f02317 Iustin Pop
-- | IAllocator mode. FIXME: use this in "HTools.Backend.IAlloc".
603 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "IAllocatorMode"
604 72e18df1 Jose A. Lopes
  [ ("IAllocatorAlloc",       "allocate")
605 72e18df1 Jose A. Lopes
  , ("IAllocatorMultiAlloc",  "multi-allocate")
606 72e18df1 Jose A. Lopes
  , ("IAllocatorReloc",       "relocate")
607 72e18df1 Jose A. Lopes
  , ("IAllocatorNodeEvac",    "node-evacuate")
608 72e18df1 Jose A. Lopes
  , ("IAllocatorChangeGroup", "change-group")
609 a3f02317 Iustin Pop
  ])
610 a3f02317 Iustin Pop
$(THH.makeJSONInstance ''IAllocatorMode)
611 497beee2 Iustin Pop
612 3673a326 Helga Velroyen
-- | Network mode.
613 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "NICMode"
614 72e18df1 Jose A. Lopes
  [ ("NMBridged", "bridged")
615 72e18df1 Jose A. Lopes
  , ("NMRouted",  "routed")
616 72e18df1 Jose A. Lopes
  , ("NMOvs",     "openvswitch")
617 9f312bae Jose A. Lopes
  , ("NMPool",    "pool")
618 497beee2 Iustin Pop
  ])
619 497beee2 Iustin Pop
$(THH.makeJSONInstance ''NICMode)
620 6903fea0 Iustin Pop
621 3bdbe4b3 Dato Simó
-- | The JobStatus data type. Note that this is ordered especially
622 3bdbe4b3 Dato Simó
-- such that greater\/lesser comparison on values of this type makes
623 3bdbe4b3 Dato Simó
-- sense.
624 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "JobStatus"
625 4475d529 Jose A. Lopes
  [ ("JOB_STATUS_QUEUED",    "queued")
626 4475d529 Jose A. Lopes
  , ("JOB_STATUS_WAITING",   "waiting")
627 4475d529 Jose A. Lopes
  , ("JOB_STATUS_CANCELING", "canceling")
628 4475d529 Jose A. Lopes
  , ("JOB_STATUS_RUNNING",   "running")
629 4475d529 Jose A. Lopes
  , ("JOB_STATUS_CANCELED",  "canceled")
630 4475d529 Jose A. Lopes
  , ("JOB_STATUS_SUCCESS",   "success")
631 4475d529 Jose A. Lopes
  , ("JOB_STATUS_ERROR",     "error")
632 4475d529 Jose A. Lopes
  ])
633 3bdbe4b3 Dato Simó
$(THH.makeJSONInstance ''JobStatus)
634 3bdbe4b3 Dato Simó
635 6903fea0 Iustin Pop
-- | Finalized job status.
636 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "FinalizedJobStatus"
637 72e18df1 Jose A. Lopes
  [ ("JobStatusCanceled",   "canceled")
638 72e18df1 Jose A. Lopes
  , ("JobStatusSuccessful", "success")
639 72e18df1 Jose A. Lopes
  , ("JobStatusFailed",     "error")
640 6903fea0 Iustin Pop
  ])
641 6903fea0 Iustin Pop
$(THH.makeJSONInstance ''FinalizedJobStatus)
642 c48711d5 Iustin Pop
643 c48711d5 Iustin Pop
-- | The Ganeti job type.
644 c48711d5 Iustin Pop
newtype JobId = JobId { fromJobId :: Int }
645 c48711d5 Iustin Pop
  deriving (Show, Eq)
646 c48711d5 Iustin Pop
647 c48711d5 Iustin Pop
-- | Builds a job ID.
648 c48711d5 Iustin Pop
makeJobId :: (Monad m) => Int -> m JobId
649 c48711d5 Iustin Pop
makeJobId i | i >= 0 = return $ JobId i
650 c48711d5 Iustin Pop
            | otherwise = fail $ "Invalid value for job ID ' " ++ show i ++ "'"
651 c48711d5 Iustin Pop
652 fd958a3d Iustin Pop
-- | Builds a job ID from a string.
653 fd958a3d Iustin Pop
makeJobIdS :: (Monad m) => String -> m JobId
654 fd958a3d Iustin Pop
makeJobIdS s = tryRead "parsing job id" s >>= makeJobId
655 fd958a3d Iustin Pop
656 c48711d5 Iustin Pop
-- | Parses a job ID.
657 c48711d5 Iustin Pop
parseJobId :: (Monad m) => JSON.JSValue -> m JobId
658 fd958a3d Iustin Pop
parseJobId (JSON.JSString x) = makeJobIdS $ JSON.fromJSString x
659 c48711d5 Iustin Pop
parseJobId (JSON.JSRational _ x) =
660 c48711d5 Iustin Pop
  if denominator x /= 1
661 c48711d5 Iustin Pop
    then fail $ "Got fractional job ID from master daemon?! Value:" ++ show x
662 c48711d5 Iustin Pop
    -- FIXME: potential integer overflow here on 32-bit platforms
663 c48711d5 Iustin Pop
    else makeJobId . fromIntegral . numerator $ x
664 c48711d5 Iustin Pop
parseJobId x = fail $ "Wrong type/value for job id: " ++ show x
665 c48711d5 Iustin Pop
666 c48711d5 Iustin Pop
instance JSON.JSON JobId where
667 c48711d5 Iustin Pop
  showJSON = JSON.showJSON . fromJobId
668 c48711d5 Iustin Pop
  readJSON = parseJobId
669 b46ba79c Iustin Pop
670 b46ba79c Iustin Pop
-- | Relative job ID type alias.
671 b46ba79c Iustin Pop
type RelativeJobId = Negative Int
672 b46ba79c Iustin Pop
673 b46ba79c Iustin Pop
-- | Job ID dependency.
674 b46ba79c Iustin Pop
data JobIdDep = JobDepRelative RelativeJobId
675 b46ba79c Iustin Pop
              | JobDepAbsolute JobId
676 b46ba79c Iustin Pop
                deriving (Show, Eq)
677 b46ba79c Iustin Pop
678 b46ba79c Iustin Pop
instance JSON.JSON JobIdDep where
679 b46ba79c Iustin Pop
  showJSON (JobDepRelative i) = showJSON i
680 b46ba79c Iustin Pop
  showJSON (JobDepAbsolute i) = showJSON i
681 b46ba79c Iustin Pop
  readJSON v =
682 b46ba79c Iustin Pop
    case JSON.readJSON v::JSON.Result (Negative Int) of
683 b46ba79c Iustin Pop
      -- first try relative dependency, usually most common
684 b46ba79c Iustin Pop
      JSON.Ok r -> return $ JobDepRelative r
685 77d43564 Iustin Pop
      JSON.Error _ -> liftM JobDepAbsolute (parseJobId v)
686 b46ba79c Iustin Pop
687 966ea086 Klaus Aehlig
-- | From job ID dependency and job ID, compute the absolute dependency.
688 966ea086 Klaus Aehlig
absoluteJobIdDep :: (Monad m) => JobIdDep -> JobId -> m JobIdDep
689 966ea086 Klaus Aehlig
absoluteJobIdDep (JobDepAbsolute jid) _ = return $ JobDepAbsolute jid
690 966ea086 Klaus Aehlig
absoluteJobIdDep (JobDepRelative rjid) jid =
691 966ea086 Klaus Aehlig
  liftM JobDepAbsolute . makeJobId $ fromJobId jid + fromNegative rjid 
692 966ea086 Klaus Aehlig
693 b46ba79c Iustin Pop
-- | Job Dependency type.
694 b46ba79c Iustin Pop
data JobDependency = JobDependency JobIdDep [FinalizedJobStatus]
695 b46ba79c Iustin Pop
                     deriving (Show, Eq)
696 b46ba79c Iustin Pop
697 b46ba79c Iustin Pop
instance JSON JobDependency where
698 b46ba79c Iustin Pop
  showJSON (JobDependency dep status) = showJSON (dep, status)
699 b46ba79c Iustin Pop
  readJSON = liftM (uncurry JobDependency) . readJSON
700 b46ba79c Iustin Pop
701 966ea086 Klaus Aehlig
-- | From job dependency and job id compute an absolute job dependency.
702 966ea086 Klaus Aehlig
absoluteJobDependency :: (Monad m) => JobDependency -> JobId -> m JobDependency
703 966ea086 Klaus Aehlig
absoluteJobDependency (JobDependency jdep fstats) jid =
704 966ea086 Klaus Aehlig
  liftM (flip JobDependency fstats) $ absoluteJobIdDep jdep jid 
705 966ea086 Klaus Aehlig
706 b46ba79c Iustin Pop
-- | Valid opcode priorities for submit.
707 b46ba79c Iustin Pop
$(THH.declareIADT "OpSubmitPriority"
708 72e18df1 Jose A. Lopes
  [ ("OpPrioLow",    'ConstantUtils.priorityLow)
709 72e18df1 Jose A. Lopes
  , ("OpPrioNormal", 'ConstantUtils.priorityNormal)
710 72e18df1 Jose A. Lopes
  , ("OpPrioHigh",   'ConstantUtils.priorityHigh)
711 b46ba79c Iustin Pop
  ])
712 b46ba79c Iustin Pop
$(THH.makeJSONInstance ''OpSubmitPriority)
713 3bdbe4b3 Dato Simó
714 37fe56e0 Iustin Pop
-- | Parse submit priorities from a string.
715 37fe56e0 Iustin Pop
parseSubmitPriority :: (Monad m) => String -> m OpSubmitPriority
716 37fe56e0 Iustin Pop
parseSubmitPriority "low"    = return OpPrioLow
717 37fe56e0 Iustin Pop
parseSubmitPriority "normal" = return OpPrioNormal
718 37fe56e0 Iustin Pop
parseSubmitPriority "high"   = return OpPrioHigh
719 37fe56e0 Iustin Pop
parseSubmitPriority str      = fail $ "Unknown priority '" ++ str ++ "'"
720 37fe56e0 Iustin Pop
721 37fe56e0 Iustin Pop
-- | Format a submit priority as string.
722 37fe56e0 Iustin Pop
fmtSubmitPriority :: OpSubmitPriority -> String
723 37fe56e0 Iustin Pop
fmtSubmitPriority OpPrioLow    = "low"
724 37fe56e0 Iustin Pop
fmtSubmitPriority OpPrioNormal = "normal"
725 37fe56e0 Iustin Pop
fmtSubmitPriority OpPrioHigh   = "high"
726 37fe56e0 Iustin Pop
727 3bdbe4b3 Dato Simó
-- | Our ADT for the OpCode status at runtime (while in a job).
728 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "OpStatus"
729 72e18df1 Jose A. Lopes
  [ ("OP_STATUS_QUEUED",    "queued")
730 72e18df1 Jose A. Lopes
  , ("OP_STATUS_WAITING",   "waiting")
731 72e18df1 Jose A. Lopes
  , ("OP_STATUS_CANCELING", "canceling")
732 72e18df1 Jose A. Lopes
  , ("OP_STATUS_RUNNING",   "running")
733 72e18df1 Jose A. Lopes
  , ("OP_STATUS_CANCELED",  "canceled")
734 72e18df1 Jose A. Lopes
  , ("OP_STATUS_SUCCESS",   "success")
735 72e18df1 Jose A. Lopes
  , ("OP_STATUS_ERROR",     "error")
736 5cd95d46 Iustin Pop
  ])
737 3bdbe4b3 Dato Simó
$(THH.makeJSONInstance ''OpStatus)
738 5cd95d46 Iustin Pop
739 5cd95d46 Iustin Pop
-- | Type for the job message type.
740 72e18df1 Jose A. Lopes
$(THH.declareLADT ''String "ELogType"
741 72e18df1 Jose A. Lopes
  [ ("ELogMessage",      "message")
742 72e18df1 Jose A. Lopes
  , ("ELogRemoteImport", "remote-import")
743 72e18df1 Jose A. Lopes
  , ("ELogJqueueTest",   "jqueue-test")
744 5cd95d46 Iustin Pop
  ])
745 5cd95d46 Iustin Pop
$(THH.makeJSONInstance ''ELogType)
746 3ff890a1 Michele Tartara
747 3ff890a1 Michele Tartara
-- | Type of one element of a reason trail.
748 3ff890a1 Michele Tartara
type ReasonElem = (String, String, Integer)
749 3ff890a1 Michele Tartara
750 3ff890a1 Michele Tartara
-- | Type representing a reason trail.
751 3ff890a1 Michele Tartara
type ReasonTrail = [ReasonElem]
752 8e6ef316 Jose A. Lopes
753 8e6ef316 Jose A. Lopes
-- | The VTYPES, a mini-type system in Python.
754 8e6ef316 Jose A. Lopes
$(THH.declareLADT ''String "VType"
755 8e6ef316 Jose A. Lopes
  [ ("VTypeString",      "string")
756 8e6ef316 Jose A. Lopes
  , ("VTypeMaybeString", "maybe-string")
757 8e6ef316 Jose A. Lopes
  , ("VTypeBool",        "bool")
758 8e6ef316 Jose A. Lopes
  , ("VTypeSize",        "size")
759 8e6ef316 Jose A. Lopes
  , ("VTypeInt",         "int")
760 8e6ef316 Jose A. Lopes
  ])
761 8e6ef316 Jose A. Lopes
$(THH.makeJSONInstance ''VType)
762 8e6ef316 Jose A. Lopes
763 59bcd180 Jose A. Lopes
instance THH.PyValue VType where
764 59bcd180 Jose A. Lopes
  showValue = THH.showValue . vTypeToRaw
765 59bcd180 Jose A. Lopes
766 8e6ef316 Jose A. Lopes
-- * Node role type
767 8e6ef316 Jose A. Lopes
768 8e6ef316 Jose A. Lopes
$(THH.declareLADT ''String "NodeRole"
769 8e6ef316 Jose A. Lopes
  [ ("NROffline",   "O")
770 8e6ef316 Jose A. Lopes
  , ("NRDrained",   "D")
771 8e6ef316 Jose A. Lopes
  , ("NRRegular",   "R")
772 8e6ef316 Jose A. Lopes
  , ("NRCandidate", "C")
773 8e6ef316 Jose A. Lopes
  , ("NRMaster",    "M")
774 8e6ef316 Jose A. Lopes
  ])
775 8e6ef316 Jose A. Lopes
$(THH.makeJSONInstance ''NodeRole)
776 8e6ef316 Jose A. Lopes
777 8e6ef316 Jose A. Lopes
-- | The description of the node role.
778 8e6ef316 Jose A. Lopes
roleDescription :: NodeRole -> String
779 8e6ef316 Jose A. Lopes
roleDescription NROffline   = "offline"
780 8e6ef316 Jose A. Lopes
roleDescription NRDrained   = "drained"
781 8e6ef316 Jose A. Lopes
roleDescription NRRegular   = "regular"
782 8e6ef316 Jose A. Lopes
roleDescription NRCandidate = "master candidate"
783 8e6ef316 Jose A. Lopes
roleDescription NRMaster    = "master"
784 8e6ef316 Jose A. Lopes
785 8e6ef316 Jose A. Lopes
-- * Disk types
786 8e6ef316 Jose A. Lopes
787 8e6ef316 Jose A. Lopes
$(THH.declareLADT ''String "DiskMode"
788 8e6ef316 Jose A. Lopes
  [ ("DiskRdOnly", "ro")
789 8e6ef316 Jose A. Lopes
  , ("DiskRdWr",   "rw")
790 8e6ef316 Jose A. Lopes
  ])
791 8e6ef316 Jose A. Lopes
$(THH.makeJSONInstance ''DiskMode)
792 8e6ef316 Jose A. Lopes
793 8e6ef316 Jose A. Lopes
-- | The persistent block driver type. Currently only one type is allowed.
794 8e6ef316 Jose A. Lopes
$(THH.declareLADT ''String "BlockDriver"
795 8e6ef316 Jose A. Lopes
  [ ("BlockDrvManual", "manual")
796 8e6ef316 Jose A. Lopes
  ])
797 8e6ef316 Jose A. Lopes
$(THH.makeJSONInstance ''BlockDriver)
798 8e6ef316 Jose A. Lopes
799 8e6ef316 Jose A. Lopes
-- * Instance types
800 8e6ef316 Jose A. Lopes
801 8e6ef316 Jose A. Lopes
$(THH.declareLADT ''String "AdminState"
802 8e6ef316 Jose A. Lopes
  [ ("AdminOffline", "offline")
803 8e6ef316 Jose A. Lopes
  , ("AdminDown",    "down")
804 8e6ef316 Jose A. Lopes
  , ("AdminUp",      "up")
805 8e6ef316 Jose A. Lopes
  ])
806 8e6ef316 Jose A. Lopes
$(THH.makeJSONInstance ''AdminState)
807 ccf17aa3 Jose A. Lopes
808 ccf17aa3 Jose A. Lopes
-- * Storage field type
809 ccf17aa3 Jose A. Lopes
810 ccf17aa3 Jose A. Lopes
$(THH.declareLADT ''String "StorageField"
811 ccf17aa3 Jose A. Lopes
  [ ( "SFUsed",        "used")
812 ccf17aa3 Jose A. Lopes
  , ( "SFName",        "name")
813 ccf17aa3 Jose A. Lopes
  , ( "SFAllocatable", "allocatable")
814 ccf17aa3 Jose A. Lopes
  , ( "SFFree",        "free")
815 ccf17aa3 Jose A. Lopes
  , ( "SFSize",        "size")
816 ccf17aa3 Jose A. Lopes
  ])
817 ccf17aa3 Jose A. Lopes
$(THH.makeJSONInstance ''StorageField)
818 9b9e088c Raffa Santi
819 9b9e088c Raffa Santi
-- * Disk access protocol
820 9b9e088c Raffa Santi
821 9b9e088c Raffa Santi
$(THH.declareLADT ''String "DiskAccessMode"
822 9b9e088c Raffa Santi
  [ ( "DiskUserspace",   "userspace")
823 9b9e088c Raffa Santi
  , ( "DiskKernelspace", "kernelspace")
824 9b9e088c Raffa Santi
  ])
825 9b9e088c Raffa Santi
$(THH.makeJSONInstance ''DiskAccessMode)
826 a5450d2a Jose A. Lopes
827 59bcd180 Jose A. Lopes
-- | Local disk status
828 59bcd180 Jose A. Lopes
--
829 59bcd180 Jose A. Lopes
-- Python code depends on:
830 59bcd180 Jose A. Lopes
--   DiskStatusOk < DiskStatusUnknown < DiskStatusFaulty
831 59bcd180 Jose A. Lopes
$(THH.declareILADT "LocalDiskStatus"
832 59bcd180 Jose A. Lopes
  [ ("DiskStatusFaulty",  3)
833 59bcd180 Jose A. Lopes
  , ("DiskStatusOk",      1)
834 59bcd180 Jose A. Lopes
  , ("DiskStatusUnknown", 2)
835 59bcd180 Jose A. Lopes
  ])
836 59bcd180 Jose A. Lopes
837 59bcd180 Jose A. Lopes
localDiskStatusName :: LocalDiskStatus -> String
838 59bcd180 Jose A. Lopes
localDiskStatusName DiskStatusFaulty = "faulty"
839 59bcd180 Jose A. Lopes
localDiskStatusName DiskStatusOk = "ok"
840 59bcd180 Jose A. Lopes
localDiskStatusName DiskStatusUnknown = "unknown"
841 59bcd180 Jose A. Lopes
842 a5450d2a Jose A. Lopes
-- | Replace disks type.
843 a5450d2a Jose A. Lopes
$(THH.declareLADT ''String "ReplaceDisksMode"
844 a5450d2a Jose A. Lopes
  [ -- Replace disks on primary
845 a5450d2a Jose A. Lopes
    ("ReplaceOnPrimary",    "replace_on_primary")
846 a5450d2a Jose A. Lopes
    -- Replace disks on secondary
847 a5450d2a Jose A. Lopes
  , ("ReplaceOnSecondary",  "replace_on_secondary")
848 a5450d2a Jose A. Lopes
    -- Change secondary node
849 a5450d2a Jose A. Lopes
  , ("ReplaceNewSecondary", "replace_new_secondary")
850 a5450d2a Jose A. Lopes
  , ("ReplaceAuto",         "replace_auto")
851 a5450d2a Jose A. Lopes
  ])
852 a5450d2a Jose A. Lopes
$(THH.makeJSONInstance ''ReplaceDisksMode)
853 c03224f6 Jose A. Lopes
854 c03224f6 Jose A. Lopes
-- | Basic timeouts for RPC calls.
855 c03224f6 Jose A. Lopes
$(THH.declareILADT "RpcTimeout"
856 c03224f6 Jose A. Lopes
  [ ("Urgent",    60)       -- 1 minute
857 c03224f6 Jose A. Lopes
  , ("Fast",      5 * 60)   -- 5 minutes
858 c03224f6 Jose A. Lopes
  , ("Normal",    15 * 60)  -- 15 minutes
859 c03224f6 Jose A. Lopes
  , ("Slow",      3600)     -- 1 hour
860 c03224f6 Jose A. Lopes
  , ("FourHours", 4 * 3600) -- 4 hours
861 c03224f6 Jose A. Lopes
  , ("OneDay",    86400)    -- 1 day
862 c03224f6 Jose A. Lopes
  ])
863 f198cf91 Thomas Thrainer
864 f198cf91 Thomas Thrainer
$(THH.declareLADT ''String "ImportExportCompression"
865 f198cf91 Thomas Thrainer
  [ -- No compression
866 f198cf91 Thomas Thrainer
    ("None", "none")
867 f198cf91 Thomas Thrainer
    -- gzip compression
868 f198cf91 Thomas Thrainer
  , ("GZip", "gzip")
869 f198cf91 Thomas Thrainer
  ])
870 f198cf91 Thomas Thrainer
$(THH.makeJSONInstance ''ImportExportCompression)
871 f198cf91 Thomas Thrainer
872 f198cf91 Thomas Thrainer
instance THH.PyValue ImportExportCompression where
873 f198cf91 Thomas Thrainer
  showValue = THH.showValue . importExportCompressionToRaw
874 bb133242 Klaus Aehlig
875 9569d877 Dimitris Aragiorgis
-- | Hotplug action.
876 9569d877 Dimitris Aragiorgis
877 9569d877 Dimitris Aragiorgis
$(THH.declareLADT ''String "HotplugAction"
878 9569d877 Dimitris Aragiorgis
  [ ("HAAdd", "hotadd")
879 9569d877 Dimitris Aragiorgis
  , ("HARemove",  "hotremove")
880 9569d877 Dimitris Aragiorgis
  , ("HAMod",     "hotmod")
881 9569d877 Dimitris Aragiorgis
  ])
882 9569d877 Dimitris Aragiorgis
$(THH.makeJSONInstance ''HotplugAction)
883 9569d877 Dimitris Aragiorgis
884 9569d877 Dimitris Aragiorgis
-- | Hotplug Device Target.
885 9569d877 Dimitris Aragiorgis
886 9569d877 Dimitris Aragiorgis
$(THH.declareLADT ''String "HotplugTarget"
887 9569d877 Dimitris Aragiorgis
  [ ("HTDisk", "hotdisk")
888 9569d877 Dimitris Aragiorgis
  , ("HTNic",  "hotnic")
889 9569d877 Dimitris Aragiorgis
  ])
890 9569d877 Dimitris Aragiorgis
$(THH.makeJSONInstance ''HotplugTarget)