Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 06c2fb4a

History | View | Annotate | Download (44.3 kB)

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