Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 13ef1fa5

History | View | Annotate | Download (45.5 kB)

1 92f51573 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 92f51573 Iustin Pop
3 92f51573 Iustin Pop
{-| Implementation of opcodes parameters.
4 92f51573 Iustin Pop
5 92f51573 Iustin Pop
These are defined in a separate module only due to TemplateHaskell
6 92f51573 Iustin Pop
stage restrictions - expressions defined in the current module can't
7 92f51573 Iustin Pop
be passed to splices. So we have to either parameters/repeat each
8 92f51573 Iustin Pop
parameter definition multiple times, or separate them into this
9 92f51573 Iustin Pop
module.
10 92f51573 Iustin Pop
11 92f51573 Iustin Pop
-}
12 92f51573 Iustin Pop
13 92f51573 Iustin Pop
{-
14 92f51573 Iustin Pop
15 92f51573 Iustin Pop
Copyright (C) 2012 Google Inc.
16 92f51573 Iustin Pop
17 92f51573 Iustin Pop
This program is free software; you can redistribute it and/or modify
18 92f51573 Iustin Pop
it under the terms of the GNU General Public License as published by
19 92f51573 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
20 92f51573 Iustin Pop
(at your option) any later version.
21 92f51573 Iustin Pop
22 92f51573 Iustin Pop
This program is distributed in the hope that it will be useful, but
23 92f51573 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
24 92f51573 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25 92f51573 Iustin Pop
General Public License for more details.
26 92f51573 Iustin Pop
27 92f51573 Iustin Pop
You should have received a copy of the GNU General Public License
28 92f51573 Iustin Pop
along with this program; if not, write to the Free Software
29 92f51573 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30 92f51573 Iustin Pop
02110-1301, USA.
31 92f51573 Iustin Pop
32 92f51573 Iustin Pop
-}
33 92f51573 Iustin Pop
34 92f51573 Iustin Pop
module Ganeti.OpParams
35 92f51573 Iustin Pop
  ( TagType(..)
36 92f51573 Iustin Pop
  , TagObject(..)
37 92f51573 Iustin Pop
  , tagObjectFrom
38 ad1c1e41 Iustin Pop
  , tagNameOf
39 92f51573 Iustin Pop
  , decodeTagObject
40 92f51573 Iustin Pop
  , encodeTagObject
41 92f51573 Iustin Pop
  , ReplaceDisksMode(..)
42 92f51573 Iustin Pop
  , DiskIndex
43 92f51573 Iustin Pop
  , mkDiskIndex
44 92f51573 Iustin Pop
  , unDiskIndex
45 6d558717 Iustin Pop
  , DiskAccess(..)
46 d6979f35 Iustin Pop
  , INicParams(..)
47 d6979f35 Iustin Pop
  , IDiskParams(..)
48 c2d3219b Iustin Pop
  , RecreateDisksInfo(..)
49 c2d3219b Iustin Pop
  , DdmOldChanges(..)
50 c2d3219b Iustin Pop
  , SetParamsMods(..)
51 398e9066 Iustin Pop
  , ExportTarget(..)
52 92f51573 Iustin Pop
  , pInstanceName
53 da4a52a3 Thomas Thrainer
  , pInstanceUuid
54 d6979f35 Iustin Pop
  , pInstances
55 d6979f35 Iustin Pop
  , pName
56 92f51573 Iustin Pop
  , pTagsList
57 92f51573 Iustin Pop
  , pTagsObject
58 d6979f35 Iustin Pop
  , pOutputFields
59 d6979f35 Iustin Pop
  , pShutdownTimeout
60 c2d3219b Iustin Pop
  , pShutdownTimeout'
61 67fc4de7 Iustin Pop
  , pShutdownInstance
62 d6979f35 Iustin Pop
  , pForce
63 d6979f35 Iustin Pop
  , pIgnoreOfflineNodes
64 d6979f35 Iustin Pop
  , pNodeName
65 1c3231aa Thomas Thrainer
  , pNodeUuid
66 d6979f35 Iustin Pop
  , pNodeNames
67 1c3231aa Thomas Thrainer
  , pNodeUuids
68 d6979f35 Iustin Pop
  , pGroupName
69 d6979f35 Iustin Pop
  , pMigrationMode
70 d6979f35 Iustin Pop
  , pMigrationLive
71 7d421386 Iustin Pop
  , pMigrationCleanup
72 d6979f35 Iustin Pop
  , pForceVariant
73 d6979f35 Iustin Pop
  , pWaitForSync
74 d6979f35 Iustin Pop
  , pWaitForSyncFalse
75 d6979f35 Iustin Pop
  , pIgnoreConsistency
76 d6979f35 Iustin Pop
  , pStorageName
77 d6979f35 Iustin Pop
  , pUseLocking
78 1f1188c3 Michael Hanselmann
  , pOpportunisticLocking
79 d6979f35 Iustin Pop
  , pNameCheck
80 d6979f35 Iustin Pop
  , pNodeGroupAllocPolicy
81 d6979f35 Iustin Pop
  , pGroupNodeParams
82 d6979f35 Iustin Pop
  , pQueryWhat
83 d6979f35 Iustin Pop
  , pEarlyRelease
84 6d558717 Iustin Pop
  , pIpCheck
85 6d558717 Iustin Pop
  , pIpConflictsCheck
86 d6979f35 Iustin Pop
  , pNoRemember
87 d6979f35 Iustin Pop
  , pMigrationTargetNode
88 1c3231aa Thomas Thrainer
  , pMigrationTargetNodeUuid
89 c2d3219b Iustin Pop
  , pMoveTargetNode
90 1c3231aa Thomas Thrainer
  , pMoveTargetNodeUuid
91 d6979f35 Iustin Pop
  , pStartupPaused
92 d6979f35 Iustin Pop
  , pVerbose
93 d6979f35 Iustin Pop
  , pDebugSimulateErrors
94 d6979f35 Iustin Pop
  , pErrorCodes
95 d6979f35 Iustin Pop
  , pSkipChecks
96 d6979f35 Iustin Pop
  , pIgnoreErrors
97 d6979f35 Iustin Pop
  , pOptGroupName
98 d6979f35 Iustin Pop
  , pDiskParams
99 d6979f35 Iustin Pop
  , pHvState
100 d6979f35 Iustin Pop
  , pDiskState
101 d6979f35 Iustin Pop
  , pIgnoreIpolicy
102 d6979f35 Iustin Pop
  , pAllowRuntimeChgs
103 6d558717 Iustin Pop
  , pInstDisks
104 6d558717 Iustin Pop
  , pDiskTemplate
105 88127c47 Iustin Pop
  , pOptDiskTemplate
106 6d558717 Iustin Pop
  , pFileDriver
107 6d558717 Iustin Pop
  , pFileStorageDir
108 3039e2dc Helga Velroyen
  , pGlobalFileStorageDir
109 4e6cfd11 Helga Velroyen
  , pGlobalSharedFileStorageDir
110 d6979f35 Iustin Pop
  , pVgName
111 d6979f35 Iustin Pop
  , pEnabledHypervisors
112 6d558717 Iustin Pop
  , pHypervisor
113 d6979f35 Iustin Pop
  , pClusterHvParams
114 6d558717 Iustin Pop
  , pInstHvParams
115 d6979f35 Iustin Pop
  , pClusterBeParams
116 6d558717 Iustin Pop
  , pInstBeParams
117 6d558717 Iustin Pop
  , pResetDefaults
118 d6979f35 Iustin Pop
  , pOsHvp
119 6d558717 Iustin Pop
  , pClusterOsParams
120 6d558717 Iustin Pop
  , pInstOsParams
121 d6979f35 Iustin Pop
  , pCandidatePoolSize
122 d6979f35 Iustin Pop
  , pUidPool
123 d6979f35 Iustin Pop
  , pAddUids
124 d6979f35 Iustin Pop
  , pRemoveUids
125 d6979f35 Iustin Pop
  , pMaintainNodeHealth
126 75f2ff7d Michele Tartara
  , pModifyEtcHosts
127 d6979f35 Iustin Pop
  , pPreallocWipeDisks
128 d6979f35 Iustin Pop
  , pNicParams
129 6d558717 Iustin Pop
  , pInstNics
130 d6979f35 Iustin Pop
  , pNdParams
131 d6979f35 Iustin Pop
  , pIpolicy
132 d6979f35 Iustin Pop
  , pDrbdHelper
133 d6979f35 Iustin Pop
  , pDefaultIAllocator
134 d6979f35 Iustin Pop
  , pMasterNetdev
135 d6979f35 Iustin Pop
  , pMasterNetmask
136 d6979f35 Iustin Pop
  , pReservedLvs
137 d6979f35 Iustin Pop
  , pHiddenOs
138 d6979f35 Iustin Pop
  , pBlacklistedOs
139 d6979f35 Iustin Pop
  , pUseExternalMipScript
140 d6979f35 Iustin Pop
  , pQueryFields
141 d6979f35 Iustin Pop
  , pQueryFilter
142 d6979f35 Iustin Pop
  , pOobCommand
143 d6979f35 Iustin Pop
  , pOobTimeout
144 d6979f35 Iustin Pop
  , pIgnoreStatus
145 d6979f35 Iustin Pop
  , pPowerDelay
146 d6979f35 Iustin Pop
  , pPrimaryIp
147 d6979f35 Iustin Pop
  , pSecondaryIp
148 d6979f35 Iustin Pop
  , pReadd
149 d6979f35 Iustin Pop
  , pNodeGroup
150 d6979f35 Iustin Pop
  , pMasterCapable
151 d6979f35 Iustin Pop
  , pVmCapable
152 d6979f35 Iustin Pop
  , pNames
153 d6979f35 Iustin Pop
  , pNodes
154 398e9066 Iustin Pop
  , pRequiredNodes
155 1c3231aa Thomas Thrainer
  , pRequiredNodeUuids
156 d6979f35 Iustin Pop
  , pStorageType
157 d6979f35 Iustin Pop
  , pStorageChanges
158 d6979f35 Iustin Pop
  , pMasterCandidate
159 d6979f35 Iustin Pop
  , pOffline
160 d6979f35 Iustin Pop
  , pDrained
161 d6979f35 Iustin Pop
  , pAutoPromote
162 d6979f35 Iustin Pop
  , pPowered
163 d6979f35 Iustin Pop
  , pIallocator
164 d6979f35 Iustin Pop
  , pRemoteNode
165 1c3231aa Thomas Thrainer
  , pRemoteNodeUuid
166 d6979f35 Iustin Pop
  , pEvacMode
167 6d558717 Iustin Pop
  , pInstCreateMode
168 6d558717 Iustin Pop
  , pNoInstall
169 6d558717 Iustin Pop
  , pInstOs
170 6d558717 Iustin Pop
  , pPrimaryNode
171 1c3231aa Thomas Thrainer
  , pPrimaryNodeUuid
172 6d558717 Iustin Pop
  , pSecondaryNode
173 1c3231aa Thomas Thrainer
  , pSecondaryNodeUuid
174 6d558717 Iustin Pop
  , pSourceHandshake
175 6d558717 Iustin Pop
  , pSourceInstance
176 6d558717 Iustin Pop
  , pSourceShutdownTimeout
177 6d558717 Iustin Pop
  , pSourceX509Ca
178 6d558717 Iustin Pop
  , pSrcNode
179 1c3231aa Thomas Thrainer
  , pSrcNodeUuid
180 6d558717 Iustin Pop
  , pSrcPath
181 6d558717 Iustin Pop
  , pStartInstance
182 6d558717 Iustin Pop
  , pInstTags
183 c2d3219b Iustin Pop
  , pMultiAllocInstances
184 c2d3219b Iustin Pop
  , pTempOsParams
185 c2d3219b Iustin Pop
  , pTempHvParams
186 c2d3219b Iustin Pop
  , pTempBeParams
187 c2d3219b Iustin Pop
  , pIgnoreFailures
188 c2d3219b Iustin Pop
  , pNewName
189 c2d3219b Iustin Pop
  , pIgnoreSecondaries
190 c2d3219b Iustin Pop
  , pRebootType
191 c2d3219b Iustin Pop
  , pIgnoreDiskSize
192 c2d3219b Iustin Pop
  , pRecreateDisksInfo
193 c2d3219b Iustin Pop
  , pStatic
194 c2d3219b Iustin Pop
  , pInstParamsNicChanges
195 c2d3219b Iustin Pop
  , pInstParamsDiskChanges
196 c2d3219b Iustin Pop
  , pRuntimeMem
197 c2d3219b Iustin Pop
  , pOsNameChange
198 c2d3219b Iustin Pop
  , pDiskIndex
199 c2d3219b Iustin Pop
  , pDiskChgAmount
200 c2d3219b Iustin Pop
  , pDiskChgAbsolute
201 c2d3219b Iustin Pop
  , pTargetGroups
202 398e9066 Iustin Pop
  , pExportMode
203 398e9066 Iustin Pop
  , pExportTargetNode
204 1c3231aa Thomas Thrainer
  , pExportTargetNodeUuid
205 398e9066 Iustin Pop
  , pRemoveInstance
206 398e9066 Iustin Pop
  , pIgnoreRemoveFailures
207 398e9066 Iustin Pop
  , pX509KeyName
208 398e9066 Iustin Pop
  , pX509DestCA
209 a451dae2 Iustin Pop
  , pTagSearchPattern
210 1cd563e2 Iustin Pop
  , pRestrictedCommand
211 7d421386 Iustin Pop
  , pReplaceDisksMode
212 7d421386 Iustin Pop
  , pReplaceDisksList
213 7d421386 Iustin Pop
  , pAllowFailover
214 7d421386 Iustin Pop
  , pDelayDuration
215 7d421386 Iustin Pop
  , pDelayOnMaster
216 7d421386 Iustin Pop
  , pDelayOnNodes
217 1c3231aa Thomas Thrainer
  , pDelayOnNodeUuids
218 a451dae2 Iustin Pop
  , pDelayRepeat
219 a3f02317 Iustin Pop
  , pIAllocatorDirection
220 a3f02317 Iustin Pop
  , pIAllocatorMode
221 a3f02317 Iustin Pop
  , pIAllocatorReqName
222 a3f02317 Iustin Pop
  , pIAllocatorNics
223 a3f02317 Iustin Pop
  , pIAllocatorDisks
224 a3f02317 Iustin Pop
  , pIAllocatorMemory
225 a3f02317 Iustin Pop
  , pIAllocatorVCpus
226 a3f02317 Iustin Pop
  , pIAllocatorOs
227 a3f02317 Iustin Pop
  , pIAllocatorInstances
228 a3f02317 Iustin Pop
  , pIAllocatorEvacMode
229 a3f02317 Iustin Pop
  , pIAllocatorSpindleUse
230 a3f02317 Iustin Pop
  , pIAllocatorCount
231 a3f02317 Iustin Pop
  , pJQueueNotifyWaitLock
232 a3f02317 Iustin Pop
  , pJQueueNotifyExec
233 a3f02317 Iustin Pop
  , pJQueueLogMessages
234 a3f02317 Iustin Pop
  , pJQueueFail
235 a3f02317 Iustin Pop
  , pTestDummyResult
236 a3f02317 Iustin Pop
  , pTestDummyMessages
237 a3f02317 Iustin Pop
  , pTestDummyFail
238 a3f02317 Iustin Pop
  , pTestDummySubmitJobs
239 8d239fa4 Iustin Pop
  , pNetworkName
240 8d239fa4 Iustin Pop
  , pNetworkAddress4
241 8d239fa4 Iustin Pop
  , pNetworkGateway4
242 8d239fa4 Iustin Pop
  , pNetworkAddress6
243 8d239fa4 Iustin Pop
  , pNetworkGateway6
244 8d239fa4 Iustin Pop
  , pNetworkMacPrefix
245 8d239fa4 Iustin Pop
  , pNetworkAddRsvdIps
246 8d239fa4 Iustin Pop
  , pNetworkRemoveRsvdIps
247 8d239fa4 Iustin Pop
  , pNetworkMode
248 8d239fa4 Iustin Pop
  , pNetworkLink
249 b46ba79c Iustin Pop
  , pDryRun
250 b46ba79c Iustin Pop
  , pDebugLevel
251 b46ba79c Iustin Pop
  , pOpPriority
252 b46ba79c Iustin Pop
  , pDependencies
253 b46ba79c Iustin Pop
  , pComment
254 516a0e94 Michele Tartara
  , pReason
255 66af5ec5 Helga Velroyen
  , pEnabledDiskTemplates
256 3131adc7 Iustin Pop
  , dOldQuery
257 3131adc7 Iustin Pop
  , dOldQueryNoLocking
258 92f51573 Iustin Pop
  ) where
259 92f51573 Iustin Pop
260 c2d3219b Iustin Pop
import Control.Monad (liftM)
261 d6979f35 Iustin Pop
import qualified Data.Set as Set
262 d6979f35 Iustin Pop
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
263 6d558717 Iustin Pop
                  JSObject, toJSObject)
264 c2d3219b Iustin Pop
import qualified Text.JSON
265 92f51573 Iustin Pop
import Text.JSON.Pretty (pp_value)
266 92f51573 Iustin Pop
267 6d558717 Iustin Pop
import Ganeti.BasicTypes
268 92f51573 Iustin Pop
import qualified Ganeti.Constants as C
269 92f51573 Iustin Pop
import Ganeti.THH
270 92f51573 Iustin Pop
import Ganeti.JSON
271 d6979f35 Iustin Pop
import Ganeti.Types
272 d6979f35 Iustin Pop
import qualified Ganeti.Query.Language as Qlang
273 92f51573 Iustin Pop
274 92f51573 Iustin Pop
-- * Helper functions and types
275 92f51573 Iustin Pop
276 d6979f35 Iustin Pop
-- * Type aliases
277 d6979f35 Iustin Pop
278 d6979f35 Iustin Pop
-- | Build a boolean field.
279 d6979f35 Iustin Pop
booleanField :: String -> Field
280 d6979f35 Iustin Pop
booleanField = flip simpleField [t| Bool |]
281 d6979f35 Iustin Pop
282 d6979f35 Iustin Pop
-- | Default a field to 'False'.
283 d6979f35 Iustin Pop
defaultFalse :: String -> Field
284 d6979f35 Iustin Pop
defaultFalse = defaultField [| False |] . booleanField
285 d6979f35 Iustin Pop
286 d6979f35 Iustin Pop
-- | Default a field to 'True'.
287 d6979f35 Iustin Pop
defaultTrue :: String -> Field
288 d6979f35 Iustin Pop
defaultTrue = defaultField [| True |] . booleanField
289 d6979f35 Iustin Pop
290 d6979f35 Iustin Pop
-- | An alias for a 'String' field.
291 d6979f35 Iustin Pop
stringField :: String -> Field
292 d6979f35 Iustin Pop
stringField = flip simpleField [t| String |]
293 d6979f35 Iustin Pop
294 d6979f35 Iustin Pop
-- | An alias for an optional string field.
295 d6979f35 Iustin Pop
optionalStringField :: String -> Field
296 d6979f35 Iustin Pop
optionalStringField = optionalField . stringField
297 d6979f35 Iustin Pop
298 d6979f35 Iustin Pop
-- | An alias for an optional non-empty string field.
299 d6979f35 Iustin Pop
optionalNEStringField :: String -> Field
300 d6979f35 Iustin Pop
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
301 d6979f35 Iustin Pop
302 a3f02317 Iustin Pop
-- | Unchecked value, should be replaced by a better definition.
303 a3f02317 Iustin Pop
type UncheckedValue = JSValue
304 d6979f35 Iustin Pop
305 d6979f35 Iustin Pop
-- | Unchecked dict, should be replaced by a better definition.
306 d6979f35 Iustin Pop
type UncheckedDict = JSObject JSValue
307 d6979f35 Iustin Pop
308 6d558717 Iustin Pop
-- | Unchecked list, shoild be replaced by a better definition.
309 6d558717 Iustin Pop
type UncheckedList = [JSValue]
310 6d558717 Iustin Pop
311 6d558717 Iustin Pop
-- | Function to force a non-negative value, without returning via a
312 6d558717 Iustin Pop
-- monad. This is needed for, and should be used /only/ in the case of
313 6d558717 Iustin Pop
-- forcing constants. In case the constant is wrong (< 0), this will
314 6d558717 Iustin Pop
-- become a runtime error.
315 6d558717 Iustin Pop
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
316 6d558717 Iustin Pop
forceNonNeg i = case mkNonNegative i of
317 6d558717 Iustin Pop
                  Ok n -> n
318 6d558717 Iustin Pop
                  Bad msg -> error msg
319 6d558717 Iustin Pop
320 92f51573 Iustin Pop
-- ** Tags
321 92f51573 Iustin Pop
322 92f51573 Iustin Pop
-- | Data type representing what items do the tag operations apply to.
323 92f51573 Iustin Pop
$(declareSADT "TagType"
324 92f51573 Iustin Pop
  [ ("TagTypeInstance", 'C.tagInstance)
325 92f51573 Iustin Pop
  , ("TagTypeNode",     'C.tagNode)
326 92f51573 Iustin Pop
  , ("TagTypeGroup",    'C.tagNodegroup)
327 92f51573 Iustin Pop
  , ("TagTypeCluster",  'C.tagCluster)
328 9d0b521e Dimitris Aragiorgis
  , ("TagTypeNetwork",  'C.tagNetwork)
329 92f51573 Iustin Pop
  ])
330 92f51573 Iustin Pop
$(makeJSONInstance ''TagType)
331 92f51573 Iustin Pop
332 92f51573 Iustin Pop
-- | Data type holding a tag object (type and object name).
333 92f51573 Iustin Pop
data TagObject = TagInstance String
334 92f51573 Iustin Pop
               | TagNode     String
335 92f51573 Iustin Pop
               | TagGroup    String
336 9d0b521e Dimitris Aragiorgis
               | TagNetwork  String
337 92f51573 Iustin Pop
               | TagCluster
338 139c0683 Iustin Pop
               deriving (Show, Eq)
339 92f51573 Iustin Pop
340 92f51573 Iustin Pop
-- | Tag type for a given tag object.
341 92f51573 Iustin Pop
tagTypeOf :: TagObject -> TagType
342 92f51573 Iustin Pop
tagTypeOf (TagInstance {}) = TagTypeInstance
343 92f51573 Iustin Pop
tagTypeOf (TagNode     {}) = TagTypeNode
344 92f51573 Iustin Pop
tagTypeOf (TagGroup    {}) = TagTypeGroup
345 92f51573 Iustin Pop
tagTypeOf (TagCluster  {}) = TagTypeCluster
346 9d0b521e Dimitris Aragiorgis
tagTypeOf (TagNetwork  {}) = TagTypeNetwork
347 92f51573 Iustin Pop
348 92f51573 Iustin Pop
-- | Gets the potential tag object name.
349 92f51573 Iustin Pop
tagNameOf :: TagObject -> Maybe String
350 92f51573 Iustin Pop
tagNameOf (TagInstance s) = Just s
351 92f51573 Iustin Pop
tagNameOf (TagNode     s) = Just s
352 92f51573 Iustin Pop
tagNameOf (TagGroup    s) = Just s
353 9d0b521e Dimitris Aragiorgis
tagNameOf (TagNetwork  s) = Just s
354 92f51573 Iustin Pop
tagNameOf  TagCluster     = Nothing
355 92f51573 Iustin Pop
356 92f51573 Iustin Pop
-- | Builds a 'TagObject' from a tag type and name.
357 92f51573 Iustin Pop
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
358 92f51573 Iustin Pop
tagObjectFrom TagTypeInstance (JSString s) =
359 92f51573 Iustin Pop
  return . TagInstance $ fromJSString s
360 92f51573 Iustin Pop
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
361 92f51573 Iustin Pop
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
362 9d0b521e Dimitris Aragiorgis
tagObjectFrom TagTypeNetwork  (JSString s) =
363 9d0b521e Dimitris Aragiorgis
  return . TagNetwork $ fromJSString s
364 92f51573 Iustin Pop
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
365 92f51573 Iustin Pop
tagObjectFrom t v =
366 92f51573 Iustin Pop
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
367 92f51573 Iustin Pop
         show (pp_value v)
368 92f51573 Iustin Pop
369 92f51573 Iustin Pop
-- | Name of the tag \"name\" field.
370 92f51573 Iustin Pop
tagNameField :: String
371 92f51573 Iustin Pop
tagNameField = "name"
372 92f51573 Iustin Pop
373 92f51573 Iustin Pop
-- | Custom encoder for 'TagObject' as represented in an opcode.
374 92f51573 Iustin Pop
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
375 92f51573 Iustin Pop
encodeTagObject t = ( showJSON (tagTypeOf t)
376 92f51573 Iustin Pop
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
377 92f51573 Iustin Pop
378 92f51573 Iustin Pop
-- | Custom decoder for 'TagObject' as represented in an opcode.
379 92f51573 Iustin Pop
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
380 92f51573 Iustin Pop
decodeTagObject obj kind = do
381 92f51573 Iustin Pop
  ttype <- fromJVal kind
382 92f51573 Iustin Pop
  tname <- fromObj obj tagNameField
383 92f51573 Iustin Pop
  tagObjectFrom ttype tname
384 92f51573 Iustin Pop
385 92f51573 Iustin Pop
-- ** Disks
386 92f51573 Iustin Pop
387 92f51573 Iustin Pop
-- | Replace disks type.
388 92f51573 Iustin Pop
$(declareSADT "ReplaceDisksMode"
389 92f51573 Iustin Pop
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
390 92f51573 Iustin Pop
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
391 92f51573 Iustin Pop
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
392 92f51573 Iustin Pop
  , ("ReplaceAuto",         'C.replaceDiskAuto)
393 92f51573 Iustin Pop
  ])
394 92f51573 Iustin Pop
$(makeJSONInstance ''ReplaceDisksMode)
395 92f51573 Iustin Pop
396 92f51573 Iustin Pop
-- | Disk index type (embedding constraints on the index value via a
397 92f51573 Iustin Pop
-- smart constructor).
398 92f51573 Iustin Pop
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
399 139c0683 Iustin Pop
  deriving (Show, Eq, Ord)
400 92f51573 Iustin Pop
401 92f51573 Iustin Pop
-- | Smart constructor for 'DiskIndex'.
402 92f51573 Iustin Pop
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
403 92f51573 Iustin Pop
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
404 92f51573 Iustin Pop
              | otherwise = fail $ "Invalid value for disk index '" ++
405 92f51573 Iustin Pop
                            show i ++ "', required between 0 and " ++
406 92f51573 Iustin Pop
                            show C.maxDisks
407 92f51573 Iustin Pop
408 92f51573 Iustin Pop
instance JSON DiskIndex where
409 92f51573 Iustin Pop
  readJSON v = readJSON v >>= mkDiskIndex
410 92f51573 Iustin Pop
  showJSON = showJSON . unDiskIndex
411 92f51573 Iustin Pop
412 d6979f35 Iustin Pop
-- ** I* param types
413 d6979f35 Iustin Pop
414 d6979f35 Iustin Pop
-- | Type holding disk access modes.
415 d6979f35 Iustin Pop
$(declareSADT "DiskAccess"
416 d6979f35 Iustin Pop
  [ ("DiskReadOnly",  'C.diskRdonly)
417 d6979f35 Iustin Pop
  , ("DiskReadWrite", 'C.diskRdwr)
418 d6979f35 Iustin Pop
  ])
419 d6979f35 Iustin Pop
$(makeJSONInstance ''DiskAccess)
420 d6979f35 Iustin Pop
421 d6979f35 Iustin Pop
-- | NIC modification definition.
422 d6979f35 Iustin Pop
$(buildObject "INicParams" "inic"
423 d6979f35 Iustin Pop
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
424 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicIp   [t| String         |]
425 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
426 d6979f35 Iustin Pop
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
427 4e4433e8 Christos Stavrakakis
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
428 d6979f35 Iustin Pop
  ])
429 d6979f35 Iustin Pop
430 6d558717 Iustin Pop
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
431 d6979f35 Iustin Pop
$(buildObject "IDiskParams" "idisk"
432 6d558717 Iustin Pop
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
433 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
434 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
435 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
436 6d558717 Iustin Pop
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
437 4e4433e8 Christos Stavrakakis
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
438 d6979f35 Iustin Pop
  ])
439 d6979f35 Iustin Pop
440 c2d3219b Iustin Pop
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
441 c2d3219b Iustin Pop
-- strange, because the type in Python is something like Either
442 c2d3219b Iustin Pop
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
443 c2d3219b Iustin Pop
-- empty list in JSON, so we have to add a custom case for the empty
444 c2d3219b Iustin Pop
-- list.
445 c2d3219b Iustin Pop
data RecreateDisksInfo
446 c2d3219b Iustin Pop
  = RecreateDisksAll
447 c2d3219b Iustin Pop
  | RecreateDisksIndices (NonEmpty DiskIndex)
448 c2d3219b Iustin Pop
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
449 139c0683 Iustin Pop
    deriving (Eq, Show)
450 c2d3219b Iustin Pop
451 c2d3219b Iustin Pop
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
452 c2d3219b Iustin Pop
readRecreateDisks (JSArray []) = return RecreateDisksAll
453 c2d3219b Iustin Pop
readRecreateDisks v =
454 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result [DiskIndex] of
455 c2d3219b Iustin Pop
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
456 c2d3219b Iustin Pop
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
457 c2d3219b Iustin Pop
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
458 c2d3219b Iustin Pop
           _ -> fail $ "Can't parse disk information as either list of disk"
459 f56013fd Iustin Pop
                ++ " indices or list of disk parameters; value received:"
460 c2d3219b Iustin Pop
                ++ show (pp_value v)
461 c2d3219b Iustin Pop
462 c2d3219b Iustin Pop
instance JSON RecreateDisksInfo where
463 c2d3219b Iustin Pop
  readJSON = readRecreateDisks
464 c2d3219b Iustin Pop
  showJSON  RecreateDisksAll            = showJSON ()
465 c2d3219b Iustin Pop
  showJSON (RecreateDisksIndices idx)   = showJSON idx
466 c2d3219b Iustin Pop
  showJSON (RecreateDisksParams params) = showJSON params
467 c2d3219b Iustin Pop
468 c2d3219b Iustin Pop
-- | Simple type for old-style ddm changes.
469 c2d3219b Iustin Pop
data DdmOldChanges = DdmOldIndex (NonNegative Int)
470 c2d3219b Iustin Pop
                   | DdmOldMod DdmSimple
471 139c0683 Iustin Pop
                     deriving (Eq, Show)
472 c2d3219b Iustin Pop
473 c2d3219b Iustin Pop
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
474 c2d3219b Iustin Pop
readDdmOldChanges v =
475 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result (NonNegative Int) of
476 c2d3219b Iustin Pop
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
477 c2d3219b Iustin Pop
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
478 c2d3219b Iustin Pop
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
479 c2d3219b Iustin Pop
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
480 c2d3219b Iustin Pop
                ++ " either index or modification"
481 c2d3219b Iustin Pop
482 c2d3219b Iustin Pop
instance JSON DdmOldChanges where
483 c2d3219b Iustin Pop
  showJSON (DdmOldIndex i) = showJSON i
484 c2d3219b Iustin Pop
  showJSON (DdmOldMod m)   = showJSON m
485 c2d3219b Iustin Pop
  readJSON = readDdmOldChanges
486 c2d3219b Iustin Pop
487 c2d3219b Iustin Pop
-- | Instance disk or nic modifications.
488 c2d3219b Iustin Pop
data SetParamsMods a
489 c2d3219b Iustin Pop
  = SetParamsEmpty
490 c2d3219b Iustin Pop
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
491 c2d3219b Iustin Pop
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
492 139c0683 Iustin Pop
    deriving (Eq, Show)
493 c2d3219b Iustin Pop
494 c2d3219b Iustin Pop
-- | Custom deserialiser for 'SetParamsMods'.
495 c2d3219b Iustin Pop
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
496 c2d3219b Iustin Pop
readSetParams (JSArray []) = return SetParamsEmpty
497 c2d3219b Iustin Pop
readSetParams v =
498 c2d3219b Iustin Pop
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
499 c2d3219b Iustin Pop
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
500 c2d3219b Iustin Pop
    _ -> liftM SetParamsNew $ readJSON v
501 c2d3219b Iustin Pop
502 c2d3219b Iustin Pop
instance (JSON a) => JSON (SetParamsMods a) where
503 c2d3219b Iustin Pop
  showJSON SetParamsEmpty = showJSON ()
504 c2d3219b Iustin Pop
  showJSON (SetParamsDeprecated v) = showJSON v
505 c2d3219b Iustin Pop
  showJSON (SetParamsNew v) = showJSON v
506 c2d3219b Iustin Pop
  readJSON = readSetParams
507 c2d3219b Iustin Pop
508 398e9066 Iustin Pop
-- | Custom type for target_node parameter of OpBackupExport, which
509 398e9066 Iustin Pop
-- varies depending on mode. FIXME: this uses an UncheckedList since
510 398e9066 Iustin Pop
-- we don't care about individual rows (just like the Python code
511 398e9066 Iustin Pop
-- tests). But the proper type could be parsed if we wanted.
512 398e9066 Iustin Pop
data ExportTarget = ExportTargetLocal NonEmptyString
513 398e9066 Iustin Pop
                  | ExportTargetRemote UncheckedList
514 139c0683 Iustin Pop
                    deriving (Eq, Show)
515 398e9066 Iustin Pop
516 398e9066 Iustin Pop
-- | Custom reader for 'ExportTarget'.
517 398e9066 Iustin Pop
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
518 398e9066 Iustin Pop
readExportTarget (JSString s) = liftM ExportTargetLocal $
519 398e9066 Iustin Pop
                                mkNonEmpty (fromJSString s)
520 398e9066 Iustin Pop
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
521 398e9066 Iustin Pop
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
522 398e9066 Iustin Pop
                     show (pp_value v)
523 398e9066 Iustin Pop
524 398e9066 Iustin Pop
instance JSON ExportTarget where
525 398e9066 Iustin Pop
  showJSON (ExportTargetLocal s)  = showJSON s
526 398e9066 Iustin Pop
  showJSON (ExportTargetRemote l) = showJSON l
527 398e9066 Iustin Pop
  readJSON = readExportTarget
528 398e9066 Iustin Pop
529 92f51573 Iustin Pop
-- * Parameters
530 92f51573 Iustin Pop
531 d6979f35 Iustin Pop
-- | A required instance name (for single-instance LUs).
532 92f51573 Iustin Pop
pInstanceName :: Field
533 92f51573 Iustin Pop
pInstanceName = simpleField "instance_name" [t| String |]
534 92f51573 Iustin Pop
535 da4a52a3 Thomas Thrainer
-- | An instance UUID (for single-instance LUs).
536 da4a52a3 Thomas Thrainer
pInstanceUuid :: Field
537 da4a52a3 Thomas Thrainer
pInstanceUuid = optionalField $ simpleField "instance_uuid" [t| String |]
538 da4a52a3 Thomas Thrainer
539 d6979f35 Iustin Pop
-- | A list of instances.
540 d6979f35 Iustin Pop
pInstances :: Field
541 d6979f35 Iustin Pop
pInstances = defaultField [| [] |] $
542 d6979f35 Iustin Pop
             simpleField "instances" [t| [NonEmptyString] |]
543 d6979f35 Iustin Pop
544 d6979f35 Iustin Pop
-- | A generic name.
545 d6979f35 Iustin Pop
pName :: Field
546 d6979f35 Iustin Pop
pName = simpleField "name" [t| NonEmptyString |]
547 d6979f35 Iustin Pop
548 92f51573 Iustin Pop
-- | Tags list.
549 92f51573 Iustin Pop
pTagsList :: Field
550 92f51573 Iustin Pop
pTagsList = simpleField "tags" [t| [String] |]
551 92f51573 Iustin Pop
552 92f51573 Iustin Pop
-- | Tags object.
553 92f51573 Iustin Pop
pTagsObject :: Field
554 fa10983e Iustin Pop
pTagsObject =
555 fa10983e Iustin Pop
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
556 fa10983e Iustin Pop
  simpleField "kind" [t| TagObject |]
557 d6979f35 Iustin Pop
558 d6979f35 Iustin Pop
-- | Selected output fields.
559 d6979f35 Iustin Pop
pOutputFields :: Field
560 d6979f35 Iustin Pop
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
561 d6979f35 Iustin Pop
562 d6979f35 Iustin Pop
-- | How long to wait for instance to shut down.
563 d6979f35 Iustin Pop
pShutdownTimeout :: Field
564 c2d3219b Iustin Pop
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
565 d6979f35 Iustin Pop
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
566 d6979f35 Iustin Pop
567 c2d3219b Iustin Pop
-- | Another name for the shutdown timeout, because we like to be
568 c2d3219b Iustin Pop
-- inconsistent.
569 c2d3219b Iustin Pop
pShutdownTimeout' :: Field
570 c2d3219b Iustin Pop
pShutdownTimeout' =
571 c2d3219b Iustin Pop
  renameField "InstShutdownTimeout" .
572 c2d3219b Iustin Pop
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
573 c2d3219b Iustin Pop
  simpleField "timeout" [t| NonNegative Int |]
574 c2d3219b Iustin Pop
575 67fc4de7 Iustin Pop
-- | Whether to shutdown the instance in backup-export.
576 67fc4de7 Iustin Pop
pShutdownInstance :: Field
577 67fc4de7 Iustin Pop
pShutdownInstance = defaultTrue "shutdown"
578 67fc4de7 Iustin Pop
579 d6979f35 Iustin Pop
-- | Whether to force the operation.
580 d6979f35 Iustin Pop
pForce :: Field
581 d6979f35 Iustin Pop
pForce = defaultFalse "force"
582 d6979f35 Iustin Pop
583 d6979f35 Iustin Pop
-- | Whether to ignore offline nodes.
584 d6979f35 Iustin Pop
pIgnoreOfflineNodes :: Field
585 d6979f35 Iustin Pop
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
586 d6979f35 Iustin Pop
587 d6979f35 Iustin Pop
-- | A required node name (for single-node LUs).
588 d6979f35 Iustin Pop
pNodeName :: Field
589 d6979f35 Iustin Pop
pNodeName = simpleField "node_name" [t| NonEmptyString |]
590 d6979f35 Iustin Pop
591 1c3231aa Thomas Thrainer
-- | A node UUID (for single-node LUs).
592 1c3231aa Thomas Thrainer
pNodeUuid :: Field
593 1c3231aa Thomas Thrainer
pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
594 1c3231aa Thomas Thrainer
595 d6979f35 Iustin Pop
-- | List of nodes.
596 d6979f35 Iustin Pop
pNodeNames :: Field
597 d6979f35 Iustin Pop
pNodeNames =
598 d6979f35 Iustin Pop
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
599 d6979f35 Iustin Pop
600 1c3231aa Thomas Thrainer
-- | List of node UUIDs.
601 1c3231aa Thomas Thrainer
pNodeUuids :: Field
602 1c3231aa Thomas Thrainer
pNodeUuids =
603 1c3231aa Thomas Thrainer
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
604 1c3231aa Thomas Thrainer
605 d6979f35 Iustin Pop
-- | A required node group name (for single-group LUs).
606 d6979f35 Iustin Pop
pGroupName :: Field
607 d6979f35 Iustin Pop
pGroupName = simpleField "group_name" [t| NonEmptyString |]
608 d6979f35 Iustin Pop
609 d6979f35 Iustin Pop
-- | Migration type (live\/non-live).
610 d6979f35 Iustin Pop
pMigrationMode :: Field
611 d6979f35 Iustin Pop
pMigrationMode =
612 417ab39c Iustin Pop
  renameField "MigrationMode" .
613 d6979f35 Iustin Pop
  optionalField $
614 d6979f35 Iustin Pop
  simpleField "mode" [t| MigrationMode |]
615 d6979f35 Iustin Pop
616 d6979f35 Iustin Pop
-- | Obsolete \'live\' migration mode (boolean).
617 d6979f35 Iustin Pop
pMigrationLive :: Field
618 d6979f35 Iustin Pop
pMigrationLive =
619 417ab39c Iustin Pop
  renameField "OldLiveMode" . optionalField $ booleanField "live"
620 d6979f35 Iustin Pop
621 7d421386 Iustin Pop
-- | Migration cleanup parameter.
622 7d421386 Iustin Pop
pMigrationCleanup :: Field
623 7d421386 Iustin Pop
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
624 7d421386 Iustin Pop
625 d6979f35 Iustin Pop
-- | Whether to force an unknown OS variant.
626 d6979f35 Iustin Pop
pForceVariant :: Field
627 d6979f35 Iustin Pop
pForceVariant = defaultFalse "force_variant"
628 d6979f35 Iustin Pop
629 d6979f35 Iustin Pop
-- | Whether to wait for the disk to synchronize.
630 d6979f35 Iustin Pop
pWaitForSync :: Field
631 d6979f35 Iustin Pop
pWaitForSync = defaultTrue "wait_for_sync"
632 d6979f35 Iustin Pop
633 d6979f35 Iustin Pop
-- | Whether to wait for the disk to synchronize (defaults to false).
634 d6979f35 Iustin Pop
pWaitForSyncFalse :: Field
635 d6979f35 Iustin Pop
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
636 d6979f35 Iustin Pop
637 d6979f35 Iustin Pop
-- | Whether to ignore disk consistency
638 d6979f35 Iustin Pop
pIgnoreConsistency :: Field
639 d6979f35 Iustin Pop
pIgnoreConsistency = defaultFalse "ignore_consistency"
640 d6979f35 Iustin Pop
641 d6979f35 Iustin Pop
-- | Storage name.
642 d6979f35 Iustin Pop
pStorageName :: Field
643 d6979f35 Iustin Pop
pStorageName =
644 d6979f35 Iustin Pop
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
645 d6979f35 Iustin Pop
646 d6979f35 Iustin Pop
-- | Whether to use synchronization.
647 d6979f35 Iustin Pop
pUseLocking :: Field
648 d6979f35 Iustin Pop
pUseLocking = defaultFalse "use_locking"
649 d6979f35 Iustin Pop
650 1f1188c3 Michael Hanselmann
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
651 1f1188c3 Michael Hanselmann
-- locked by another opcode won't be considered for instance allocation (only
652 1f1188c3 Michael Hanselmann
-- when an iallocator is used).
653 1f1188c3 Michael Hanselmann
pOpportunisticLocking :: Field
654 1f1188c3 Michael Hanselmann
pOpportunisticLocking = defaultFalse "opportunistic_locking"
655 1f1188c3 Michael Hanselmann
656 d6979f35 Iustin Pop
-- | Whether to check name.
657 d6979f35 Iustin Pop
pNameCheck :: Field
658 d6979f35 Iustin Pop
pNameCheck = defaultTrue "name_check"
659 d6979f35 Iustin Pop
660 d6979f35 Iustin Pop
-- | Instance allocation policy.
661 d6979f35 Iustin Pop
pNodeGroupAllocPolicy :: Field
662 d6979f35 Iustin Pop
pNodeGroupAllocPolicy = optionalField $
663 d6979f35 Iustin Pop
                        simpleField "alloc_policy" [t| AllocPolicy |]
664 d6979f35 Iustin Pop
665 d6979f35 Iustin Pop
-- | Default node parameters for group.
666 d6979f35 Iustin Pop
pGroupNodeParams :: Field
667 d6979f35 Iustin Pop
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
668 d6979f35 Iustin Pop
669 d6979f35 Iustin Pop
-- | Resource(s) to query for.
670 d6979f35 Iustin Pop
pQueryWhat :: Field
671 d6979f35 Iustin Pop
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
672 d6979f35 Iustin Pop
673 d6979f35 Iustin Pop
-- | Whether to release locks as soon as possible.
674 d6979f35 Iustin Pop
pEarlyRelease :: Field
675 d6979f35 Iustin Pop
pEarlyRelease = defaultFalse "early_release"
676 d6979f35 Iustin Pop
677 6d558717 Iustin Pop
-- | Whether to ensure instance's IP address is inactive.
678 6d558717 Iustin Pop
pIpCheck :: Field
679 6d558717 Iustin Pop
pIpCheck = defaultTrue "ip_check"
680 6d558717 Iustin Pop
681 6d558717 Iustin Pop
-- | Check for conflicting IPs.
682 6d558717 Iustin Pop
pIpConflictsCheck :: Field
683 6d558717 Iustin Pop
pIpConflictsCheck = defaultTrue "conflicts_check"
684 d6979f35 Iustin Pop
685 d6979f35 Iustin Pop
-- | Do not remember instance state changes.
686 d6979f35 Iustin Pop
pNoRemember :: Field
687 d6979f35 Iustin Pop
pNoRemember = defaultFalse "no_remember"
688 d6979f35 Iustin Pop
689 d6979f35 Iustin Pop
-- | Target node for instance migration/failover.
690 d6979f35 Iustin Pop
pMigrationTargetNode :: Field
691 d6979f35 Iustin Pop
pMigrationTargetNode = optionalNEStringField "target_node"
692 d6979f35 Iustin Pop
693 1c3231aa Thomas Thrainer
-- | Target node UUID for instance migration/failover.
694 1c3231aa Thomas Thrainer
pMigrationTargetNodeUuid :: Field
695 1c3231aa Thomas Thrainer
pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
696 1c3231aa Thomas Thrainer
697 c2d3219b Iustin Pop
-- | Target node for instance move (required).
698 c2d3219b Iustin Pop
pMoveTargetNode :: Field
699 c2d3219b Iustin Pop
pMoveTargetNode =
700 c2d3219b Iustin Pop
  renameField "MoveTargetNode" $
701 c2d3219b Iustin Pop
  simpleField "target_node" [t| NonEmptyString |]
702 c2d3219b Iustin Pop
703 1c3231aa Thomas Thrainer
-- | Target node UUID for instance move.
704 1c3231aa Thomas Thrainer
pMoveTargetNodeUuid :: Field
705 1c3231aa Thomas Thrainer
pMoveTargetNodeUuid =
706 1c3231aa Thomas Thrainer
  renameField "MoveTargetNodeUuid" . optionalField $
707 1c3231aa Thomas Thrainer
  simpleField "target_node_uuid" [t| NonEmptyString |]
708 1c3231aa Thomas Thrainer
709 d6979f35 Iustin Pop
-- | Pause instance at startup.
710 d6979f35 Iustin Pop
pStartupPaused :: Field
711 d6979f35 Iustin Pop
pStartupPaused = defaultFalse "startup_paused"
712 d6979f35 Iustin Pop
713 d6979f35 Iustin Pop
-- | Verbose mode.
714 d6979f35 Iustin Pop
pVerbose :: Field
715 d6979f35 Iustin Pop
pVerbose = defaultFalse "verbose"
716 d6979f35 Iustin Pop
717 d6979f35 Iustin Pop
-- ** Parameters for cluster verification
718 d6979f35 Iustin Pop
719 d6979f35 Iustin Pop
-- | Whether to simulate errors (useful for debugging).
720 d6979f35 Iustin Pop
pDebugSimulateErrors :: Field
721 d6979f35 Iustin Pop
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
722 d6979f35 Iustin Pop
723 d6979f35 Iustin Pop
-- | Error codes.
724 d6979f35 Iustin Pop
pErrorCodes :: Field
725 d6979f35 Iustin Pop
pErrorCodes = defaultFalse "error_codes"
726 d6979f35 Iustin Pop
727 d6979f35 Iustin Pop
-- | Which checks to skip.
728 d6979f35 Iustin Pop
pSkipChecks :: Field
729 d6979f35 Iustin Pop
pSkipChecks = defaultField [| Set.empty |] $
730 d6979f35 Iustin Pop
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
731 d6979f35 Iustin Pop
732 d6979f35 Iustin Pop
-- | List of error codes that should be treated as warnings.
733 d6979f35 Iustin Pop
pIgnoreErrors :: Field
734 d6979f35 Iustin Pop
pIgnoreErrors = defaultField [| Set.empty |] $
735 d6979f35 Iustin Pop
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
736 d6979f35 Iustin Pop
737 d6979f35 Iustin Pop
-- | Optional group name.
738 d6979f35 Iustin Pop
pOptGroupName :: Field
739 417ab39c Iustin Pop
pOptGroupName = renameField "OptGroupName" .
740 d6979f35 Iustin Pop
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
741 d6979f35 Iustin Pop
742 d6979f35 Iustin Pop
-- | Disk templates' parameter defaults.
743 d6979f35 Iustin Pop
pDiskParams :: Field
744 d6979f35 Iustin Pop
pDiskParams = optionalField $
745 d6979f35 Iustin Pop
              simpleField "diskparams" [t| GenericContainer DiskTemplate
746 d6979f35 Iustin Pop
                                           UncheckedDict |]
747 d6979f35 Iustin Pop
748 d6979f35 Iustin Pop
-- * Parameters for node resource model
749 d6979f35 Iustin Pop
750 d6979f35 Iustin Pop
-- | Set hypervisor states.
751 d6979f35 Iustin Pop
pHvState :: Field
752 d6979f35 Iustin Pop
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
753 d6979f35 Iustin Pop
754 d6979f35 Iustin Pop
-- | Set disk states.
755 d6979f35 Iustin Pop
pDiskState :: Field
756 d6979f35 Iustin Pop
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
757 d6979f35 Iustin Pop
758 d6979f35 Iustin Pop
-- | Whether to ignore ipolicy violations.
759 d6979f35 Iustin Pop
pIgnoreIpolicy :: Field
760 d6979f35 Iustin Pop
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
761 d6979f35 Iustin Pop
762 d6979f35 Iustin Pop
-- | Allow runtime changes while migrating.
763 d6979f35 Iustin Pop
pAllowRuntimeChgs :: Field
764 d6979f35 Iustin Pop
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
765 d6979f35 Iustin Pop
766 d6979f35 Iustin Pop
-- | Utility type for OpClusterSetParams.
767 d6979f35 Iustin Pop
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
768 d6979f35 Iustin Pop
769 d6979f35 Iustin Pop
-- | Utility type of OsList.
770 d6979f35 Iustin Pop
type TestClusterOsList = [TestClusterOsListItem]
771 d6979f35 Iustin Pop
772 d6979f35 Iustin Pop
-- Utility type for NIC definitions.
773 d6979f35 Iustin Pop
--type TestNicDef = INicParams
774 6d558717 Iustin Pop
775 6d558717 Iustin Pop
-- | List of instance disks.
776 6d558717 Iustin Pop
pInstDisks :: Field
777 6d558717 Iustin Pop
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
778 6d558717 Iustin Pop
779 6d558717 Iustin Pop
-- | Instance disk template.
780 6d558717 Iustin Pop
pDiskTemplate :: Field
781 6d558717 Iustin Pop
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
782 6d558717 Iustin Pop
783 88127c47 Iustin Pop
-- | Instance disk template.
784 88127c47 Iustin Pop
pOptDiskTemplate :: Field
785 88127c47 Iustin Pop
pOptDiskTemplate =
786 88127c47 Iustin Pop
  optionalField .
787 88127c47 Iustin Pop
  renameField "OptDiskTemplate" $
788 88127c47 Iustin Pop
  simpleField "disk_template" [t| DiskTemplate |]
789 88127c47 Iustin Pop
790 6d558717 Iustin Pop
-- | File driver.
791 6d558717 Iustin Pop
pFileDriver :: Field
792 6d558717 Iustin Pop
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
793 6d558717 Iustin Pop
794 6d558717 Iustin Pop
-- | Directory for storing file-backed disks.
795 6d558717 Iustin Pop
pFileStorageDir :: Field
796 6d558717 Iustin Pop
pFileStorageDir = optionalNEStringField "file_storage_dir"
797 d6979f35 Iustin Pop
798 3039e2dc Helga Velroyen
-- | Global directory for storing file-backed disks.
799 3039e2dc Helga Velroyen
pGlobalFileStorageDir :: Field
800 3039e2dc Helga Velroyen
pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
801 3039e2dc Helga Velroyen
802 4e6cfd11 Helga Velroyen
-- | Global directory for storing shared-file-backed disks.
803 4e6cfd11 Helga Velroyen
pGlobalSharedFileStorageDir :: Field
804 4e6cfd11 Helga Velroyen
pGlobalSharedFileStorageDir = optionalNEStringField "shared_file_storage_dir"
805 4e6cfd11 Helga Velroyen
806 d6979f35 Iustin Pop
-- | Volume group name.
807 d6979f35 Iustin Pop
pVgName :: Field
808 d6979f35 Iustin Pop
pVgName = optionalStringField "vg_name"
809 d6979f35 Iustin Pop
810 d6979f35 Iustin Pop
-- | List of enabled hypervisors.
811 d6979f35 Iustin Pop
pEnabledHypervisors :: Field
812 d6979f35 Iustin Pop
pEnabledHypervisors =
813 d6979f35 Iustin Pop
  optionalField $
814 d6979f35 Iustin Pop
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
815 d6979f35 Iustin Pop
816 66af5ec5 Helga Velroyen
-- | List of enabled disk templates.
817 66af5ec5 Helga Velroyen
pEnabledDiskTemplates :: Field
818 66af5ec5 Helga Velroyen
pEnabledDiskTemplates =
819 66af5ec5 Helga Velroyen
  optionalField $
820 66af5ec5 Helga Velroyen
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
821 66af5ec5 Helga Velroyen
822 6d558717 Iustin Pop
-- | Selected hypervisor for an instance.
823 6d558717 Iustin Pop
pHypervisor :: Field
824 6d558717 Iustin Pop
pHypervisor =
825 6d558717 Iustin Pop
  optionalField $
826 6d558717 Iustin Pop
  simpleField "hypervisor" [t| Hypervisor |]
827 6d558717 Iustin Pop
828 d6979f35 Iustin Pop
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
829 d6979f35 Iustin Pop
pClusterHvParams :: Field
830 d6979f35 Iustin Pop
pClusterHvParams =
831 6d558717 Iustin Pop
  renameField "ClusterHvParams" .
832 d6979f35 Iustin Pop
  optionalField $
833 d6979f35 Iustin Pop
  simpleField "hvparams" [t| Container UncheckedDict |]
834 d6979f35 Iustin Pop
835 6d558717 Iustin Pop
-- | Instance hypervisor parameters.
836 6d558717 Iustin Pop
pInstHvParams :: Field
837 6d558717 Iustin Pop
pInstHvParams =
838 6d558717 Iustin Pop
  renameField "InstHvParams" .
839 6d558717 Iustin Pop
  defaultField [| toJSObject [] |] $
840 6d558717 Iustin Pop
  simpleField "hvparams" [t| UncheckedDict |]
841 6d558717 Iustin Pop
842 d6979f35 Iustin Pop
-- | Cluster-wide beparams.
843 d6979f35 Iustin Pop
pClusterBeParams :: Field
844 6d558717 Iustin Pop
pClusterBeParams =
845 6d558717 Iustin Pop
  renameField "ClusterBeParams" .
846 6d558717 Iustin Pop
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
847 6d558717 Iustin Pop
848 6d558717 Iustin Pop
-- | Instance beparams.
849 6d558717 Iustin Pop
pInstBeParams :: Field
850 6d558717 Iustin Pop
pInstBeParams =
851 6d558717 Iustin Pop
  renameField "InstBeParams" .
852 6d558717 Iustin Pop
  defaultField [| toJSObject [] |] $
853 6d558717 Iustin Pop
  simpleField "beparams" [t| UncheckedDict |]
854 6d558717 Iustin Pop
855 6d558717 Iustin Pop
-- | Reset instance parameters to default if equal.
856 6d558717 Iustin Pop
pResetDefaults :: Field
857 6d558717 Iustin Pop
pResetDefaults = defaultFalse "identify_defaults"
858 d6979f35 Iustin Pop
859 d6979f35 Iustin Pop
-- | Cluster-wide per-OS hypervisor parameter defaults.
860 d6979f35 Iustin Pop
pOsHvp :: Field
861 d6979f35 Iustin Pop
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
862 d6979f35 Iustin Pop
863 d6979f35 Iustin Pop
-- | Cluster-wide OS parameter defaults.
864 6d558717 Iustin Pop
pClusterOsParams :: Field
865 6d558717 Iustin Pop
pClusterOsParams =
866 c2d3219b Iustin Pop
  renameField "ClusterOsParams" .
867 d6979f35 Iustin Pop
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
868 d6979f35 Iustin Pop
869 6d558717 Iustin Pop
-- | Instance OS parameters.
870 6d558717 Iustin Pop
pInstOsParams :: Field
871 6d558717 Iustin Pop
pInstOsParams =
872 c2d3219b Iustin Pop
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
873 6d558717 Iustin Pop
  simpleField "osparams" [t| UncheckedDict |]
874 6d558717 Iustin Pop
875 c2d3219b Iustin Pop
-- | Temporary OS parameters (currently only in reinstall, might be
876 c2d3219b Iustin Pop
-- added to install as well).
877 c2d3219b Iustin Pop
pTempOsParams :: Field
878 c2d3219b Iustin Pop
pTempOsParams =
879 c2d3219b Iustin Pop
  renameField "TempOsParams" .
880 c2d3219b Iustin Pop
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
881 c2d3219b Iustin Pop
882 c2d3219b Iustin Pop
-- | Temporary hypervisor parameters, hypervisor-dependent.
883 c2d3219b Iustin Pop
pTempHvParams :: Field
884 c2d3219b Iustin Pop
pTempHvParams =
885 c2d3219b Iustin Pop
  renameField "TempHvParams" .
886 c2d3219b Iustin Pop
  defaultField [| toJSObject [] |] $
887 c2d3219b Iustin Pop
  simpleField "hvparams" [t| UncheckedDict |]
888 c2d3219b Iustin Pop
889 c2d3219b Iustin Pop
-- | Temporary backend parameters.
890 c2d3219b Iustin Pop
pTempBeParams :: Field
891 c2d3219b Iustin Pop
pTempBeParams =
892 c2d3219b Iustin Pop
  renameField "TempBeParams" .
893 c2d3219b Iustin Pop
  defaultField [| toJSObject [] |] $
894 c2d3219b Iustin Pop
  simpleField "beparams" [t| UncheckedDict |]
895 c2d3219b Iustin Pop
896 d6979f35 Iustin Pop
-- | Candidate pool size.
897 d6979f35 Iustin Pop
pCandidatePoolSize :: Field
898 d6979f35 Iustin Pop
pCandidatePoolSize =
899 d6979f35 Iustin Pop
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
900 d6979f35 Iustin Pop
901 d6979f35 Iustin Pop
-- | Set UID pool, must be list of lists describing UID ranges (two
902 d6979f35 Iustin Pop
-- items, start and end inclusive.
903 d6979f35 Iustin Pop
pUidPool :: Field
904 d6979f35 Iustin Pop
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
905 d6979f35 Iustin Pop
906 d6979f35 Iustin Pop
-- | Extend UID pool, must be list of lists describing UID ranges (two
907 d6979f35 Iustin Pop
-- items, start and end inclusive.
908 d6979f35 Iustin Pop
pAddUids :: Field
909 d6979f35 Iustin Pop
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
910 d6979f35 Iustin Pop
911 d6979f35 Iustin Pop
-- | Shrink UID pool, must be list of lists describing UID ranges (two
912 d6979f35 Iustin Pop
-- items, start and end inclusive) to be removed.
913 d6979f35 Iustin Pop
pRemoveUids :: Field
914 d6979f35 Iustin Pop
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
915 d6979f35 Iustin Pop
916 d6979f35 Iustin Pop
-- | Whether to automatically maintain node health.
917 d6979f35 Iustin Pop
pMaintainNodeHealth :: Field
918 d6979f35 Iustin Pop
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
919 d6979f35 Iustin Pop
920 75f2ff7d Michele Tartara
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
921 75f2ff7d Michele Tartara
pModifyEtcHosts :: Field
922 75f2ff7d Michele Tartara
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
923 75f2ff7d Michele Tartara
924 d6979f35 Iustin Pop
-- | Whether to wipe disks before allocating them to instances.
925 d6979f35 Iustin Pop
pPreallocWipeDisks :: Field
926 d6979f35 Iustin Pop
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
927 d6979f35 Iustin Pop
928 d6979f35 Iustin Pop
-- | Cluster-wide NIC parameter defaults.
929 d6979f35 Iustin Pop
pNicParams :: Field
930 d6979f35 Iustin Pop
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
931 d6979f35 Iustin Pop
932 6d558717 Iustin Pop
-- | Instance NIC definitions.
933 6d558717 Iustin Pop
pInstNics :: Field
934 6d558717 Iustin Pop
pInstNics = simpleField "nics" [t| [INicParams] |]
935 6d558717 Iustin Pop
936 d6979f35 Iustin Pop
-- | Cluster-wide node parameter defaults.
937 d6979f35 Iustin Pop
pNdParams :: Field
938 d6979f35 Iustin Pop
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
939 d6979f35 Iustin Pop
940 398e9066 Iustin Pop
-- | Cluster-wide ipolicy specs.
941 d6979f35 Iustin Pop
pIpolicy :: Field
942 d6979f35 Iustin Pop
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
943 d6979f35 Iustin Pop
944 d6979f35 Iustin Pop
-- | DRBD helper program.
945 d6979f35 Iustin Pop
pDrbdHelper :: Field
946 d6979f35 Iustin Pop
pDrbdHelper = optionalStringField "drbd_helper"
947 d6979f35 Iustin Pop
948 d6979f35 Iustin Pop
-- | Default iallocator for cluster.
949 d6979f35 Iustin Pop
pDefaultIAllocator :: Field
950 d6979f35 Iustin Pop
pDefaultIAllocator = optionalStringField "default_iallocator"
951 d6979f35 Iustin Pop
952 d6979f35 Iustin Pop
-- | Master network device.
953 d6979f35 Iustin Pop
pMasterNetdev :: Field
954 d6979f35 Iustin Pop
pMasterNetdev = optionalStringField "master_netdev"
955 d6979f35 Iustin Pop
956 d6979f35 Iustin Pop
-- | Netmask of the master IP.
957 d6979f35 Iustin Pop
pMasterNetmask :: Field
958 67fc4de7 Iustin Pop
pMasterNetmask =
959 67fc4de7 Iustin Pop
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
960 d6979f35 Iustin Pop
961 d6979f35 Iustin Pop
-- | List of reserved LVs.
962 d6979f35 Iustin Pop
pReservedLvs :: Field
963 d6979f35 Iustin Pop
pReservedLvs =
964 d6979f35 Iustin Pop
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
965 d6979f35 Iustin Pop
966 d6979f35 Iustin Pop
-- | Modify list of hidden operating systems: each modification must
967 d6979f35 Iustin Pop
-- have two items, the operation and the OS name; the operation can be
968 d6979f35 Iustin Pop
-- add or remove.
969 d6979f35 Iustin Pop
pHiddenOs :: Field
970 d6979f35 Iustin Pop
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
971 d6979f35 Iustin Pop
972 d6979f35 Iustin Pop
-- | Modify list of blacklisted operating systems: each modification
973 d6979f35 Iustin Pop
-- must have two items, the operation and the OS name; the operation
974 d6979f35 Iustin Pop
-- can be add or remove.
975 d6979f35 Iustin Pop
pBlacklistedOs :: Field
976 d6979f35 Iustin Pop
pBlacklistedOs =
977 d6979f35 Iustin Pop
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
978 d6979f35 Iustin Pop
979 d6979f35 Iustin Pop
-- | Whether to use an external master IP address setup script.
980 d6979f35 Iustin Pop
pUseExternalMipScript :: Field
981 d6979f35 Iustin Pop
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
982 d6979f35 Iustin Pop
983 d6979f35 Iustin Pop
-- | Requested fields.
984 d6979f35 Iustin Pop
pQueryFields :: Field
985 d6979f35 Iustin Pop
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
986 d6979f35 Iustin Pop
987 d6979f35 Iustin Pop
-- | Query filter.
988 d6979f35 Iustin Pop
pQueryFilter :: Field
989 d6979f35 Iustin Pop
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
990 d6979f35 Iustin Pop
991 d6979f35 Iustin Pop
-- | OOB command to run.
992 d6979f35 Iustin Pop
pOobCommand :: Field
993 d6979f35 Iustin Pop
pOobCommand = simpleField "command" [t| OobCommand |]
994 d6979f35 Iustin Pop
995 d6979f35 Iustin Pop
-- | Timeout before the OOB helper will be terminated.
996 d6979f35 Iustin Pop
pOobTimeout :: Field
997 d6979f35 Iustin Pop
pOobTimeout =
998 d6979f35 Iustin Pop
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
999 d6979f35 Iustin Pop
1000 d6979f35 Iustin Pop
-- | Ignores the node offline status for power off.
1001 d6979f35 Iustin Pop
pIgnoreStatus :: Field
1002 d6979f35 Iustin Pop
pIgnoreStatus = defaultFalse "ignore_status"
1003 d6979f35 Iustin Pop
1004 d6979f35 Iustin Pop
-- | Time in seconds to wait between powering on nodes.
1005 d6979f35 Iustin Pop
pPowerDelay :: Field
1006 d6979f35 Iustin Pop
pPowerDelay =
1007 d6979f35 Iustin Pop
  -- FIXME: we can't use the proper type "NonNegative Double", since
1008 d6979f35 Iustin Pop
  -- the default constant is a plain Double, not a non-negative one.
1009 d6979f35 Iustin Pop
  defaultField [| C.oobPowerDelay |] $
1010 d6979f35 Iustin Pop
  simpleField "power_delay" [t| Double |]
1011 d6979f35 Iustin Pop
1012 d6979f35 Iustin Pop
-- | Primary IP address.
1013 d6979f35 Iustin Pop
pPrimaryIp :: Field
1014 d6979f35 Iustin Pop
pPrimaryIp = optionalStringField "primary_ip"
1015 d6979f35 Iustin Pop
1016 d6979f35 Iustin Pop
-- | Secondary IP address.
1017 d6979f35 Iustin Pop
pSecondaryIp :: Field
1018 d6979f35 Iustin Pop
pSecondaryIp = optionalNEStringField "secondary_ip"
1019 d6979f35 Iustin Pop
1020 d6979f35 Iustin Pop
-- | Whether node is re-added to cluster.
1021 d6979f35 Iustin Pop
pReadd :: Field
1022 d6979f35 Iustin Pop
pReadd = defaultFalse "readd"
1023 d6979f35 Iustin Pop
1024 d6979f35 Iustin Pop
-- | Initial node group.
1025 d6979f35 Iustin Pop
pNodeGroup :: Field
1026 d6979f35 Iustin Pop
pNodeGroup = optionalNEStringField "group"
1027 d6979f35 Iustin Pop
1028 d6979f35 Iustin Pop
-- | Whether node can become master or master candidate.
1029 d6979f35 Iustin Pop
pMasterCapable :: Field
1030 d6979f35 Iustin Pop
pMasterCapable = optionalField $ booleanField "master_capable"
1031 d6979f35 Iustin Pop
1032 d6979f35 Iustin Pop
-- | Whether node can host instances.
1033 d6979f35 Iustin Pop
pVmCapable :: Field
1034 d6979f35 Iustin Pop
pVmCapable = optionalField $ booleanField "vm_capable"
1035 d6979f35 Iustin Pop
1036 d6979f35 Iustin Pop
-- | List of names.
1037 d6979f35 Iustin Pop
pNames :: Field
1038 d6979f35 Iustin Pop
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1039 d6979f35 Iustin Pop
1040 d6979f35 Iustin Pop
-- | List of node names.
1041 d6979f35 Iustin Pop
pNodes :: Field
1042 d6979f35 Iustin Pop
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1043 d6979f35 Iustin Pop
1044 398e9066 Iustin Pop
-- | Required list of node names.
1045 398e9066 Iustin Pop
pRequiredNodes :: Field
1046 398e9066 Iustin Pop
pRequiredNodes =
1047 398e9066 Iustin Pop
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1048 398e9066 Iustin Pop
1049 1c3231aa Thomas Thrainer
-- | Required list of node names.
1050 1c3231aa Thomas Thrainer
pRequiredNodeUuids :: Field
1051 1c3231aa Thomas Thrainer
pRequiredNodeUuids =
1052 1c3231aa Thomas Thrainer
  renameField "ReqNodeUuids " . optionalField $
1053 1c3231aa Thomas Thrainer
    simpleField "node_uuids" [t| [NonEmptyString] |]
1054 1c3231aa Thomas Thrainer
1055 d6979f35 Iustin Pop
-- | Storage type.
1056 d6979f35 Iustin Pop
pStorageType :: Field
1057 d6979f35 Iustin Pop
pStorageType = simpleField "storage_type" [t| StorageType |]
1058 d6979f35 Iustin Pop
1059 d6979f35 Iustin Pop
-- | Storage changes (unchecked).
1060 d6979f35 Iustin Pop
pStorageChanges :: Field
1061 d6979f35 Iustin Pop
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1062 d6979f35 Iustin Pop
1063 d6979f35 Iustin Pop
-- | Whether the node should become a master candidate.
1064 d6979f35 Iustin Pop
pMasterCandidate :: Field
1065 d6979f35 Iustin Pop
pMasterCandidate = optionalField $ booleanField "master_candidate"
1066 d6979f35 Iustin Pop
1067 d6979f35 Iustin Pop
-- | Whether the node should be marked as offline.
1068 d6979f35 Iustin Pop
pOffline :: Field
1069 d6979f35 Iustin Pop
pOffline = optionalField $ booleanField "offline"
1070 d6979f35 Iustin Pop
1071 d6979f35 Iustin Pop
-- | Whether the node should be marked as drained.
1072 d6979f35 Iustin Pop
pDrained ::Field
1073 d6979f35 Iustin Pop
pDrained = optionalField $ booleanField "drained"
1074 d6979f35 Iustin Pop
1075 d6979f35 Iustin Pop
-- | Whether node(s) should be promoted to master candidate if necessary.
1076 d6979f35 Iustin Pop
pAutoPromote :: Field
1077 d6979f35 Iustin Pop
pAutoPromote = defaultFalse "auto_promote"
1078 d6979f35 Iustin Pop
1079 d6979f35 Iustin Pop
-- | Whether the node should be marked as powered
1080 d6979f35 Iustin Pop
pPowered :: Field
1081 d6979f35 Iustin Pop
pPowered = optionalField $ booleanField "powered"
1082 d6979f35 Iustin Pop
1083 d6979f35 Iustin Pop
-- | Iallocator for deciding the target node for shared-storage
1084 d6979f35 Iustin Pop
-- instances during migrate and failover.
1085 d6979f35 Iustin Pop
pIallocator :: Field
1086 d6979f35 Iustin Pop
pIallocator = optionalNEStringField "iallocator"
1087 d6979f35 Iustin Pop
1088 d6979f35 Iustin Pop
-- | New secondary node.
1089 d6979f35 Iustin Pop
pRemoteNode :: Field
1090 d6979f35 Iustin Pop
pRemoteNode = optionalNEStringField "remote_node"
1091 d6979f35 Iustin Pop
1092 1c3231aa Thomas Thrainer
-- | New secondary node UUID.
1093 1c3231aa Thomas Thrainer
pRemoteNodeUuid :: Field
1094 1c3231aa Thomas Thrainer
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1095 1c3231aa Thomas Thrainer
1096 d6979f35 Iustin Pop
-- | Node evacuation mode.
1097 d6979f35 Iustin Pop
pEvacMode :: Field
1098 d6979f35 Iustin Pop
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1099 6d558717 Iustin Pop
1100 6d558717 Iustin Pop
-- | Instance creation mode.
1101 6d558717 Iustin Pop
pInstCreateMode :: Field
1102 6d558717 Iustin Pop
pInstCreateMode =
1103 6d558717 Iustin Pop
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1104 6d558717 Iustin Pop
1105 6d558717 Iustin Pop
-- | Do not install the OS (will disable automatic start).
1106 6d558717 Iustin Pop
pNoInstall :: Field
1107 6d558717 Iustin Pop
pNoInstall = optionalField $ booleanField "no_install"
1108 6d558717 Iustin Pop
1109 6d558717 Iustin Pop
-- | OS type for instance installation.
1110 6d558717 Iustin Pop
pInstOs :: Field
1111 6d558717 Iustin Pop
pInstOs = optionalNEStringField "os_type"
1112 6d558717 Iustin Pop
1113 6d558717 Iustin Pop
-- | Primary node for an instance.
1114 6d558717 Iustin Pop
pPrimaryNode :: Field
1115 6d558717 Iustin Pop
pPrimaryNode = optionalNEStringField "pnode"
1116 6d558717 Iustin Pop
1117 1c3231aa Thomas Thrainer
-- | Primary node UUID for an instance.
1118 1c3231aa Thomas Thrainer
pPrimaryNodeUuid :: Field
1119 1c3231aa Thomas Thrainer
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1120 1c3231aa Thomas Thrainer
1121 6d558717 Iustin Pop
-- | Secondary node for an instance.
1122 6d558717 Iustin Pop
pSecondaryNode :: Field
1123 6d558717 Iustin Pop
pSecondaryNode = optionalNEStringField "snode"
1124 6d558717 Iustin Pop
1125 1c3231aa Thomas Thrainer
-- | Secondary node UUID for an instance.
1126 1c3231aa Thomas Thrainer
pSecondaryNodeUuid :: Field
1127 1c3231aa Thomas Thrainer
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1128 1c3231aa Thomas Thrainer
1129 6d558717 Iustin Pop
-- | Signed handshake from source (remote import only).
1130 6d558717 Iustin Pop
pSourceHandshake :: Field
1131 6d558717 Iustin Pop
pSourceHandshake =
1132 6d558717 Iustin Pop
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1133 6d558717 Iustin Pop
1134 6d558717 Iustin Pop
-- | Source instance name (remote import only).
1135 6d558717 Iustin Pop
pSourceInstance :: Field
1136 6d558717 Iustin Pop
pSourceInstance = optionalNEStringField "source_instance_name"
1137 6d558717 Iustin Pop
1138 6d558717 Iustin Pop
-- | How long source instance was given to shut down (remote import only).
1139 6d558717 Iustin Pop
-- FIXME: non-negative int, whereas the constant is a plain int.
1140 6d558717 Iustin Pop
pSourceShutdownTimeout :: Field
1141 6d558717 Iustin Pop
pSourceShutdownTimeout =
1142 6d558717 Iustin Pop
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1143 6d558717 Iustin Pop
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1144 6d558717 Iustin Pop
1145 6d558717 Iustin Pop
-- | Source X509 CA in PEM format (remote import only).
1146 6d558717 Iustin Pop
pSourceX509Ca :: Field
1147 6d558717 Iustin Pop
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1148 6d558717 Iustin Pop
1149 6d558717 Iustin Pop
-- | Source node for import.
1150 6d558717 Iustin Pop
pSrcNode :: Field
1151 6d558717 Iustin Pop
pSrcNode = optionalNEStringField "src_node"
1152 6d558717 Iustin Pop
1153 1c3231aa Thomas Thrainer
-- | Source node for import.
1154 1c3231aa Thomas Thrainer
pSrcNodeUuid :: Field
1155 1c3231aa Thomas Thrainer
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1156 1c3231aa Thomas Thrainer
1157 6d558717 Iustin Pop
-- | Source directory for import.
1158 6d558717 Iustin Pop
pSrcPath :: Field
1159 6d558717 Iustin Pop
pSrcPath = optionalNEStringField "src_path"
1160 6d558717 Iustin Pop
1161 6d558717 Iustin Pop
-- | Whether to start instance after creation.
1162 6d558717 Iustin Pop
pStartInstance :: Field
1163 6d558717 Iustin Pop
pStartInstance = defaultTrue "start"
1164 6d558717 Iustin Pop
1165 6d558717 Iustin Pop
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1166 6d558717 Iustin Pop
-- migrates to NonEmpty String.
1167 6d558717 Iustin Pop
pInstTags :: Field
1168 6d558717 Iustin Pop
pInstTags =
1169 6d558717 Iustin Pop
  renameField "InstTags" .
1170 6d558717 Iustin Pop
  defaultField [| [] |] $
1171 6d558717 Iustin Pop
  simpleField "tags" [t| [NonEmptyString] |]
1172 c2d3219b Iustin Pop
1173 c2d3219b Iustin Pop
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1174 c2d3219b Iustin Pop
pMultiAllocInstances :: Field
1175 c2d3219b Iustin Pop
pMultiAllocInstances =
1176 c2d3219b Iustin Pop
  renameField "InstMultiAlloc" .
1177 c2d3219b Iustin Pop
  defaultField [| [] |] $
1178 c2d3219b Iustin Pop
  simpleField "instances"[t| UncheckedList |]
1179 c2d3219b Iustin Pop
1180 c2d3219b Iustin Pop
-- | Ignore failures parameter.
1181 c2d3219b Iustin Pop
pIgnoreFailures :: Field
1182 c2d3219b Iustin Pop
pIgnoreFailures = defaultFalse "ignore_failures"
1183 c2d3219b Iustin Pop
1184 c2d3219b Iustin Pop
-- | New instance or cluster name.
1185 c2d3219b Iustin Pop
pNewName :: Field
1186 c2d3219b Iustin Pop
pNewName = simpleField "new_name" [t| NonEmptyString |]
1187 c2d3219b Iustin Pop
1188 c2d3219b Iustin Pop
-- | Whether to start the instance even if secondary disks are failing.
1189 c2d3219b Iustin Pop
pIgnoreSecondaries :: Field
1190 c2d3219b Iustin Pop
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1191 c2d3219b Iustin Pop
1192 c2d3219b Iustin Pop
-- | How to reboot the instance.
1193 c2d3219b Iustin Pop
pRebootType :: Field
1194 c2d3219b Iustin Pop
pRebootType = simpleField "reboot_type" [t| RebootType |]
1195 c2d3219b Iustin Pop
1196 c2d3219b Iustin Pop
-- | Whether to ignore recorded disk size.
1197 c2d3219b Iustin Pop
pIgnoreDiskSize :: Field
1198 c2d3219b Iustin Pop
pIgnoreDiskSize = defaultFalse "ignore_size"
1199 c2d3219b Iustin Pop
1200 c2d3219b Iustin Pop
-- | Disk list for recreate disks.
1201 c2d3219b Iustin Pop
pRecreateDisksInfo :: Field
1202 c2d3219b Iustin Pop
pRecreateDisksInfo =
1203 c2d3219b Iustin Pop
  renameField "RecreateDisksInfo" .
1204 c2d3219b Iustin Pop
  defaultField [| RecreateDisksAll |] $
1205 c2d3219b Iustin Pop
  simpleField "disks" [t| RecreateDisksInfo |]
1206 c2d3219b Iustin Pop
1207 c2d3219b Iustin Pop
-- | Whether to only return configuration data without querying nodes.
1208 c2d3219b Iustin Pop
pStatic :: Field
1209 c2d3219b Iustin Pop
pStatic = defaultFalse "static"
1210 c2d3219b Iustin Pop
1211 c2d3219b Iustin Pop
-- | InstanceSetParams NIC changes.
1212 c2d3219b Iustin Pop
pInstParamsNicChanges :: Field
1213 c2d3219b Iustin Pop
pInstParamsNicChanges =
1214 c2d3219b Iustin Pop
  renameField "InstNicChanges" .
1215 c2d3219b Iustin Pop
  defaultField [| SetParamsEmpty |] $
1216 c2d3219b Iustin Pop
  simpleField "nics" [t| SetParamsMods INicParams |]
1217 c2d3219b Iustin Pop
1218 c2d3219b Iustin Pop
-- | InstanceSetParams Disk changes.
1219 c2d3219b Iustin Pop
pInstParamsDiskChanges :: Field
1220 c2d3219b Iustin Pop
pInstParamsDiskChanges =
1221 c2d3219b Iustin Pop
  renameField "InstDiskChanges" .
1222 c2d3219b Iustin Pop
  defaultField [| SetParamsEmpty |] $
1223 c2d3219b Iustin Pop
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1224 c2d3219b Iustin Pop
1225 c2d3219b Iustin Pop
-- | New runtime memory.
1226 c2d3219b Iustin Pop
pRuntimeMem :: Field
1227 c2d3219b Iustin Pop
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1228 c2d3219b Iustin Pop
1229 c2d3219b Iustin Pop
-- | Change the instance's OS without reinstalling the instance
1230 c2d3219b Iustin Pop
pOsNameChange :: Field
1231 c2d3219b Iustin Pop
pOsNameChange = optionalNEStringField "os_name"
1232 c2d3219b Iustin Pop
1233 c2d3219b Iustin Pop
-- | Disk index for e.g. grow disk.
1234 c2d3219b Iustin Pop
pDiskIndex :: Field
1235 c2d3219b Iustin Pop
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1236 c2d3219b Iustin Pop
1237 c2d3219b Iustin Pop
-- | Disk amount to add or grow to.
1238 c2d3219b Iustin Pop
pDiskChgAmount :: Field
1239 c2d3219b Iustin Pop
pDiskChgAmount =
1240 c2d3219b Iustin Pop
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1241 c2d3219b Iustin Pop
1242 c2d3219b Iustin Pop
-- | Whether the amount parameter is an absolute target or a relative one.
1243 c2d3219b Iustin Pop
pDiskChgAbsolute :: Field
1244 c2d3219b Iustin Pop
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1245 c2d3219b Iustin Pop
1246 c2d3219b Iustin Pop
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1247 c2d3219b Iustin Pop
pTargetGroups :: Field
1248 c2d3219b Iustin Pop
pTargetGroups =
1249 c2d3219b Iustin Pop
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1250 398e9066 Iustin Pop
1251 398e9066 Iustin Pop
-- | Export mode field.
1252 398e9066 Iustin Pop
pExportMode :: Field
1253 398e9066 Iustin Pop
pExportMode =
1254 398e9066 Iustin Pop
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1255 398e9066 Iustin Pop
1256 398e9066 Iustin Pop
-- | Export target_node field, depends on mode.
1257 398e9066 Iustin Pop
pExportTargetNode :: Field
1258 398e9066 Iustin Pop
pExportTargetNode =
1259 398e9066 Iustin Pop
  renameField "ExportTarget" $
1260 398e9066 Iustin Pop
  simpleField "target_node" [t| ExportTarget |]
1261 398e9066 Iustin Pop
1262 1c3231aa Thomas Thrainer
-- | Export target node UUID field.
1263 1c3231aa Thomas Thrainer
pExportTargetNodeUuid :: Field
1264 1c3231aa Thomas Thrainer
pExportTargetNodeUuid =
1265 1c3231aa Thomas Thrainer
  renameField "ExportTargetNodeUuid" . optionalField $
1266 1c3231aa Thomas Thrainer
  simpleField "target_node_uuid" [t| NonEmptyString |]
1267 1c3231aa Thomas Thrainer
1268 398e9066 Iustin Pop
-- | Whether to remove instance after export.
1269 398e9066 Iustin Pop
pRemoveInstance :: Field
1270 398e9066 Iustin Pop
pRemoveInstance = defaultFalse "remove_instance"
1271 398e9066 Iustin Pop
1272 398e9066 Iustin Pop
-- | Whether to ignore failures while removing instances.
1273 398e9066 Iustin Pop
pIgnoreRemoveFailures :: Field
1274 398e9066 Iustin Pop
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1275 398e9066 Iustin Pop
1276 398e9066 Iustin Pop
-- | Name of X509 key (remote export only).
1277 398e9066 Iustin Pop
pX509KeyName :: Field
1278 398e9066 Iustin Pop
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1279 398e9066 Iustin Pop
1280 398e9066 Iustin Pop
-- | Destination X509 CA (remote export only).
1281 398e9066 Iustin Pop
pX509DestCA :: Field
1282 398e9066 Iustin Pop
pX509DestCA = optionalNEStringField "destination_x509_ca"
1283 a451dae2 Iustin Pop
1284 a451dae2 Iustin Pop
-- | Search pattern (regular expression). FIXME: this should be
1285 a451dae2 Iustin Pop
-- compiled at load time?
1286 a451dae2 Iustin Pop
pTagSearchPattern :: Field
1287 a451dae2 Iustin Pop
pTagSearchPattern =
1288 a451dae2 Iustin Pop
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1289 a451dae2 Iustin Pop
1290 1cd563e2 Iustin Pop
-- | Restricted command name.
1291 1cd563e2 Iustin Pop
pRestrictedCommand :: Field
1292 1cd563e2 Iustin Pop
pRestrictedCommand =
1293 1cd563e2 Iustin Pop
  renameField "RestrictedCommand" $
1294 1cd563e2 Iustin Pop
  simpleField "command" [t| NonEmptyString |]
1295 1cd563e2 Iustin Pop
1296 7d421386 Iustin Pop
-- | Replace disks mode.
1297 7d421386 Iustin Pop
pReplaceDisksMode :: Field
1298 7d421386 Iustin Pop
pReplaceDisksMode =
1299 7d421386 Iustin Pop
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1300 7d421386 Iustin Pop
1301 7d421386 Iustin Pop
-- | List of disk indices.
1302 7d421386 Iustin Pop
pReplaceDisksList :: Field
1303 7d421386 Iustin Pop
pReplaceDisksList =
1304 7d421386 Iustin Pop
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1305 7d421386 Iustin Pop
1306 7d421386 Iustin Pop
-- | Whether do allow failover in migrations.
1307 7d421386 Iustin Pop
pAllowFailover :: Field
1308 7d421386 Iustin Pop
pAllowFailover = defaultFalse "allow_failover"
1309 7d421386 Iustin Pop
1310 a3f02317 Iustin Pop
-- * Test opcode parameters
1311 a3f02317 Iustin Pop
1312 7d421386 Iustin Pop
-- | Duration parameter for 'OpTestDelay'.
1313 7d421386 Iustin Pop
pDelayDuration :: Field
1314 7d421386 Iustin Pop
pDelayDuration =
1315 60f20a41 Iustin Pop
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1316 7d421386 Iustin Pop
1317 7d421386 Iustin Pop
-- | on_master field for 'OpTestDelay'.
1318 7d421386 Iustin Pop
pDelayOnMaster :: Field
1319 7d421386 Iustin Pop
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1320 7d421386 Iustin Pop
1321 7d421386 Iustin Pop
-- | on_nodes field for 'OpTestDelay'.
1322 7d421386 Iustin Pop
pDelayOnNodes :: Field
1323 7d421386 Iustin Pop
pDelayOnNodes =
1324 7d421386 Iustin Pop
  renameField "DelayOnNodes" .
1325 7d421386 Iustin Pop
  defaultField [| [] |] $
1326 7d421386 Iustin Pop
  simpleField "on_nodes" [t| [NonEmptyString] |]
1327 7d421386 Iustin Pop
1328 1c3231aa Thomas Thrainer
-- | on_node_uuids field for 'OpTestDelay'.
1329 1c3231aa Thomas Thrainer
pDelayOnNodeUuids :: Field
1330 1c3231aa Thomas Thrainer
pDelayOnNodeUuids =
1331 1c3231aa Thomas Thrainer
  renameField "DelayOnNodeUuids" . optionalField $
1332 1c3231aa Thomas Thrainer
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1333 1c3231aa Thomas Thrainer
1334 a451dae2 Iustin Pop
-- | Repeat parameter for OpTestDelay.
1335 a451dae2 Iustin Pop
pDelayRepeat :: Field
1336 a451dae2 Iustin Pop
pDelayRepeat =
1337 a451dae2 Iustin Pop
  renameField "DelayRepeat" .
1338 a451dae2 Iustin Pop
  defaultField [| forceNonNeg (0::Int) |] $
1339 a451dae2 Iustin Pop
  simpleField "repeat" [t| NonNegative Int |]
1340 a3f02317 Iustin Pop
1341 a3f02317 Iustin Pop
-- | IAllocator test direction.
1342 a3f02317 Iustin Pop
pIAllocatorDirection :: Field
1343 a3f02317 Iustin Pop
pIAllocatorDirection =
1344 a3f02317 Iustin Pop
  renameField "IAllocatorDirection" $
1345 a3f02317 Iustin Pop
  simpleField "direction" [t| IAllocatorTestDir |]
1346 a3f02317 Iustin Pop
1347 a3f02317 Iustin Pop
-- | IAllocator test mode.
1348 a3f02317 Iustin Pop
pIAllocatorMode :: Field
1349 a3f02317 Iustin Pop
pIAllocatorMode =
1350 a3f02317 Iustin Pop
  renameField "IAllocatorMode" $
1351 a3f02317 Iustin Pop
  simpleField "mode" [t| IAllocatorMode |]
1352 a3f02317 Iustin Pop
1353 a3f02317 Iustin Pop
-- | IAllocator target name (new instance, node to evac, etc.).
1354 a3f02317 Iustin Pop
pIAllocatorReqName :: Field
1355 a3f02317 Iustin Pop
pIAllocatorReqName =
1356 a3f02317 Iustin Pop
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1357 a3f02317 Iustin Pop
1358 a3f02317 Iustin Pop
-- | Custom OpTestIAllocator nics.
1359 a3f02317 Iustin Pop
pIAllocatorNics :: Field
1360 a3f02317 Iustin Pop
pIAllocatorNics =
1361 a3f02317 Iustin Pop
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1362 a3f02317 Iustin Pop
1363 a3f02317 Iustin Pop
-- | Custom OpTestAllocator disks.
1364 a3f02317 Iustin Pop
pIAllocatorDisks :: Field
1365 a3f02317 Iustin Pop
pIAllocatorDisks =
1366 a3f02317 Iustin Pop
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1367 a3f02317 Iustin Pop
1368 a3f02317 Iustin Pop
-- | IAllocator memory field.
1369 a3f02317 Iustin Pop
pIAllocatorMemory :: Field
1370 a3f02317 Iustin Pop
pIAllocatorMemory =
1371 a3f02317 Iustin Pop
  renameField "IAllocatorMem" .
1372 a3f02317 Iustin Pop
  optionalField $
1373 a3f02317 Iustin Pop
  simpleField "memory" [t| NonNegative Int |]
1374 a3f02317 Iustin Pop
1375 a3f02317 Iustin Pop
-- | IAllocator vcpus field.
1376 a3f02317 Iustin Pop
pIAllocatorVCpus :: Field
1377 a3f02317 Iustin Pop
pIAllocatorVCpus =
1378 a3f02317 Iustin Pop
  renameField "IAllocatorVCpus" .
1379 a3f02317 Iustin Pop
  optionalField $
1380 a3f02317 Iustin Pop
  simpleField "vcpus" [t| NonNegative Int |]
1381 a3f02317 Iustin Pop
1382 a3f02317 Iustin Pop
-- | IAllocator os field.
1383 a3f02317 Iustin Pop
pIAllocatorOs :: Field
1384 a3f02317 Iustin Pop
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1385 a3f02317 Iustin Pop
1386 a3f02317 Iustin Pop
-- | IAllocator instances field.
1387 a3f02317 Iustin Pop
pIAllocatorInstances :: Field
1388 a3f02317 Iustin Pop
pIAllocatorInstances =
1389 a3f02317 Iustin Pop
  renameField "IAllocatorInstances " .
1390 a3f02317 Iustin Pop
  optionalField $
1391 a3f02317 Iustin Pop
  simpleField "instances" [t| [NonEmptyString] |]
1392 a3f02317 Iustin Pop
1393 a3f02317 Iustin Pop
-- | IAllocator evac mode.
1394 a3f02317 Iustin Pop
pIAllocatorEvacMode :: Field
1395 a3f02317 Iustin Pop
pIAllocatorEvacMode =
1396 a3f02317 Iustin Pop
  renameField "IAllocatorEvacMode" .
1397 a3f02317 Iustin Pop
  optionalField $
1398 a3f02317 Iustin Pop
  simpleField "evac_mode" [t| NodeEvacMode |]
1399 a3f02317 Iustin Pop
1400 a3f02317 Iustin Pop
-- | IAllocator spindle use.
1401 a3f02317 Iustin Pop
pIAllocatorSpindleUse :: Field
1402 a3f02317 Iustin Pop
pIAllocatorSpindleUse =
1403 a3f02317 Iustin Pop
  renameField "IAllocatorSpindleUse" .
1404 a3f02317 Iustin Pop
  defaultField [| forceNonNeg (1::Int) |] $
1405 a3f02317 Iustin Pop
  simpleField "spindle_use" [t| NonNegative Int |]
1406 a3f02317 Iustin Pop
1407 a3f02317 Iustin Pop
-- | IAllocator count field.
1408 a3f02317 Iustin Pop
pIAllocatorCount :: Field
1409 a3f02317 Iustin Pop
pIAllocatorCount =
1410 a3f02317 Iustin Pop
  renameField "IAllocatorCount" .
1411 a3f02317 Iustin Pop
  defaultField [| forceNonNeg (1::Int) |] $
1412 a3f02317 Iustin Pop
  simpleField "count" [t| NonNegative Int |]
1413 a3f02317 Iustin Pop
1414 a3f02317 Iustin Pop
-- | 'OpTestJqueue' notify_waitlock.
1415 a3f02317 Iustin Pop
pJQueueNotifyWaitLock :: Field
1416 a3f02317 Iustin Pop
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1417 a3f02317 Iustin Pop
1418 a3f02317 Iustin Pop
-- | 'OpTestJQueue' notify_exec.
1419 a3f02317 Iustin Pop
pJQueueNotifyExec :: Field
1420 a3f02317 Iustin Pop
pJQueueNotifyExec = defaultFalse "notify_exec"
1421 a3f02317 Iustin Pop
1422 a3f02317 Iustin Pop
-- | 'OpTestJQueue' log_messages.
1423 a3f02317 Iustin Pop
pJQueueLogMessages :: Field
1424 a3f02317 Iustin Pop
pJQueueLogMessages =
1425 a3f02317 Iustin Pop
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1426 a3f02317 Iustin Pop
1427 a3f02317 Iustin Pop
-- | 'OpTestJQueue' fail attribute.
1428 a3f02317 Iustin Pop
pJQueueFail :: Field
1429 a3f02317 Iustin Pop
pJQueueFail =
1430 a3f02317 Iustin Pop
  renameField "JQueueFail" $ defaultFalse "fail"
1431 a3f02317 Iustin Pop
1432 a3f02317 Iustin Pop
-- | 'OpTestDummy' result field.
1433 a3f02317 Iustin Pop
pTestDummyResult :: Field
1434 a3f02317 Iustin Pop
pTestDummyResult =
1435 a3f02317 Iustin Pop
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1436 a3f02317 Iustin Pop
1437 a3f02317 Iustin Pop
-- | 'OpTestDummy' messages field.
1438 a3f02317 Iustin Pop
pTestDummyMessages :: Field
1439 a3f02317 Iustin Pop
pTestDummyMessages =
1440 a3f02317 Iustin Pop
  renameField "TestDummyMessages" $
1441 a3f02317 Iustin Pop
  simpleField "messages" [t| UncheckedValue |]
1442 a3f02317 Iustin Pop
1443 a3f02317 Iustin Pop
-- | 'OpTestDummy' fail field.
1444 a3f02317 Iustin Pop
pTestDummyFail :: Field
1445 a3f02317 Iustin Pop
pTestDummyFail =
1446 a3f02317 Iustin Pop
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1447 a3f02317 Iustin Pop
1448 a3f02317 Iustin Pop
-- | 'OpTestDummy' submit_jobs field.
1449 a3f02317 Iustin Pop
pTestDummySubmitJobs :: Field
1450 a3f02317 Iustin Pop
pTestDummySubmitJobs =
1451 a3f02317 Iustin Pop
  renameField "TestDummySubmitJobs" $
1452 a3f02317 Iustin Pop
  simpleField "submit_jobs" [t| UncheckedValue |]
1453 8d239fa4 Iustin Pop
1454 8d239fa4 Iustin Pop
-- * Network parameters
1455 8d239fa4 Iustin Pop
1456 8d239fa4 Iustin Pop
-- | Network name.
1457 8d239fa4 Iustin Pop
pNetworkName :: Field
1458 8d239fa4 Iustin Pop
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1459 8d239fa4 Iustin Pop
1460 8d239fa4 Iustin Pop
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1461 8d239fa4 Iustin Pop
pNetworkAddress4 :: Field
1462 8d239fa4 Iustin Pop
pNetworkAddress4 =
1463 8d239fa4 Iustin Pop
  renameField "NetworkAddress4" $
1464 8d239fa4 Iustin Pop
  simpleField "network" [t| NonEmptyString |]
1465 8d239fa4 Iustin Pop
1466 8d239fa4 Iustin Pop
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1467 8d239fa4 Iustin Pop
pNetworkGateway4 :: Field
1468 8d239fa4 Iustin Pop
pNetworkGateway4 =
1469 8d239fa4 Iustin Pop
  renameField "NetworkGateway4" $
1470 8d239fa4 Iustin Pop
  optionalNEStringField "gateway"
1471 8d239fa4 Iustin Pop
1472 8d239fa4 Iustin Pop
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1473 8d239fa4 Iustin Pop
pNetworkAddress6 :: Field
1474 8d239fa4 Iustin Pop
pNetworkAddress6 =
1475 8d239fa4 Iustin Pop
  renameField "NetworkAddress6" $
1476 8d239fa4 Iustin Pop
  optionalNEStringField "network6"
1477 8d239fa4 Iustin Pop
1478 8d239fa4 Iustin Pop
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1479 8d239fa4 Iustin Pop
pNetworkGateway6 :: Field
1480 8d239fa4 Iustin Pop
pNetworkGateway6 =
1481 8d239fa4 Iustin Pop
  renameField "NetworkGateway6" $
1482 8d239fa4 Iustin Pop
  optionalNEStringField "gateway6"
1483 8d239fa4 Iustin Pop
1484 8d239fa4 Iustin Pop
-- | Network specific mac prefix (that overrides the cluster one).
1485 8d239fa4 Iustin Pop
pNetworkMacPrefix :: Field
1486 8d239fa4 Iustin Pop
pNetworkMacPrefix =
1487 8d239fa4 Iustin Pop
  renameField "NetMacPrefix" $
1488 8d239fa4 Iustin Pop
  optionalNEStringField "mac_prefix"
1489 8d239fa4 Iustin Pop
1490 8d239fa4 Iustin Pop
-- | Network add reserved IPs.
1491 8d239fa4 Iustin Pop
pNetworkAddRsvdIps :: Field
1492 8d239fa4 Iustin Pop
pNetworkAddRsvdIps =
1493 8d239fa4 Iustin Pop
  renameField "NetworkAddRsvdIps" .
1494 8d239fa4 Iustin Pop
  optionalField $
1495 8d239fa4 Iustin Pop
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1496 8d239fa4 Iustin Pop
1497 8d239fa4 Iustin Pop
-- | Network remove reserved IPs.
1498 8d239fa4 Iustin Pop
pNetworkRemoveRsvdIps :: Field
1499 8d239fa4 Iustin Pop
pNetworkRemoveRsvdIps =
1500 8d239fa4 Iustin Pop
  renameField "NetworkRemoveRsvdIps" .
1501 8d239fa4 Iustin Pop
  optionalField $
1502 8d239fa4 Iustin Pop
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1503 8d239fa4 Iustin Pop
1504 8d239fa4 Iustin Pop
-- | Network mode when connecting to a group.
1505 8d239fa4 Iustin Pop
pNetworkMode :: Field
1506 8d239fa4 Iustin Pop
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1507 8d239fa4 Iustin Pop
1508 8d239fa4 Iustin Pop
-- | Network link when connecting to a group.
1509 8d239fa4 Iustin Pop
pNetworkLink :: Field
1510 8d239fa4 Iustin Pop
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1511 3131adc7 Iustin Pop
1512 b46ba79c Iustin Pop
-- * Common opcode parameters
1513 b46ba79c Iustin Pop
1514 b46ba79c Iustin Pop
-- | Run checks only, don't execute.
1515 b46ba79c Iustin Pop
pDryRun :: Field
1516 b46ba79c Iustin Pop
pDryRun = optionalField $ booleanField "dry_run"
1517 b46ba79c Iustin Pop
1518 b46ba79c Iustin Pop
-- | Debug level.
1519 b46ba79c Iustin Pop
pDebugLevel :: Field
1520 b46ba79c Iustin Pop
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1521 b46ba79c Iustin Pop
1522 b46ba79c Iustin Pop
-- | Opcode priority. Note: python uses a separate constant, we're
1523 b46ba79c Iustin Pop
-- using the actual value we know it's the default.
1524 b46ba79c Iustin Pop
pOpPriority :: Field
1525 b46ba79c Iustin Pop
pOpPriority =
1526 b46ba79c Iustin Pop
  defaultField [| OpPrioNormal |] $
1527 b46ba79c Iustin Pop
  simpleField "priority" [t| OpSubmitPriority |]
1528 b46ba79c Iustin Pop
1529 b46ba79c Iustin Pop
-- | Job dependencies.
1530 b46ba79c Iustin Pop
pDependencies :: Field
1531 1496f5f3 Iustin Pop
pDependencies =
1532 1496f5f3 Iustin Pop
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1533 b46ba79c Iustin Pop
1534 b46ba79c Iustin Pop
-- | Comment field.
1535 b46ba79c Iustin Pop
pComment :: Field
1536 1496f5f3 Iustin Pop
pComment = optionalNullSerField $ stringField "comment"
1537 b46ba79c Iustin Pop
1538 516a0e94 Michele Tartara
-- | Reason trail field.
1539 516a0e94 Michele Tartara
pReason :: Field
1540 516a0e94 Michele Tartara
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1541 516a0e94 Michele Tartara
1542 3131adc7 Iustin Pop
-- * Entire opcode parameter list
1543 3131adc7 Iustin Pop
1544 3131adc7 Iustin Pop
-- | Old-style query opcode, with locking.
1545 3131adc7 Iustin Pop
dOldQuery :: [Field]
1546 3131adc7 Iustin Pop
dOldQuery =
1547 3131adc7 Iustin Pop
  [ pOutputFields
1548 3131adc7 Iustin Pop
  , pNames
1549 3131adc7 Iustin Pop
  , pUseLocking
1550 3131adc7 Iustin Pop
  ]
1551 3131adc7 Iustin Pop
1552 3131adc7 Iustin Pop
-- | Old-style query opcode, without locking.
1553 3131adc7 Iustin Pop
dOldQueryNoLocking :: [Field]
1554 3131adc7 Iustin Pop
dOldQueryNoLocking =
1555 3131adc7 Iustin Pop
  [ pOutputFields
1556 3131adc7 Iustin Pop
  , pNames
1557 3131adc7 Iustin Pop
  ]