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