Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Types.hs @ 13d26b66

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