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