Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 9d0b521e

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