Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 88b58ed6

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