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