Merge 'EvacNode' and 'NodeEvacMode'
[ganeti-local] / src / Ganeti / OpParams.hs
index a1e445c..ed06a02 100644 (file)
@@ -32,13 +32,7 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 -}
 
 module Ganeti.OpParams
-  ( TagType(..)
-  , TagObject(..)
-  , tagObjectFrom
-  , tagNameOf
-  , decodeTagObject
-  , encodeTagObject
-  , ReplaceDisksMode(..)
+  ( ReplaceDisksMode(..)
   , DiskIndex
   , mkDiskIndex
   , unDiskIndex
@@ -50,10 +44,12 @@ module Ganeti.OpParams
   , SetParamsMods(..)
   , ExportTarget(..)
   , pInstanceName
+  , pInstanceUuid
   , pInstances
   , pName
   , pTagsList
   , pTagsObject
+  , pTagsName
   , pOutputFields
   , pShutdownTimeout
   , pShutdownTimeout'
@@ -61,7 +57,9 @@ module Ganeti.OpParams
   , pForce
   , pIgnoreOfflineNodes
   , pNodeName
+  , pNodeUuid
   , pNodeNames
+  , pNodeUuids
   , pGroupName
   , pMigrationMode
   , pMigrationLive
@@ -82,7 +80,9 @@ module Ganeti.OpParams
   , pIpConflictsCheck
   , pNoRemember
   , pMigrationTargetNode
+  , pMigrationTargetNodeUuid
   , pMoveTargetNode
+  , pMoveTargetNodeUuid
   , pStartupPaused
   , pVerbose
   , pDebugSimulateErrors
@@ -100,6 +100,8 @@ module Ganeti.OpParams
   , pOptDiskTemplate
   , pFileDriver
   , pFileStorageDir
+  , pGlobalFileStorageDir
+  , pGlobalSharedFileStorageDir
   , pVgName
   , pEnabledHypervisors
   , pHypervisor
@@ -132,6 +134,7 @@ module Ganeti.OpParams
   , pUseExternalMipScript
   , pQueryFields
   , pQueryFilter
+  , pQueryFieldsFields
   , pOobCommand
   , pOobTimeout
   , pIgnoreStatus
@@ -145,6 +148,7 @@ module Ganeti.OpParams
   , pNames
   , pNodes
   , pRequiredNodes
+  , pRequiredNodeUuids
   , pStorageType
   , pStorageChanges
   , pMasterCandidate
@@ -154,17 +158,21 @@ module Ganeti.OpParams
   , pPowered
   , pIallocator
   , pRemoteNode
+  , pRemoteNodeUuid
   , pEvacMode
   , pInstCreateMode
   , pNoInstall
   , pInstOs
   , pPrimaryNode
+  , pPrimaryNodeUuid
   , pSecondaryNode
+  , pSecondaryNodeUuid
   , pSourceHandshake
   , pSourceInstance
   , pSourceShutdownTimeout
   , pSourceX509Ca
   , pSrcNode
+  , pSrcNodeUuid
   , pSrcPath
   , pStartInstance
   , pInstTags
@@ -189,6 +197,7 @@ module Ganeti.OpParams
   , pTargetGroups
   , pExportMode
   , pExportTargetNode
+  , pExportTargetNodeUuid
   , pRemoveInstance
   , pIgnoreRemoveFailures
   , pX509KeyName
@@ -201,6 +210,7 @@ module Ganeti.OpParams
   , pDelayDuration
   , pDelayOnMaster
   , pDelayOnNodes
+  , pDelayOnNodeUuids
   , pDelayRepeat
   , pIAllocatorDirection
   , pIAllocatorMode
@@ -239,14 +249,11 @@ module Ganeti.OpParams
   , pComment
   , pReason
   , pEnabledDiskTemplates
-  , dOldQuery
-  , dOldQueryNoLocking
   ) where
 
 import Control.Monad (liftM)
-import qualified Data.Set as Set
-import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
-                  JSObject, toJSObject)
+import Text.JSON (JSON, JSValue(..), JSObject (..), readJSON, showJSON,
+                  fromJSString, toJSObject)
 import qualified Text.JSON
 import Text.JSON.Pretty (pp_value)
 
@@ -259,8 +266,6 @@ import qualified Ganeti.Query.Language as Qlang
 
 -- * Helper functions and types
 
--- * Type aliases
-
 -- | Build a boolean field.
 booleanField :: String -> Field
 booleanField = flip simpleField [t| Bool |]
@@ -285,15 +290,6 @@ optionalStringField = optionalField . stringField
 optionalNEStringField :: String -> Field
 optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
 
--- | Unchecked value, should be replaced by a better definition.
-type UncheckedValue = JSValue
-
--- | Unchecked dict, should be replaced by a better definition.
-type UncheckedDict = JSObject JSValue
-
--- | Unchecked list, shoild be replaced by a better definition.
-type UncheckedList = [JSValue]
-
 -- | Function to force a non-negative value, without returning via a
 -- monad. This is needed for, and should be used /only/ in the case of
 -- forcing constants. In case the constant is wrong (< 0), this will
@@ -303,65 +299,6 @@ forceNonNeg i = case mkNonNegative i of
                   Ok n -> n
                   Bad msg -> error msg
 
--- ** Tags
-
--- | Data type representing what items do the tag operations apply to.
-$(declareSADT "TagType"
-  [ ("TagTypeInstance", 'C.tagInstance)
-  , ("TagTypeNode",     'C.tagNode)
-  , ("TagTypeGroup",    'C.tagNodegroup)
-  , ("TagTypeCluster",  'C.tagCluster)
-  ])
-$(makeJSONInstance ''TagType)
-
--- | Data type holding a tag object (type and object name).
-data TagObject = TagInstance String
-               | TagNode     String
-               | TagGroup    String
-               | TagCluster
-               deriving (Show, Eq)
-
--- | Tag type for a given tag object.
-tagTypeOf :: TagObject -> TagType
-tagTypeOf (TagInstance {}) = TagTypeInstance
-tagTypeOf (TagNode     {}) = TagTypeNode
-tagTypeOf (TagGroup    {}) = TagTypeGroup
-tagTypeOf (TagCluster  {}) = TagTypeCluster
-
--- | Gets the potential tag object name.
-tagNameOf :: TagObject -> Maybe String
-tagNameOf (TagInstance s) = Just s
-tagNameOf (TagNode     s) = Just s
-tagNameOf (TagGroup    s) = Just s
-tagNameOf  TagCluster     = Nothing
-
--- | Builds a 'TagObject' from a tag type and name.
-tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
-tagObjectFrom TagTypeInstance (JSString s) =
-  return . TagInstance $ fromJSString s
-tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
-tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
-tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
-tagObjectFrom t v =
-  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
-         show (pp_value v)
-
--- | Name of the tag \"name\" field.
-tagNameField :: String
-tagNameField = "name"
-
--- | Custom encoder for 'TagObject' as represented in an opcode.
-encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
-encodeTagObject t = ( showJSON (tagTypeOf t)
-                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
-
--- | Custom decoder for 'TagObject' as represented in an opcode.
-decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
-decodeTagObject obj kind = do
-  ttype <- fromJVal kind
-  tname <- fromObj obj tagNameField
-  tagObjectFrom ttype tname
-
 -- ** Disks
 
 -- | Replace disks type.
@@ -400,11 +337,13 @@ $(makeJSONInstance ''DiskAccess)
 
 -- | NIC modification definition.
 $(buildObject "INicParams" "inic"
-  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
-  , optionalField $ simpleField C.inicIp   [t| String         |]
-  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
-  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
-  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
+  [ optionalField $ simpleField C.inicMac    [t| NonEmptyString |]
+  , optionalField $ simpleField C.inicIp     [t| String         |]
+  , optionalField $ simpleField C.inicMode   [t| NonEmptyString |]
+  , optionalField $ simpleField C.inicLink   [t| NonEmptyString |]
+  , optionalField $ simpleField C.inicName   [t| NonEmptyString |]
+  , optionalField $ simpleField C.inicVlan   [t| NonEmptyString |]
+  , optionalField $ simpleField C.inicBridge [t| NonEmptyString |]
   ])
 
 -- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
@@ -486,11 +425,11 @@ instance (JSON a) => JSON (SetParamsMods a) where
   readJSON = readSetParams
 
 -- | Custom type for target_node parameter of OpBackupExport, which
--- varies depending on mode. FIXME: this uses an UncheckedList since
+-- varies depending on mode. FIXME: this uses an [JSValue] since
 -- we don't care about individual rows (just like the Python code
 -- tests). But the proper type could be parsed if we wanted.
 data ExportTarget = ExportTargetLocal NonEmptyString
-                  | ExportTargetRemote UncheckedList
+                  | ExportTargetRemote [JSValue]
                     deriving (Eq, Show)
 
 -- | Custom reader for 'ExportTarget'.
@@ -506,365 +445,191 @@ instance JSON ExportTarget where
   showJSON (ExportTargetRemote l) = showJSON l
   readJSON = readExportTarget
 
--- * Parameters
-
--- | A required instance name (for single-instance LUs).
-pInstanceName :: Field
-pInstanceName = simpleField "instance_name" [t| String |]
-
--- | A list of instances.
-pInstances :: Field
-pInstances = defaultField [| [] |] $
-             simpleField "instances" [t| [NonEmptyString] |]
-
--- | A generic name.
-pName :: Field
-pName = simpleField "name" [t| NonEmptyString |]
-
--- | Tags list.
-pTagsList :: Field
-pTagsList = simpleField "tags" [t| [String] |]
-
--- | Tags object.
-pTagsObject :: Field
-pTagsObject =
-  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
-  simpleField "kind" [t| TagObject |]
-
--- | Selected output fields.
-pOutputFields :: Field
-pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
-
--- | How long to wait for instance to shut down.
-pShutdownTimeout :: Field
-pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
-                   simpleField "shutdown_timeout" [t| NonNegative Int |]
-
--- | Another name for the shutdown timeout, because we like to be
--- inconsistent.
-pShutdownTimeout' :: Field
-pShutdownTimeout' =
-  renameField "InstShutdownTimeout" .
-  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
-  simpleField "timeout" [t| NonNegative Int |]
-
--- | Whether to shutdown the instance in backup-export.
-pShutdownInstance :: Field
-pShutdownInstance = defaultTrue "shutdown"
-
--- | Whether to force the operation.
-pForce :: Field
-pForce = defaultFalse "force"
-
--- | Whether to ignore offline nodes.
-pIgnoreOfflineNodes :: Field
-pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
-
--- | A required node name (for single-node LUs).
-pNodeName :: Field
-pNodeName = simpleField "node_name" [t| NonEmptyString |]
-
--- | List of nodes.
-pNodeNames :: Field
-pNodeNames =
-  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
-
--- | A required node group name (for single-group LUs).
-pGroupName :: Field
-pGroupName = simpleField "group_name" [t| NonEmptyString |]
-
--- | Migration type (live\/non-live).
-pMigrationMode :: Field
-pMigrationMode =
-  renameField "MigrationMode" .
-  optionalField $
-  simpleField "mode" [t| MigrationMode |]
-
--- | Obsolete \'live\' migration mode (boolean).
-pMigrationLive :: Field
-pMigrationLive =
-  renameField "OldLiveMode" . optionalField $ booleanField "live"
-
--- | Migration cleanup parameter.
-pMigrationCleanup :: Field
-pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
-
--- | Whether to force an unknown OS variant.
-pForceVariant :: Field
-pForceVariant = defaultFalse "force_variant"
-
--- | Whether to wait for the disk to synchronize.
-pWaitForSync :: Field
-pWaitForSync = defaultTrue "wait_for_sync"
-
--- | Whether to wait for the disk to synchronize (defaults to false).
-pWaitForSyncFalse :: Field
-pWaitForSyncFalse = defaultField [| False |] pWaitForSync
-
--- | Whether to ignore disk consistency
-pIgnoreConsistency :: Field
-pIgnoreConsistency = defaultFalse "ignore_consistency"
-
--- | Storage name.
-pStorageName :: Field
-pStorageName =
-  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
-
--- | Whether to use synchronization.
-pUseLocking :: Field
-pUseLocking = defaultFalse "use_locking"
-
--- | Whether to employ opportunistic locking for nodes, meaning nodes already
--- locked by another opcode won't be considered for instance allocation (only
--- when an iallocator is used).
-pOpportunisticLocking :: Field
-pOpportunisticLocking = defaultFalse "opportunistic_locking"
-
--- | Whether to check name.
-pNameCheck :: Field
-pNameCheck = defaultTrue "name_check"
-
--- | Instance allocation policy.
-pNodeGroupAllocPolicy :: Field
-pNodeGroupAllocPolicy = optionalField $
-                        simpleField "alloc_policy" [t| AllocPolicy |]
-
--- | Default node parameters for group.
-pGroupNodeParams :: Field
-pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
-
--- | Resource(s) to query for.
-pQueryWhat :: Field
-pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
-
--- | Whether to release locks as soon as possible.
-pEarlyRelease :: Field
-pEarlyRelease = defaultFalse "early_release"
-
--- | Whether to ensure instance's IP address is inactive.
-pIpCheck :: Field
-pIpCheck = defaultTrue "ip_check"
+-- * Common opcode parameters
 
--- | Check for conflicting IPs.
-pIpConflictsCheck :: Field
-pIpConflictsCheck = defaultTrue "conflicts_check"
+pDryRun :: Field
+pDryRun =
+  withDoc "Run checks only, don't execute" .
+  optionalField $ booleanField "dry_run"
 
--- | Do not remember instance state changes.
-pNoRemember :: Field
-pNoRemember = defaultFalse "no_remember"
+pDebugLevel :: Field
+pDebugLevel =
+  withDoc "Debug level" .
+  optionalField $ simpleField "debug_level" [t| NonNegative Int |]
 
--- | Target node for instance migration/failover.
-pMigrationTargetNode :: Field
-pMigrationTargetNode = optionalNEStringField "target_node"
+pOpPriority :: Field
+pOpPriority =
+  withDoc "Opcode priority. Note: python uses a separate constant,\
+          \ we're using the actual value we know it's the default" .
+  defaultField [| OpPrioNormal |] $
+  simpleField "priority" [t| OpSubmitPriority |]
 
--- | Target node for instance move (required).
-pMoveTargetNode :: Field
-pMoveTargetNode =
-  renameField "MoveTargetNode" $
-  simpleField "target_node" [t| NonEmptyString |]
+pDependencies :: Field
+pDependencies =
+  withDoc "Job dependencies" .
+  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
 
--- | Pause instance at startup.
-pStartupPaused :: Field
-pStartupPaused = defaultFalse "startup_paused"
+pComment :: Field
+pComment =
+  withDoc "Comment field" .
+  optionalNullSerField $ stringField "comment"
 
--- | Verbose mode.
-pVerbose :: Field
-pVerbose = defaultFalse "verbose"
+pReason :: Field
+pReason =
+  withDoc "Reason trail field" $
+  simpleField C.opcodeReason [t| ReasonTrail |]
 
--- ** Parameters for cluster verification
+-- * Parameters
 
--- | Whether to simulate errors (useful for debugging).
 pDebugSimulateErrors :: Field
-pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
+pDebugSimulateErrors =
+  withDoc "Whether to simulate errors (useful for debugging)" $
+  defaultFalse "debug_simulate_errors"
 
--- | Error codes.
 pErrorCodes :: Field
-pErrorCodes = defaultFalse "error_codes"
+pErrorCodes = 
+  withDoc "Error codes" $
+  defaultFalse "error_codes"
 
--- | Which checks to skip.
 pSkipChecks :: Field
-pSkipChecks = defaultField [| Set.empty |] $
-              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
+pSkipChecks = 
+  withDoc "Which checks to skip" .
+  defaultField [| emptyListSet |] $
+  simpleField "skip_checks" [t| ListSet VerifyOptionalChecks |]
 
--- | List of error codes that should be treated as warnings.
 pIgnoreErrors :: Field
-pIgnoreErrors = defaultField [| Set.empty |] $
-                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
-
--- | Optional group name.
-pOptGroupName :: Field
-pOptGroupName = renameField "OptGroupName" .
-                optionalField $ simpleField "group_name" [t| NonEmptyString |]
-
--- | Disk templates' parameter defaults.
-pDiskParams :: Field
-pDiskParams = optionalField $
-              simpleField "diskparams" [t| GenericContainer DiskTemplate
-                                           UncheckedDict |]
-
--- * Parameters for node resource model
-
--- | Set hypervisor states.
-pHvState :: Field
-pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
+pIgnoreErrors =
+  withDoc "List of error codes that should be treated as warnings" .
+  defaultField [| emptyListSet |] $
+  simpleField "ignore_errors" [t| ListSet CVErrorCode |]
 
--- | Set disk states.
-pDiskState :: Field
-pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
+pVerbose :: Field
+pVerbose =
+  withDoc "Verbose mode" $
+  defaultFalse "verbose"
 
--- | Whether to ignore ipolicy violations.
-pIgnoreIpolicy :: Field
-pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
+pOptGroupName :: Field
+pOptGroupName =
+  withDoc "Optional group name" .
+  renameField "OptGroupName" .
+  optionalField $ simpleField "group_name" [t| NonEmptyString |]
 
--- | Allow runtime changes while migrating.
-pAllowRuntimeChgs :: Field
-pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
+pGroupName :: Field
+pGroupName =
+  withDoc "Group name" $
+  simpleField "group_name" [t| NonEmptyString |]
 
--- | Utility type for OpClusterSetParams.
-type TestClusterOsListItem = (DdmSimple, NonEmptyString)
+pInstances :: Field
+pInstances =
+  withDoc "List of instances" .
+  defaultField [| [] |] $
+  simpleField "instances" [t| [NonEmptyString] |]
 
--- | Utility type of OsList.
-type TestClusterOsList = [TestClusterOsListItem]
+pOutputFields :: Field
+pOutputFields =
+  withDoc "Selected output fields" $
+  simpleField "output_fields" [t| [NonEmptyString] |]
 
--- Utility type for NIC definitions.
---type TestNicDef = INicParams
+pName :: Field
+pName =
+  withDoc "A generic name" $
+  simpleField "name" [t| NonEmptyString |]
 
--- | List of instance disks.
-pInstDisks :: Field
-pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
+pForce :: Field
+pForce =
+  withDoc "Whether to force the operation" $
+  defaultFalse "force"
 
--- | Instance disk template.
-pDiskTemplate :: Field
-pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
+pHvState :: Field
+pHvState =
+  withDoc "Set hypervisor states" .
+  optionalField $ simpleField "hv_state" [t| JSObject JSValue |]
 
--- | Instance disk template.
-pOptDiskTemplate :: Field
-pOptDiskTemplate =
-  optionalField .
-  renameField "OptDiskTemplate" $
-  simpleField "disk_template" [t| DiskTemplate |]
+pDiskState :: Field
+pDiskState =
+  withDoc "Set disk states" .
+  optionalField $ simpleField "disk_state" [t| JSObject JSValue |]
 
--- | File driver.
-pFileDriver :: Field
-pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
+-- | Global directory for storing file-backed disks.
+pGlobalFileStorageDir :: Field
+pGlobalFileStorageDir = optionalNEStringField "file_storage_dir"
 
--- | Directory for storing file-backed disks.
-pFileStorageDir :: Field
-pFileStorageDir = optionalNEStringField "file_storage_dir"
+-- | Global directory for storing shared-file-backed disks.
+pGlobalSharedFileStorageDir :: Field
+pGlobalSharedFileStorageDir = optionalNEStringField "shared_file_storage_dir"
 
 -- | Volume group name.
 pVgName :: Field
-pVgName = optionalStringField "vg_name"
+pVgName =
+  withDoc "Volume group name" $
+  optionalStringField "vg_name"
 
--- | List of enabled hypervisors.
 pEnabledHypervisors :: Field
 pEnabledHypervisors =
+  withDoc "List of enabled hypervisors" .
   optionalField $
-  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
+  simpleField "enabled_hypervisors" [t| [Hypervisor] |]
 
--- | List of enabled disk templates.
-pEnabledDiskTemplates :: Field
-pEnabledDiskTemplates =
-  optionalField $
-  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
-
--- | Selected hypervisor for an instance.
-pHypervisor :: Field
-pHypervisor =
-  optionalField $
-  simpleField "hypervisor" [t| Hypervisor |]
-
--- | Cluster-wide hypervisor parameters, hypervisor-dependent.
 pClusterHvParams :: Field
 pClusterHvParams =
+  withDoc "Cluster-wide hypervisor parameters, hypervisor-dependent" .
   renameField "ClusterHvParams" .
   optionalField $
-  simpleField "hvparams" [t| Container UncheckedDict |]
-
--- | Instance hypervisor parameters.
-pInstHvParams :: Field
-pInstHvParams =
-  renameField "InstHvParams" .
-  defaultField [| toJSObject [] |] $
-  simpleField "hvparams" [t| UncheckedDict |]
+  simpleField "hvparams" [t| GenericContainer String (JSObject JSValue) |]
 
--- | Cluster-wide beparams.
 pClusterBeParams :: Field
 pClusterBeParams =
+  withDoc "Cluster-wide backend parameter defaults" .
   renameField "ClusterBeParams" .
-  optionalField $ simpleField "beparams" [t| UncheckedDict |]
+  optionalField $ simpleField "beparams" [t| JSObject JSValue |]
 
--- | Instance beparams.
-pInstBeParams :: Field
-pInstBeParams =
-  renameField "InstBeParams" .
-  defaultField [| toJSObject [] |] $
-  simpleField "beparams" [t| UncheckedDict |]
-
--- | Reset instance parameters to default if equal.
-pResetDefaults :: Field
-pResetDefaults = defaultFalse "identify_defaults"
-
--- | Cluster-wide per-OS hypervisor parameter defaults.
 pOsHvp :: Field
-pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
+pOsHvp =
+  withDoc "Cluster-wide per-OS hypervisor parameter defaults" .
+  optionalField $
+  simpleField "os_hvp" [t| GenericContainer String (JSObject JSValue) |]
 
--- | Cluster-wide OS parameter defaults.
 pClusterOsParams :: Field
 pClusterOsParams =
+  withDoc "Cluster-wide OS parameter defaults" .
   renameField "ClusterOsParams" .
-  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
-
--- | Instance OS parameters.
-pInstOsParams :: Field
-pInstOsParams =
-  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
-  simpleField "osparams" [t| UncheckedDict |]
-
--- | Temporary OS parameters (currently only in reinstall, might be
--- added to install as well).
-pTempOsParams :: Field
-pTempOsParams =
-  renameField "TempOsParams" .
-  optionalField $ simpleField "osparams" [t| UncheckedDict |]
-
--- | Temporary hypervisor parameters, hypervisor-dependent.
-pTempHvParams :: Field
-pTempHvParams =
-  renameField "TempHvParams" .
-  defaultField [| toJSObject [] |] $
-  simpleField "hvparams" [t| UncheckedDict |]
+  optionalField $
+  simpleField "osparams" [t| GenericContainer String (JSObject JSValue) |]
 
--- | Temporary backend parameters.
-pTempBeParams :: Field
-pTempBeParams =
-  renameField "TempBeParams" .
-  defaultField [| toJSObject [] |] $
-  simpleField "beparams" [t| UncheckedDict |]
+pDiskParams :: Field
+pDiskParams =
+  withDoc "Disk templates' parameter defaults" .
+  optionalField $
+  simpleField "diskparams"
+              [t| GenericContainer DiskTemplate (JSObject JSValue) |]
 
--- | Candidate pool size.
 pCandidatePoolSize :: Field
 pCandidatePoolSize =
+  withDoc "Master candidate pool size" .
   optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
 
--- | Set UID pool, must be list of lists describing UID ranges (two
--- items, start and end inclusive.
 pUidPool :: Field
-pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
+pUidPool =
+  withDoc "Set UID pool, must be list of lists describing UID ranges\
+          \ (two items, start and end inclusive)" .
+  optionalField $ simpleField "uid_pool" [t| [(Int, Int)] |]
 
--- | Extend UID pool, must be list of lists describing UID ranges (two
--- items, start and end inclusive.
 pAddUids :: Field
-pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
+pAddUids =
+  withDoc "Extend UID pool, must be list of lists describing UID\
+          \ ranges (two items, start and end inclusive)" .
+  optionalField $ simpleField "add_uids" [t| [(Int, Int)] |]
 
--- | Shrink UID pool, must be list of lists describing UID ranges (two
--- items, start and end inclusive) to be removed.
 pRemoveUids :: Field
-pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
+pRemoveUids =
+  withDoc "Shrink UID pool, must be list of lists describing UID\
+          \ ranges (two items, start and end inclusive) to be removed" .
+  optionalField $ simpleField "remove_uids" [t| [(Int, Int)] |]
 
--- | Whether to automatically maintain node health.
 pMaintainNodeHealth :: Field
-pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
+pMaintainNodeHealth =
+  withDoc "Whether to automatically maintain node health" .
+  optionalField $ booleanField "maintain_node_health"
 
 -- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
 pModifyEtcHosts :: Field
@@ -872,601 +637,967 @@ pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
 
 -- | Whether to wipe disks before allocating them to instances.
 pPreallocWipeDisks :: Field
-pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
+pPreallocWipeDisks =
+  withDoc "Whether to wipe disks before allocating them to instances" .
+  optionalField $ booleanField "prealloc_wipe_disks"
 
--- | Cluster-wide NIC parameter defaults.
 pNicParams :: Field
-pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
-
--- | Instance NIC definitions.
-pInstNics :: Field
-pInstNics = simpleField "nics" [t| [INicParams] |]
+pNicParams =
+  withDoc "Cluster-wide NIC parameter defaults" .
+  optionalField $ simpleField "nicparams" [t| INicParams |]
 
--- | Cluster-wide node parameter defaults.
-pNdParams :: Field
-pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
-
--- | Cluster-wide ipolicy specs.
 pIpolicy :: Field
-pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
+pIpolicy =
+  withDoc "Ipolicy specs" .
+  optionalField $ simpleField "ipolicy" [t| JSObject JSValue |]
 
--- | DRBD helper program.
 pDrbdHelper :: Field
-pDrbdHelper = optionalStringField "drbd_helper"
+pDrbdHelper =
+  withDoc "DRBD helper program" $
+  optionalStringField "drbd_helper"
 
--- | Default iallocator for cluster.
 pDefaultIAllocator :: Field
-pDefaultIAllocator = optionalStringField "default_iallocator"
+pDefaultIAllocator =
+  withDoc "Default iallocator for cluster" $
+  optionalStringField "default_iallocator"
 
--- | Master network device.
 pMasterNetdev :: Field
-pMasterNetdev = optionalStringField "master_netdev"
+pMasterNetdev =
+  withDoc "Master network device" $
+  optionalStringField "master_netdev"
 
--- | Netmask of the master IP.
 pMasterNetmask :: Field
 pMasterNetmask =
+  withDoc "Netmask of the master IP" .
   optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
 
--- | List of reserved LVs.
 pReservedLvs :: Field
 pReservedLvs =
+  withDoc "List of reserved LVs" .
   optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
 
--- | Modify list of hidden operating systems: each modification must
--- have two items, the operation and the OS name; the operation can be
--- add or remove.
 pHiddenOs :: Field
-pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
+pHiddenOs =
+  withDoc "Modify list of hidden operating systems: each modification\
+          \ must have two items, the operation and the OS name; the operation\
+          \ can be add or remove" .
+  optionalField $ simpleField "hidden_os" [t| [(DdmSimple, NonEmptyString)] |]
 
--- | Modify list of blacklisted operating systems: each modification
--- must have two items, the operation and the OS name; the operation
--- can be add or remove.
 pBlacklistedOs :: Field
 pBlacklistedOs =
-  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
+  withDoc "Modify list of blacklisted operating systems: each\
+          \ modification must have two items, the operation and the OS name;\
+          \ the operation can be add or remove" .
+  optionalField $
+  simpleField "blacklisted_os" [t| [(DdmSimple, NonEmptyString)] |]
 
--- | Whether to use an external master IP address setup script.
 pUseExternalMipScript :: Field
-pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
+pUseExternalMipScript =
+  withDoc "Whether to use an external master IP address setup script" .
+  optionalField $ booleanField "use_external_mip_script"
+
+pEnabledDiskTemplates :: Field
+pEnabledDiskTemplates =
+  withDoc "List of enabled disk templates" .
+  optionalField $
+  simpleField "enabled_disk_templates" [t| [DiskTemplate] |]
+
+pQueryWhat :: Field
+pQueryWhat =
+  withDoc "Resource(s) to query for" $
+  simpleField "what" [t| Qlang.QueryTypeOp |]
+
+pUseLocking :: Field
+pUseLocking =
+  withDoc "Whether to use synchronization" $
+  defaultFalse "use_locking"
 
--- | Requested fields.
 pQueryFields :: Field
-pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
+pQueryFields =
+  withDoc "Requested fields" $
+  simpleField "fields" [t| [NonEmptyString] |]
 
--- | Query filter.
 pQueryFilter :: Field
-pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
+pQueryFilter =
+  withDoc "Query filter" .
+  optionalField $ simpleField "qfilter" [t| [JSValue] |]
+
+pQueryFieldsFields :: Field
+pQueryFieldsFields =
+  withDoc "Requested fields; if not given, all are returned" .
+  renameField "QueryFieldsFields" $
+  optionalField pQueryFields
+
+pNodeNames :: Field
+pNodeNames =
+  withDoc "List of node names to run the OOB command against" .
+  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
+
+pNodeUuids :: Field
+pNodeUuids =
+  withDoc "List of node UUIDs" .
+  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
 
--- | OOB command to run.
 pOobCommand :: Field
-pOobCommand = simpleField "command" [t| OobCommand |]
+pOobCommand =
+  withDoc "OOB command to run" $
+  simpleField "command" [t| OobCommand |]
 
--- | Timeout before the OOB helper will be terminated.
 pOobTimeout :: Field
 pOobTimeout =
-  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
+  withDoc "Timeout before the OOB helper will be terminated" .
+  defaultField [| C.oobTimeout |] $
+  simpleField "timeout" [t| Int |]
 
--- | Ignores the node offline status for power off.
 pIgnoreStatus :: Field
-pIgnoreStatus = defaultFalse "ignore_status"
+pIgnoreStatus =
+  withDoc "Ignores the node offline status for power off" $
+  defaultFalse "ignore_status"
 
--- | Time in seconds to wait between powering on nodes.
 pPowerDelay :: Field
 pPowerDelay =
   -- FIXME: we can't use the proper type "NonNegative Double", since
   -- the default constant is a plain Double, not a non-negative one.
+  -- And trying to fix the constant introduces a cyclic import.
+  withDoc "Time in seconds to wait between powering on nodes" .
   defaultField [| C.oobPowerDelay |] $
   simpleField "power_delay" [t| Double |]
 
--- | Primary IP address.
+pRequiredNodes :: Field
+pRequiredNodes =
+  withDoc "Required list of node names" .
+  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
+
+pRequiredNodeUuids :: Field
+pRequiredNodeUuids =
+  withDoc "Required list of node UUIDs" .
+  renameField "ReqNodeUuids " . optionalField $
+  simpleField "node_uuids" [t| [NonEmptyString] |]
+
+pRestrictedCommand :: Field
+pRestrictedCommand =
+  withDoc "Restricted command name" .
+  renameField "RestrictedCommand" $
+  simpleField "command" [t| NonEmptyString |]
+
+pNodeName :: Field
+pNodeName =
+  withDoc "A required node name (for single-node LUs)" $
+  simpleField "node_name" [t| NonEmptyString |]
+
+pNodeUuid :: Field
+pNodeUuid =
+  withDoc "A node UUID (for single-node LUs)" .
+  optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
+
 pPrimaryIp :: Field
-pPrimaryIp = optionalStringField "primary_ip"
+pPrimaryIp =
+  withDoc "Primary IP address" .
+  optionalField $
+  simpleField "primary_ip" [t| NonEmptyString |]
 
--- | Secondary IP address.
 pSecondaryIp :: Field
-pSecondaryIp = optionalNEStringField "secondary_ip"
+pSecondaryIp =
+  withDoc "Secondary IP address" $
+  optionalNEStringField "secondary_ip"
 
--- | Whether node is re-added to cluster.
 pReadd :: Field
-pReadd = defaultFalse "readd"
+pReadd =
+  withDoc "Whether node is re-added to cluster" $
+  defaultFalse "readd"
 
--- | Initial node group.
 pNodeGroup :: Field
-pNodeGroup = optionalNEStringField "group"
+pNodeGroup =
+  withDoc "Initial node group" $
+  optionalNEStringField "group"
 
--- | Whether node can become master or master candidate.
 pMasterCapable :: Field
-pMasterCapable = optionalField $ booleanField "master_capable"
+pMasterCapable =
+  withDoc "Whether node can become master or master candidate" .
+  optionalField $ booleanField "master_capable"
 
--- | Whether node can host instances.
 pVmCapable :: Field
-pVmCapable = optionalField $ booleanField "vm_capable"
+pVmCapable =
+  withDoc "Whether node can host instances" .
+  optionalField $ booleanField "vm_capable"
 
--- | List of names.
+pNdParams :: Field
+pNdParams =
+  withDoc "Node parameters" .
+  renameField "genericNdParams" .
+  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
+  
 pNames :: Field
-pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
+pNames =
+  withDoc "List of names" .
+  defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
 
--- | List of node names.
 pNodes :: Field
-pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
+pNodes =
+  withDoc "List of nodes" .
+  defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
 
--- | Required list of node names.
-pRequiredNodes :: Field
-pRequiredNodes =
-  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
-
--- | Storage type.
 pStorageType :: Field
-pStorageType = simpleField "storage_type" [t| StorageType |]
+pStorageType =
+  withDoc "Storage type" $
+  simpleField "storage_type" [t| StorageType |]
+
+pStorageName :: Field
+pStorageName =
+  withDoc "Storage name" .
+  renameField "StorageName" .
+  optionalField $ simpleField "name" [t| NonEmptyString |]
 
--- | Storage changes (unchecked).
 pStorageChanges :: Field
-pStorageChanges = simpleField "changes" [t| UncheckedDict |]
+pStorageChanges =
+  withDoc "Requested storage changes" $
+  simpleField "changes" [t| JSObject JSValue |]
+
+pIgnoreConsistency :: Field
+pIgnoreConsistency =
+  withDoc "Whether to ignore disk consistency" $
+  defaultFalse "ignore_consistency"
 
--- | Whether the node should become a master candidate.
 pMasterCandidate :: Field
-pMasterCandidate = optionalField $ booleanField "master_candidate"
+pMasterCandidate =
+  withDoc "Whether the node should become a master candidate" .
+  optionalField $ booleanField "master_candidate"
 
--- | Whether the node should be marked as offline.
 pOffline :: Field
-pOffline = optionalField $ booleanField "offline"
+pOffline =
+  withDoc "Whether to mark the node or instance offline" .
+  optionalField $ booleanField "offline"
 
--- | Whether the node should be marked as drained.
 pDrained ::Field
-pDrained = optionalField $ booleanField "drained"
+pDrained =
+  withDoc "Whether to mark the node as drained" .
+  optionalField $ booleanField "drained"
 
--- | Whether node(s) should be promoted to master candidate if necessary.
 pAutoPromote :: Field
-pAutoPromote = defaultFalse "auto_promote"
+pAutoPromote =
+  withDoc "Whether node(s) should be promoted to master candidate if\
+          \ necessary" $
+  defaultFalse "auto_promote"
 
--- | Whether the node should be marked as powered
 pPowered :: Field
-pPowered = optionalField $ booleanField "powered"
+pPowered =
+  withDoc "Whether the node should be marked as powered" .
+  optionalField $ booleanField "powered"
+
+pMigrationMode :: Field
+pMigrationMode =
+  withDoc "Migration type (live/non-live)" .
+  renameField "MigrationMode" .
+  optionalField $
+  simpleField "mode" [t| MigrationMode |]
+
+pMigrationLive :: Field
+pMigrationLive =
+  withDoc "Obsolete \'live\' migration mode (do not use)" .
+  renameField "OldLiveMode" . optionalField $ booleanField "live"
+
+pMigrationTargetNode :: Field
+pMigrationTargetNode =
+  withDoc "Target node for instance migration/failover" $
+  optionalNEStringField "target_node"
 
--- | Iallocator for deciding the target node for shared-storage
--- instances during migrate and failover.
+pMigrationTargetNodeUuid :: Field
+pMigrationTargetNodeUuid =
+  withDoc "Target node UUID for instance migration/failover" $
+  optionalNEStringField "target_node_uuid"
+
+pAllowRuntimeChgs :: Field
+pAllowRuntimeChgs =
+  withDoc "Whether to allow runtime changes while migrating" $
+  defaultTrue "allow_runtime_changes"
+
+pIgnoreIpolicy :: Field
+pIgnoreIpolicy =
+  withDoc "Whether to ignore ipolicy violations" $
+  defaultFalse "ignore_ipolicy"
+  
 pIallocator :: Field
-pIallocator = optionalNEStringField "iallocator"
+pIallocator =
+  withDoc "Iallocator for deciding the target node for shared-storage\
+          \ instances" $
+  optionalNEStringField "iallocator"
+
+pEarlyRelease :: Field
+pEarlyRelease =
+  withDoc "Whether to release locks as soon as possible" $
+  defaultFalse "early_release"
 
--- | New secondary node.
 pRemoteNode :: Field
-pRemoteNode = optionalNEStringField "remote_node"
+pRemoteNode =
+  withDoc "New secondary node" $
+  optionalNEStringField "remote_node"
+
+pRemoteNodeUuid :: Field
+pRemoteNodeUuid =
+  withDoc "New secondary node UUID" $
+  optionalNEStringField "remote_node_uuid"
 
--- | Node evacuation mode.
 pEvacMode :: Field
-pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
+pEvacMode =
+  withDoc "Node evacuation mode" .
+  renameField "EvacMode" $ simpleField "mode" [t| EvacMode |]
+
+pInstanceName :: Field
+pInstanceName =
+  withDoc "A required instance name (for single-instance LUs)" $
+  simpleField "instance_name" [t| String |]
+
+pForceVariant :: Field
+pForceVariant =
+  withDoc "Whether to force an unknown OS variant" $
+  defaultFalse "force_variant"
+
+pWaitForSync :: Field
+pWaitForSync =
+  withDoc "Whether to wait for the disk to synchronize" $
+  defaultTrue "wait_for_sync"
+
+pNameCheck :: Field
+pNameCheck =
+  withDoc "Whether to check name" $
+  defaultTrue "name_check"
+
+pInstBeParams :: Field
+pInstBeParams =
+  withDoc "Backend parameters for instance" .
+  renameField "InstBeParams" .
+  defaultField [| toJSObject [] |] $
+  simpleField "beparams" [t| JSObject JSValue |]
+
+pInstDisks :: Field
+pInstDisks =
+  withDoc "List of instance disks" .
+  renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
+
+pDiskTemplate :: Field
+pDiskTemplate =
+  withDoc "Disk template" $
+  simpleField "disk_template" [t| DiskTemplate |]
+
+pFileDriver :: Field
+pFileDriver =
+  withDoc "Driver for file-backed disks" .
+  optionalField $ simpleField "file_driver" [t| FileDriver |]
+
+pFileStorageDir :: Field
+pFileStorageDir =
+  withDoc "Directory for storing file-backed disks" $
+  optionalNEStringField "file_storage_dir"
+
+pInstHvParams :: Field
+pInstHvParams =
+  withDoc "Hypervisor parameters for instance, hypervisor-dependent" .
+  renameField "InstHvParams" .
+  defaultField [| toJSObject [] |] $
+  simpleField "hvparams" [t| JSObject JSValue |]
+
+pHypervisor :: Field
+pHypervisor =
+  withDoc "Selected hypervisor for an instance" .
+  optionalField $
+  simpleField "hypervisor" [t| Hypervisor |]
+
+pResetDefaults :: Field
+pResetDefaults =
+  withDoc "Reset instance parameters to default if equal" $
+  defaultFalse "identify_defaults"
+
+pIpCheck :: Field
+pIpCheck =
+  withDoc "Whether to ensure instance's IP address is inactive" $
+  defaultTrue "ip_check"
+
+pIpConflictsCheck :: Field
+pIpConflictsCheck =
+  withDoc "Whether to check for conflicting IP addresses" $
+  defaultTrue "conflicts_check"
 
--- | Instance creation mode.
 pInstCreateMode :: Field
 pInstCreateMode =
+  withDoc "Instance creation mode" .
   renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
 
--- | Do not install the OS (will disable automatic start).
+pInstNics :: Field
+pInstNics =
+  withDoc "List of NIC (network interface) definitions" $
+  simpleField "nics" [t| [INicParams] |]
+
 pNoInstall :: Field
-pNoInstall = optionalField $ booleanField "no_install"
+pNoInstall =
+  withDoc "Do not install the OS (will disable automatic start)" .
+  optionalField $ booleanField "no_install"
 
--- | OS type for instance installation.
 pInstOs :: Field
-pInstOs = optionalNEStringField "os_type"
+pInstOs =
+  withDoc "OS type for instance installation" $
+  optionalNEStringField "os_type"
+
+pInstOsParams :: Field
+pInstOsParams =
+  withDoc "OS parameters for instance" .
+  renameField "InstOsParams" .
+  defaultField [| toJSObject [] |] $
+  simpleField "osparams" [t| JSObject JSValue |]
 
--- | Primary node for an instance.
 pPrimaryNode :: Field
-pPrimaryNode = optionalNEStringField "pnode"
+pPrimaryNode =
+  withDoc "Primary node for an instance" $
+  optionalNEStringField "pnode"
+
+pPrimaryNodeUuid :: Field
+pPrimaryNodeUuid =
+  withDoc "Primary node UUID for an instance" $
+  optionalNEStringField "pnode_uuid"
 
--- | Secondary node for an instance.
 pSecondaryNode :: Field
-pSecondaryNode = optionalNEStringField "snode"
+pSecondaryNode =
+  withDoc "Secondary node for an instance" $
+  optionalNEStringField "snode"
+
+pSecondaryNodeUuid :: Field
+pSecondaryNodeUuid =
+  withDoc "Secondary node UUID for an instance" $
+  optionalNEStringField "snode_uuid"
 
--- | Signed handshake from source (remote import only).
 pSourceHandshake :: Field
 pSourceHandshake =
-  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
+  withDoc "Signed handshake from source (remote import only)" .
+  optionalField $ simpleField "source_handshake" [t| [JSValue] |]
 
--- | Source instance name (remote import only).
 pSourceInstance :: Field
-pSourceInstance = optionalNEStringField "source_instance_name"
+pSourceInstance =
+  withDoc "Source instance name (remote import only)" $
+  optionalNEStringField "source_instance_name"
 
--- | How long source instance was given to shut down (remote import only).
 -- FIXME: non-negative int, whereas the constant is a plain int.
 pSourceShutdownTimeout :: Field
 pSourceShutdownTimeout =
+  withDoc "How long source instance was given to shut down (remote import\
+          \ only)" .
   defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
   simpleField "source_shutdown_timeout" [t| NonNegative Int |]
 
--- | Source X509 CA in PEM format (remote import only).
 pSourceX509Ca :: Field
-pSourceX509Ca = optionalNEStringField "source_x509_ca"
+pSourceX509Ca =
+  withDoc "Source X509 CA in PEM format (remote import only)" $
+  optionalNEStringField "source_x509_ca"
 
--- | Source node for import.
 pSrcNode :: Field
-pSrcNode = optionalNEStringField "src_node"
+pSrcNode =
+  withDoc "Source node for import" $
+  optionalNEStringField "src_node"
+
+pSrcNodeUuid :: Field
+pSrcNodeUuid =
+  withDoc "Source node UUID for import" $
+  optionalNEStringField "src_node_uuid"
 
--- | Source directory for import.
 pSrcPath :: Field
-pSrcPath = optionalNEStringField "src_path"
+pSrcPath =
+  withDoc "Source directory for import" $
+  optionalNEStringField "src_path"
 
--- | Whether to start instance after creation.
 pStartInstance :: Field
-pStartInstance = defaultTrue "start"
+pStartInstance =
+  withDoc "Whether to start instance after creation" $
+  defaultTrue "start"
 
--- | Instance tags. FIXME: unify/simplify with pTags, once that
--- migrates to NonEmpty String.
+-- FIXME: unify/simplify with pTags, once that migrates to NonEmpty String"
 pInstTags :: Field
 pInstTags =
+  withDoc "Instance tags" .
   renameField "InstTags" .
   defaultField [| [] |] $
   simpleField "tags" [t| [NonEmptyString] |]
 
--- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
 pMultiAllocInstances :: Field
 pMultiAllocInstances =
+  withDoc "List of instance create opcodes describing the instances to\
+          \ allocate" .
   renameField "InstMultiAlloc" .
   defaultField [| [] |] $
-  simpleField "instances"[t| UncheckedList |]
+  simpleField "instances"[t| [JSValue] |]
+
+pOpportunisticLocking :: Field
+pOpportunisticLocking =
+  withDoc "Whether to employ opportunistic locking for nodes, meaning\
+          \ nodes already locked by another opcode won't be considered for\
+          \ instance allocation (only when an iallocator is used)" $
+  defaultFalse "opportunistic_locking"
+
+pInstanceUuid :: Field
+pInstanceUuid =
+  withDoc "An instance UUID (for single-instance LUs)" .
+  optionalField $ simpleField "instance_uuid" [t| NonEmptyString |]
+
+pTempOsParams :: Field
+pTempOsParams =
+  withDoc "Temporary OS parameters (currently only in reinstall, might be\
+          \ added to install as well)" .
+  renameField "TempOsParams" .
+  optionalField $ simpleField "osparams" [t| JSObject JSValue |]
+
+pShutdownTimeout :: Field
+pShutdownTimeout =
+  withDoc "How long to wait for instance to shut down" .
+  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
+  simpleField "shutdown_timeout" [t| NonNegative Int |]
+
+-- | Another name for the shutdown timeout, because we like to be
+-- inconsistent.
+pShutdownTimeout' :: Field
+pShutdownTimeout' =
+  withDoc "How long to wait for instance to shut down" .
+  renameField "InstShutdownTimeout" .
+  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
+  simpleField "timeout" [t| NonNegative Int |]
 
--- | Ignore failures parameter.
 pIgnoreFailures :: Field
-pIgnoreFailures = defaultFalse "ignore_failures"
+pIgnoreFailures =
+  withDoc "Whether to ignore failures during removal" $
+  defaultFalse "ignore_failures"
 
--- | New instance or cluster name.
 pNewName :: Field
-pNewName = simpleField "new_name" [t| NonEmptyString |]
+pNewName =
+  withDoc "New group or instance name" $
+  simpleField "new_name" [t| NonEmptyString |]
+  
+pIgnoreOfflineNodes :: Field
+pIgnoreOfflineNodes =
+  withDoc "Whether to ignore offline nodes" $
+  defaultFalse "ignore_offline_nodes"
+
+pTempHvParams :: Field
+pTempHvParams =
+  withDoc "Temporary hypervisor parameters, hypervisor-dependent" .
+  renameField "TempHvParams" .
+  defaultField [| toJSObject [] |] $
+  simpleField "hvparams" [t| JSObject JSValue |]
+
+pTempBeParams :: Field
+pTempBeParams =
+  withDoc "Temporary backend parameters" .
+  renameField "TempBeParams" .
+  defaultField [| toJSObject [] |] $
+  simpleField "beparams" [t| JSObject JSValue |]
+
+pNoRemember :: Field
+pNoRemember =
+  withDoc "Do not remember instance state changes" $
+  defaultFalse "no_remember"
+
+pStartupPaused :: Field
+pStartupPaused =
+  withDoc "Pause instance at startup" $
+  defaultFalse "startup_paused"
 
--- | Whether to start the instance even if secondary disks are failing.
 pIgnoreSecondaries :: Field
-pIgnoreSecondaries = defaultFalse "ignore_secondaries"
+pIgnoreSecondaries =
+  withDoc "Whether to start the instance even if secondary disks are failing" $
+  defaultFalse "ignore_secondaries"
 
--- | How to reboot the instance.
 pRebootType :: Field
-pRebootType = simpleField "reboot_type" [t| RebootType |]
+pRebootType =
+  withDoc "How to reboot the instance" $
+  simpleField "reboot_type" [t| RebootType |]
 
--- | Whether to ignore recorded disk size.
-pIgnoreDiskSize :: Field
-pIgnoreDiskSize = defaultFalse "ignore_size"
+pReplaceDisksMode :: Field
+pReplaceDisksMode =
+  withDoc "Replacement mode" .
+  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
+
+pReplaceDisksList :: Field
+pReplaceDisksList =
+  withDoc "List of disk indices" .
+  renameField "ReplaceDisksList" .
+  defaultField [| [] |] $
+  simpleField "disks" [t| [DiskIndex] |]
+
+pMigrationCleanup :: Field
+pMigrationCleanup =
+  withDoc "Whether a previously failed migration should be cleaned up" .
+  renameField "MigrationCleanup" $ defaultFalse "cleanup"
 
--- | Disk list for recreate disks.
+pAllowFailover :: Field
+pAllowFailover =
+  withDoc "Whether we can fallback to failover if migration is not possible" $
+  defaultFalse "allow_failover"
+
+pMoveTargetNode :: Field
+pMoveTargetNode =
+  withDoc "Target node for instance move" .
+  renameField "MoveTargetNode" $
+  simpleField "target_node" [t| NonEmptyString |]
+
+pMoveTargetNodeUuid :: Field
+pMoveTargetNodeUuid =
+  withDoc "Target node UUID for instance move" .
+  renameField "MoveTargetNodeUuid" . optionalField $
+  simpleField "target_node_uuid" [t| NonEmptyString |]
+
+pIgnoreDiskSize :: Field
+pIgnoreDiskSize =
+  withDoc "Whether to ignore recorded disk size" $
+  defaultFalse "ignore_size"
+  
+pWaitForSyncFalse :: Field
+pWaitForSyncFalse =
+  withDoc "Whether to wait for the disk to synchronize (defaults to false)" $
+  defaultField [| False |] pWaitForSync
+  
 pRecreateDisksInfo :: Field
 pRecreateDisksInfo =
+  withDoc "Disk list for recreate disks" .
   renameField "RecreateDisksInfo" .
   defaultField [| RecreateDisksAll |] $
   simpleField "disks" [t| RecreateDisksInfo |]
 
--- | Whether to only return configuration data without querying nodes.
 pStatic :: Field
-pStatic = defaultFalse "static"
+pStatic =
+  withDoc "Whether to only return configuration data without querying nodes" $
+  defaultFalse "static"
 
--- | InstanceSetParams NIC changes.
 pInstParamsNicChanges :: Field
 pInstParamsNicChanges =
+  withDoc "List of NIC changes" .
   renameField "InstNicChanges" .
   defaultField [| SetParamsEmpty |] $
   simpleField "nics" [t| SetParamsMods INicParams |]
 
--- | InstanceSetParams Disk changes.
 pInstParamsDiskChanges :: Field
 pInstParamsDiskChanges =
+  withDoc "List of disk changes" .
   renameField "InstDiskChanges" .
   defaultField [| SetParamsEmpty |] $
   simpleField "disks" [t| SetParamsMods IDiskParams |]
 
--- | New runtime memory.
 pRuntimeMem :: Field
-pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
+pRuntimeMem =
+  withDoc "New runtime memory" .
+  optionalField $ simpleField "runtime_mem" [t| Positive Int |]
+
+pOptDiskTemplate :: Field
+pOptDiskTemplate =
+  withDoc "Instance disk template" .
+  optionalField .
+  renameField "OptDiskTemplate" $
+  simpleField "disk_template" [t| DiskTemplate |]
 
--- | Change the instance's OS without reinstalling the instance
 pOsNameChange :: Field
-pOsNameChange = optionalNEStringField "os_name"
+pOsNameChange =
+  withDoc "Change the instance's OS without reinstalling the instance" $
+  optionalNEStringField "os_name"
 
--- | Disk index for e.g. grow disk.
 pDiskIndex :: Field
-pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
+pDiskIndex =
+  withDoc "Disk index for e.g. grow disk" .
+  renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
 
--- | Disk amount to add or grow to.
 pDiskChgAmount :: Field
 pDiskChgAmount =
+  withDoc "Disk amount to add or grow to" .
   renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
 
--- | Whether the amount parameter is an absolute target or a relative one.
 pDiskChgAbsolute :: Field
-pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
+pDiskChgAbsolute =
+  withDoc
+    "Whether the amount parameter is an absolute target or a relative one" .
+  renameField "DiskChkAbsolute" $ defaultFalse "absolute"
 
--- | Destination group names or UUIDs (defaults to \"all but current group\".
 pTargetGroups :: Field
 pTargetGroups =
+  withDoc
+    "Destination group names or UUIDs (defaults to \"all but current group\")" .
   optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
 
--- | Export mode field.
+pNodeGroupAllocPolicy :: Field
+pNodeGroupAllocPolicy =
+  withDoc "Instance allocation policy" .
+  optionalField $
+  simpleField "alloc_policy" [t| AllocPolicy |]
+
+pGroupNodeParams :: Field
+pGroupNodeParams =
+  withDoc "Default node parameters for group" .
+  optionalField $ simpleField "ndparams" [t| JSObject JSValue |]
+
 pExportMode :: Field
 pExportMode =
+  withDoc "Export mode" .
   renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
 
--- | Export target_node field, depends on mode.
+-- FIXME: Rename target_node as it changes meaning for different
+-- export modes (e.g. "destination")
 pExportTargetNode :: Field
 pExportTargetNode =
+  withDoc "Target node (depends on export mode)" .
   renameField "ExportTarget" $
   simpleField "target_node" [t| ExportTarget |]
 
--- | Whether to remove instance after export.
+pExportTargetNodeUuid :: Field
+pExportTargetNodeUuid =
+  withDoc "Target node UUID (if local export)" .
+  renameField "ExportTargetNodeUuid" . optionalField $
+  simpleField "target_node_uuid" [t| NonEmptyString |]
+
+pShutdownInstance :: Field
+pShutdownInstance =
+  withDoc "Whether to shutdown the instance before export" $
+  defaultTrue "shutdown"
+
 pRemoveInstance :: Field
-pRemoveInstance = defaultFalse "remove_instance"
+pRemoveInstance =
+  withDoc "Whether to remove instance after export" $
+  defaultFalse "remove_instance"
 
--- | Whether to ignore failures while removing instances.
 pIgnoreRemoveFailures :: Field
-pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
+pIgnoreRemoveFailures =
+  withDoc "Whether to ignore failures while removing instances" $
+  defaultFalse "ignore_remove_failures"
 
--- | Name of X509 key (remote export only).
 pX509KeyName :: Field
-pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
+pX509KeyName =
+  withDoc "Name of X509 key (remote export only)" .
+  optionalField $ simpleField "x509_key_name" [t| [JSValue] |]
 
--- | Destination X509 CA (remote export only).
 pX509DestCA :: Field
-pX509DestCA = optionalNEStringField "destination_x509_ca"
+pX509DestCA =
+  withDoc "Destination X509 CA (remote export only)" $
+  optionalNEStringField "destination_x509_ca"
 
--- | Search pattern (regular expression). FIXME: this should be
--- compiled at load time?
-pTagSearchPattern :: Field
-pTagSearchPattern =
-  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
-
--- | Restricted command name.
-pRestrictedCommand :: Field
-pRestrictedCommand =
-  renameField "RestrictedCommand" $
-  simpleField "command" [t| NonEmptyString |]
-
--- | Replace disks mode.
-pReplaceDisksMode :: Field
-pReplaceDisksMode =
-  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
+pTagsObject :: Field
+pTagsObject =
+  withDoc "Tag kind" $
+  simpleField "kind" [t| TagKind |]
 
--- | List of disk indices.
-pReplaceDisksList :: Field
-pReplaceDisksList =
-  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
+pTagsName :: Field
+pTagsName =
+  withDoc "Name of object" .
+  renameField "TagsGetName" .
+  optionalField $ simpleField "name" [t| String |]
 
--- | Whether do allow failover in migrations.
-pAllowFailover :: Field
-pAllowFailover = defaultFalse "allow_failover"
+pTagsList :: Field
+pTagsList =
+  withDoc "List of tag names" $
+  simpleField "tags" [t| [String] |]
 
--- * Test opcode parameters
+-- FIXME: this should be compiled at load time?
+pTagSearchPattern :: Field
+pTagSearchPattern =
+  withDoc "Search pattern (regular expression)" .
+  renameField "TagSearchPattern" $
+  simpleField "pattern" [t| NonEmptyString |]
 
--- | Duration parameter for 'OpTestDelay'.
 pDelayDuration :: Field
 pDelayDuration =
-  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
+  withDoc "Duration parameter for 'OpTestDelay'" .
+  renameField "DelayDuration" $
+  simpleField "duration" [t| Double |]
 
--- | on_master field for 'OpTestDelay'.
 pDelayOnMaster :: Field
-pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
+pDelayOnMaster =
+  withDoc "on_master field for 'OpTestDelay'" .
+  renameField "DelayOnMaster" $
+  defaultTrue "on_master"
 
--- | on_nodes field for 'OpTestDelay'.
 pDelayOnNodes :: Field
 pDelayOnNodes =
+  withDoc "on_nodes field for 'OpTestDelay'" .
   renameField "DelayOnNodes" .
   defaultField [| [] |] $
   simpleField "on_nodes" [t| [NonEmptyString] |]
 
--- | Repeat parameter for OpTestDelay.
+pDelayOnNodeUuids :: Field
+pDelayOnNodeUuids =
+  withDoc "on_node_uuids field for 'OpTestDelay'" .
+  renameField "DelayOnNodeUuids" . optionalField $
+  simpleField "on_node_uuids" [t| [NonEmptyString] |]
+
 pDelayRepeat :: Field
 pDelayRepeat =
+  withDoc "Repeat parameter for OpTestDelay" .
   renameField "DelayRepeat" .
   defaultField [| forceNonNeg (0::Int) |] $
   simpleField "repeat" [t| NonNegative Int |]
 
--- | IAllocator test direction.
 pIAllocatorDirection :: Field
 pIAllocatorDirection =
+  withDoc "IAllocator test direction" .
   renameField "IAllocatorDirection" $
   simpleField "direction" [t| IAllocatorTestDir |]
 
--- | IAllocator test mode.
 pIAllocatorMode :: Field
 pIAllocatorMode =
+  withDoc "IAllocator test mode" .
   renameField "IAllocatorMode" $
   simpleField "mode" [t| IAllocatorMode |]
 
--- | IAllocator target name (new instance, node to evac, etc.).
 pIAllocatorReqName :: Field
 pIAllocatorReqName =
+  withDoc "IAllocator target name (new instance, node to evac, etc.)" .
   renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
 
--- | Custom OpTestIAllocator nics.
 pIAllocatorNics :: Field
 pIAllocatorNics =
-  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
+  withDoc "Custom OpTestIAllocator nics" .
+  renameField "IAllocatorNics" .
+  optionalField $ simpleField "nics" [t| [INicParams] |]
 
--- | Custom OpTestAllocator disks.
 pIAllocatorDisks :: Field
 pIAllocatorDisks =
-  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
+  withDoc "Custom OpTestAllocator disks" .
+  renameField "IAllocatorDisks" .
+  optionalField $ simpleField "disks" [t| [JSValue] |]
 
--- | IAllocator memory field.
 pIAllocatorMemory :: Field
 pIAllocatorMemory =
+  withDoc "IAllocator memory field" .
   renameField "IAllocatorMem" .
   optionalField $
   simpleField "memory" [t| NonNegative Int |]
 
--- | IAllocator vcpus field.
 pIAllocatorVCpus :: Field
 pIAllocatorVCpus =
+  withDoc "IAllocator vcpus field" .
   renameField "IAllocatorVCpus" .
   optionalField $
   simpleField "vcpus" [t| NonNegative Int |]
 
--- | IAllocator os field.
 pIAllocatorOs :: Field
-pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
+pIAllocatorOs =
+  withDoc "IAllocator os field" .
+  renameField "IAllocatorOs" $ optionalNEStringField "os"
 
--- | IAllocator instances field.
 pIAllocatorInstances :: Field
 pIAllocatorInstances =
+  withDoc "IAllocator instances field" .
   renameField "IAllocatorInstances " .
   optionalField $
   simpleField "instances" [t| [NonEmptyString] |]
 
--- | IAllocator evac mode.
 pIAllocatorEvacMode :: Field
 pIAllocatorEvacMode =
+  withDoc "IAllocator evac mode" .
   renameField "IAllocatorEvacMode" .
   optionalField $
-  simpleField "evac_mode" [t| NodeEvacMode |]
+  simpleField "evac_mode" [t| EvacMode |]
 
--- | IAllocator spindle use.
 pIAllocatorSpindleUse :: Field
 pIAllocatorSpindleUse =
+  withDoc "IAllocator spindle use" .
   renameField "IAllocatorSpindleUse" .
   defaultField [| forceNonNeg (1::Int) |] $
   simpleField "spindle_use" [t| NonNegative Int |]
 
--- | IAllocator count field.
 pIAllocatorCount :: Field
 pIAllocatorCount =
+  withDoc "IAllocator count field" .
   renameField "IAllocatorCount" .
   defaultField [| forceNonNeg (1::Int) |] $
   simpleField "count" [t| NonNegative Int |]
 
--- | 'OpTestJqueue' notify_waitlock.
 pJQueueNotifyWaitLock :: Field
-pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
+pJQueueNotifyWaitLock =
+  withDoc "'OpTestJqueue' notify_waitlock" $
+  defaultFalse "notify_waitlock"
 
--- | 'OpTestJQueue' notify_exec.
 pJQueueNotifyExec :: Field
-pJQueueNotifyExec = defaultFalse "notify_exec"
+pJQueueNotifyExec =
+  withDoc "'OpTestJQueue' notify_exec" $
+  defaultFalse "notify_exec"
 
--- | 'OpTestJQueue' log_messages.
 pJQueueLogMessages :: Field
 pJQueueLogMessages =
+  withDoc "'OpTestJQueue' log_messages" .
   defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
 
--- | 'OpTestJQueue' fail attribute.
 pJQueueFail :: Field
 pJQueueFail =
+  withDoc "'OpTestJQueue' fail attribute" .
   renameField "JQueueFail" $ defaultFalse "fail"
 
--- | 'OpTestDummy' result field.
 pTestDummyResult :: Field
 pTestDummyResult =
-  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
+  withDoc "'OpTestDummy' result field" .
+  renameField "TestDummyResult" $ simpleField "result" [t| JSValue |]
 
--- | 'OpTestDummy' messages field.
 pTestDummyMessages :: Field
 pTestDummyMessages =
+  withDoc "'OpTestDummy' messages field" .
   renameField "TestDummyMessages" $
-  simpleField "messages" [t| UncheckedValue |]
+  simpleField "messages" [t| JSValue |]
 
--- | 'OpTestDummy' fail field.
 pTestDummyFail :: Field
 pTestDummyFail =
-  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
+  withDoc "'OpTestDummy' fail field" .
+  renameField "TestDummyFail" $ simpleField "fail" [t| JSValue |]
 
--- | 'OpTestDummy' submit_jobs field.
 pTestDummySubmitJobs :: Field
 pTestDummySubmitJobs =
+  withDoc "'OpTestDummy' submit_jobs field" .
   renameField "TestDummySubmitJobs" $
-  simpleField "submit_jobs" [t| UncheckedValue |]
-
--- * Network parameters
+  simpleField "submit_jobs" [t| JSValue |]
 
--- | Network name.
 pNetworkName :: Field
-pNetworkName = simpleField "network_name" [t| NonEmptyString |]
+pNetworkName =
+  withDoc "Network name" $
+  simpleField "network_name" [t| NonEmptyString |]
 
--- | Network address (IPv4 subnet). FIXME: no real type for this.
 pNetworkAddress4 :: Field
 pNetworkAddress4 =
+  withDoc "Network address (IPv4 subnet)" .
   renameField "NetworkAddress4" $
-  simpleField "network" [t| NonEmptyString |]
+  simpleField "network" [t| IPv4Network |]
 
--- | Network gateway (IPv4 address). FIXME: no real type for this.
 pNetworkGateway4 :: Field
 pNetworkGateway4 =
-  renameField "NetworkGateway4" $
-  optionalNEStringField "gateway"
+  withDoc "Network gateway (IPv4 address)" .
+  renameField "NetworkGateway4" .
+  optionalField $ simpleField "gateway" [t| IPv4Address |]
 
--- | Network address (IPv6 subnet). FIXME: no real type for this.
 pNetworkAddress6 :: Field
 pNetworkAddress6 =
-  renameField "NetworkAddress6" $
-  optionalNEStringField "network6"
+  withDoc "Network address (IPv6 subnet)" .
+  renameField "NetworkAddress6" .
+  optionalField $ simpleField "network6" [t| IPv6Network |]
 
--- | Network gateway (IPv6 address). FIXME: no real type for this.
 pNetworkGateway6 :: Field
 pNetworkGateway6 =
-  renameField "NetworkGateway6" $
-  optionalNEStringField "gateway6"
+  withDoc "Network gateway (IPv6 address)" .
+  renameField "NetworkGateway6" .
+  optionalField $ simpleField "gateway6" [t| IPv6Address |]
 
--- | Network specific mac prefix (that overrides the cluster one).
 pNetworkMacPrefix :: Field
 pNetworkMacPrefix =
+  withDoc "Network specific mac prefix (that overrides the cluster one)" .
   renameField "NetMacPrefix" $
   optionalNEStringField "mac_prefix"
 
--- | Network add reserved IPs.
 pNetworkAddRsvdIps :: Field
 pNetworkAddRsvdIps =
+  withDoc "Which IP addresses to reserve" .
   renameField "NetworkAddRsvdIps" .
   optionalField $
-  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
+  simpleField "add_reserved_ips" [t| [IPv4Address] |]
 
--- | Network remove reserved IPs.
 pNetworkRemoveRsvdIps :: Field
 pNetworkRemoveRsvdIps =
+  withDoc "Which external IP addresses to release" .
   renameField "NetworkRemoveRsvdIps" .
   optionalField $
-  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
+  simpleField "remove_reserved_ips" [t| [IPv4Address] |]
 
--- | Network mode when connecting to a group.
 pNetworkMode :: Field
-pNetworkMode = simpleField "network_mode" [t| NICMode |]
+pNetworkMode =
+  withDoc "Network mode when connecting to a group" $
+  simpleField "network_mode" [t| NICMode |]
 
--- | Network link when connecting to a group.
 pNetworkLink :: Field
-pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
-
--- * Common opcode parameters
-
--- | Run checks only, don't execute.
-pDryRun :: Field
-pDryRun = optionalField $ booleanField "dry_run"
-
--- | Debug level.
-pDebugLevel :: Field
-pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
-
--- | Opcode priority. Note: python uses a separate constant, we're
--- using the actual value we know it's the default.
-pOpPriority :: Field
-pOpPriority =
-  defaultField [| OpPrioNormal |] $
-  simpleField "priority" [t| OpSubmitPriority |]
-
--- | Job dependencies.
-pDependencies :: Field
-pDependencies =
-  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
-
--- | Comment field.
-pComment :: Field
-pComment = optionalNullSerField $ stringField "comment"
-
--- | Reason trail field.
-pReason :: Field
-pReason = simpleField C.opcodeReason [t| ReasonTrail |]
-
--- * Entire opcode parameter list
-
--- | Old-style query opcode, with locking.
-dOldQuery :: [Field]
-dOldQuery =
-  [ pOutputFields
-  , pNames
-  , pUseLocking
-  ]
-
--- | Old-style query opcode, without locking.
-dOldQueryNoLocking :: [Field]
-dOldQueryNoLocking =
-  [ pOutputFields
-  , pNames
-  ]
+pNetworkLink =
+  withDoc "Network link when connecting to a group" $
+  simpleField "network_link" [t| NonEmptyString |]