Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / OpParams.hs @ cefd4a4a

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