Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 1498270e

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