Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ da4a52a3

History | View | Annotate | Download (44.7 kB)

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
  ( TagType(..)
36
  , TagObject(..)
37
  , tagObjectFrom
38
  , tagNameOf
39
  , decodeTagObject
40
  , encodeTagObject
41
  , ReplaceDisksMode(..)
42
  , DiskIndex
43
  , mkDiskIndex
44
  , unDiskIndex
45
  , DiskAccess(..)
46
  , INicParams(..)
47
  , IDiskParams(..)
48
  , RecreateDisksInfo(..)
49
  , DdmOldChanges(..)
50
  , SetParamsMods(..)
51
  , ExportTarget(..)
52
  , pInstanceName
53
  , pInstanceUuid
54
  , pInstances
55
  , pName
56
  , pTagsList
57
  , pTagsObject
58
  , pOutputFields
59
  , pShutdownTimeout
60
  , pShutdownTimeout'
61
  , pShutdownInstance
62
  , pForce
63
  , pIgnoreOfflineNodes
64
  , pNodeName
65
  , pNodeUuid
66
  , pNodeNames
67
  , pNodeUuids
68
  , pGroupName
69
  , pMigrationMode
70
  , pMigrationLive
71
  , pMigrationCleanup
72
  , pForceVariant
73
  , pWaitForSync
74
  , pWaitForSyncFalse
75
  , pIgnoreConsistency
76
  , pStorageName
77
  , pUseLocking
78
  , pOpportunisticLocking
79
  , pNameCheck
80
  , pNodeGroupAllocPolicy
81
  , pGroupNodeParams
82
  , pQueryWhat
83
  , pEarlyRelease
84
  , pIpCheck
85
  , pIpConflictsCheck
86
  , pNoRemember
87
  , pMigrationTargetNode
88
  , pMigrationTargetNodeUuid
89
  , pMoveTargetNode
90
  , pMoveTargetNodeUuid
91
  , pStartupPaused
92
  , pVerbose
93
  , pDebugSimulateErrors
94
  , pErrorCodes
95
  , pSkipChecks
96
  , pIgnoreErrors
97
  , pOptGroupName
98
  , pDiskParams
99
  , pHvState
100
  , pDiskState
101
  , pIgnoreIpolicy
102
  , pAllowRuntimeChgs
103
  , pInstDisks
104
  , pDiskTemplate
105
  , pOptDiskTemplate
106
  , pFileDriver
107
  , pFileStorageDir
108
  , pVgName
109
  , pEnabledHypervisors
110
  , pHypervisor
111
  , pClusterHvParams
112
  , pInstHvParams
113
  , pClusterBeParams
114
  , pInstBeParams
115
  , pResetDefaults
116
  , pOsHvp
117
  , pClusterOsParams
118
  , pInstOsParams
119
  , pCandidatePoolSize
120
  , pUidPool
121
  , pAddUids
122
  , pRemoveUids
123
  , pMaintainNodeHealth
124
  , pPreallocWipeDisks
125
  , pNicParams
126
  , pInstNics
127
  , pNdParams
128
  , pIpolicy
129
  , pDrbdHelper
130
  , pDefaultIAllocator
131
  , pMasterNetdev
132
  , pMasterNetmask
133
  , pReservedLvs
134
  , pHiddenOs
135
  , pBlacklistedOs
136
  , pUseExternalMipScript
137
  , pQueryFields
138
  , pQueryFilter
139
  , pOobCommand
140
  , pOobTimeout
141
  , pIgnoreStatus
142
  , pPowerDelay
143
  , pPrimaryIp
144
  , pSecondaryIp
145
  , pReadd
146
  , pNodeGroup
147
  , pMasterCapable
148
  , pVmCapable
149
  , pNames
150
  , pNodes
151
  , pRequiredNodes
152
  , pRequiredNodeUuids
153
  , pStorageType
154
  , pStorageChanges
155
  , pMasterCandidate
156
  , pOffline
157
  , pDrained
158
  , pAutoPromote
159
  , pPowered
160
  , pIallocator
161
  , pRemoteNode
162
  , pRemoteNodeUuid
163
  , pEvacMode
164
  , pInstCreateMode
165
  , pNoInstall
166
  , pInstOs
167
  , pPrimaryNode
168
  , pPrimaryNodeUuid
169
  , pSecondaryNode
170
  , pSecondaryNodeUuid
171
  , pSourceHandshake
172
  , pSourceInstance
173
  , pSourceShutdownTimeout
174
  , pSourceX509Ca
175
  , pSrcNode
176
  , pSrcNodeUuid
177
  , pSrcPath
178
  , pStartInstance
179
  , pInstTags
180
  , pMultiAllocInstances
181
  , pTempOsParams
182
  , pTempHvParams
183
  , pTempBeParams
184
  , pIgnoreFailures
185
  , pNewName
186
  , pIgnoreSecondaries
187
  , pRebootType
188
  , pIgnoreDiskSize
189
  , pRecreateDisksInfo
190
  , pStatic
191
  , pInstParamsNicChanges
192
  , pInstParamsDiskChanges
193
  , pRuntimeMem
194
  , pOsNameChange
195
  , pDiskIndex
196
  , pDiskChgAmount
197
  , pDiskChgAbsolute
198
  , pTargetGroups
199
  , pExportMode
200
  , pExportTargetNode
201
  , pExportTargetNodeUuid
202
  , pRemoveInstance
203
  , pIgnoreRemoveFailures
204
  , pX509KeyName
205
  , pX509DestCA
206
  , pTagSearchPattern
207
  , pRestrictedCommand
208
  , pReplaceDisksMode
209
  , pReplaceDisksList
210
  , pAllowFailover
211
  , pDelayDuration
212
  , pDelayOnMaster
213
  , pDelayOnNodes
214
  , pDelayOnNodeUuids
215
  , pDelayRepeat
216
  , pIAllocatorDirection
217
  , pIAllocatorMode
218
  , pIAllocatorReqName
219
  , pIAllocatorNics
220
  , pIAllocatorDisks
221
  , pIAllocatorMemory
222
  , pIAllocatorVCpus
223
  , pIAllocatorOs
224
  , pIAllocatorInstances
225
  , pIAllocatorEvacMode
226
  , pIAllocatorSpindleUse
227
  , pIAllocatorCount
228
  , pJQueueNotifyWaitLock
229
  , pJQueueNotifyExec
230
  , pJQueueLogMessages
231
  , pJQueueFail
232
  , pTestDummyResult
233
  , pTestDummyMessages
234
  , pTestDummyFail
235
  , pTestDummySubmitJobs
236
  , pNetworkName
237
  , pNetworkAddress4
238
  , pNetworkGateway4
239
  , pNetworkAddress6
240
  , pNetworkGateway6
241
  , pNetworkMacPrefix
242
  , pNetworkAddRsvdIps
243
  , pNetworkRemoveRsvdIps
244
  , pNetworkMode
245
  , pNetworkLink
246
  , pDryRun
247
  , pDebugLevel
248
  , pOpPriority
249
  , pDependencies
250
  , pComment
251
  , pReason
252
  , pEnabledDiskTemplates
253
  , dOldQuery
254
  , dOldQueryNoLocking
255
  ) where
256

    
257
import Control.Monad (liftM)
258
import qualified Data.Set as Set
259
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
260
                  JSObject, toJSObject)
261
import qualified Text.JSON
262
import Text.JSON.Pretty (pp_value)
263

    
264
import Ganeti.BasicTypes
265
import qualified Ganeti.Constants as C
266
import Ganeti.THH
267
import Ganeti.JSON
268
import Ganeti.Types
269
import qualified Ganeti.Query.Language as Qlang
270

    
271
-- * Helper functions and types
272

    
273
-- * Type aliases
274

    
275
-- | Build a boolean field.
276
booleanField :: String -> Field
277
booleanField = flip simpleField [t| Bool |]
278

    
279
-- | Default a field to 'False'.
280
defaultFalse :: String -> Field
281
defaultFalse = defaultField [| False |] . booleanField
282

    
283
-- | Default a field to 'True'.
284
defaultTrue :: String -> Field
285
defaultTrue = defaultField [| True |] . booleanField
286

    
287
-- | An alias for a 'String' field.
288
stringField :: String -> Field
289
stringField = flip simpleField [t| String |]
290

    
291
-- | An alias for an optional string field.
292
optionalStringField :: String -> Field
293
optionalStringField = optionalField . stringField
294

    
295
-- | An alias for an optional non-empty string field.
296
optionalNEStringField :: String -> Field
297
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
298

    
299
-- | Unchecked value, should be replaced by a better definition.
300
type UncheckedValue = JSValue
301

    
302
-- | Unchecked dict, should be replaced by a better definition.
303
type UncheckedDict = JSObject JSValue
304

    
305
-- | Unchecked list, shoild be replaced by a better definition.
306
type UncheckedList = [JSValue]
307

    
308
-- | Function to force a non-negative value, without returning via a
309
-- monad. This is needed for, and should be used /only/ in the case of
310
-- forcing constants. In case the constant is wrong (< 0), this will
311
-- become a runtime error.
312
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
313
forceNonNeg i = case mkNonNegative i of
314
                  Ok n -> n
315
                  Bad msg -> error msg
316

    
317
-- ** Tags
318

    
319
-- | Data type representing what items do the tag operations apply to.
320
$(declareSADT "TagType"
321
  [ ("TagTypeInstance", 'C.tagInstance)
322
  , ("TagTypeNode",     'C.tagNode)
323
  , ("TagTypeGroup",    'C.tagNodegroup)
324
  , ("TagTypeCluster",  'C.tagCluster)
325
  ])
326
$(makeJSONInstance ''TagType)
327

    
328
-- | Data type holding a tag object (type and object name).
329
data TagObject = TagInstance String
330
               | TagNode     String
331
               | TagGroup    String
332
               | TagCluster
333
               deriving (Show, Eq)
334

    
335
-- | Tag type for a given tag object.
336
tagTypeOf :: TagObject -> TagType
337
tagTypeOf (TagInstance {}) = TagTypeInstance
338
tagTypeOf (TagNode     {}) = TagTypeNode
339
tagTypeOf (TagGroup    {}) = TagTypeGroup
340
tagTypeOf (TagCluster  {}) = TagTypeCluster
341

    
342
-- | Gets the potential tag object name.
343
tagNameOf :: TagObject -> Maybe String
344
tagNameOf (TagInstance s) = Just s
345
tagNameOf (TagNode     s) = Just s
346
tagNameOf (TagGroup    s) = Just s
347
tagNameOf  TagCluster     = Nothing
348

    
349
-- | Builds a 'TagObject' from a tag type and name.
350
tagObjectFrom :: (Monad m) => TagType -> JSValue -> m TagObject
351
tagObjectFrom TagTypeInstance (JSString s) =
352
  return . TagInstance $ fromJSString s
353
tagObjectFrom TagTypeNode     (JSString s) = return . TagNode $ fromJSString s
354
tagObjectFrom TagTypeGroup    (JSString s) = return . TagGroup $ fromJSString s
355
tagObjectFrom TagTypeCluster   JSNull      = return TagCluster
356
tagObjectFrom t v =
357
  fail $ "Invalid tag type/name combination: " ++ show t ++ "/" ++
358
         show (pp_value v)
359

    
360
-- | Name of the tag \"name\" field.
361
tagNameField :: String
362
tagNameField = "name"
363

    
364
-- | Custom encoder for 'TagObject' as represented in an opcode.
365
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
366
encodeTagObject t = ( showJSON (tagTypeOf t)
367
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
368

    
369
-- | Custom decoder for 'TagObject' as represented in an opcode.
370
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
371
decodeTagObject obj kind = do
372
  ttype <- fromJVal kind
373
  tname <- fromObj obj tagNameField
374
  tagObjectFrom ttype tname
375

    
376
-- ** Disks
377

    
378
-- | Replace disks type.
379
$(declareSADT "ReplaceDisksMode"
380
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
381
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
382
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
383
  , ("ReplaceAuto",         'C.replaceDiskAuto)
384
  ])
385
$(makeJSONInstance ''ReplaceDisksMode)
386

    
387
-- | Disk index type (embedding constraints on the index value via a
388
-- smart constructor).
389
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
390
  deriving (Show, Eq, Ord)
391

    
392
-- | Smart constructor for 'DiskIndex'.
393
mkDiskIndex :: (Monad m) => Int -> m DiskIndex
394
mkDiskIndex i | i >= 0 && i < C.maxDisks = return (DiskIndex i)
395
              | otherwise = fail $ "Invalid value for disk index '" ++
396
                            show i ++ "', required between 0 and " ++
397
                            show C.maxDisks
398

    
399
instance JSON DiskIndex where
400
  readJSON v = readJSON v >>= mkDiskIndex
401
  showJSON = showJSON . unDiskIndex
402

    
403
-- ** I* param types
404

    
405
-- | Type holding disk access modes.
406
$(declareSADT "DiskAccess"
407
  [ ("DiskReadOnly",  'C.diskRdonly)
408
  , ("DiskReadWrite", 'C.diskRdwr)
409
  ])
410
$(makeJSONInstance ''DiskAccess)
411

    
412
-- | NIC modification definition.
413
$(buildObject "INicParams" "inic"
414
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
415
  , optionalField $ simpleField C.inicIp   [t| String         |]
416
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
417
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
418
  , optionalField $ simpleField C.inicName [t| NonEmptyString |]
419
  ])
420

    
421
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
422
$(buildObject "IDiskParams" "idisk"
423
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
424
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
425
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
426
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
427
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
428
  , optionalField $ simpleField C.idiskName   [t| NonEmptyString |]
429
  ])
430

    
431
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
432
-- strange, because the type in Python is something like Either
433
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
434
-- empty list in JSON, so we have to add a custom case for the empty
435
-- list.
436
data RecreateDisksInfo
437
  = RecreateDisksAll
438
  | RecreateDisksIndices (NonEmpty DiskIndex)
439
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
440
    deriving (Eq, Show)
441

    
442
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
443
readRecreateDisks (JSArray []) = return RecreateDisksAll
444
readRecreateDisks v =
445
  case readJSON v::Text.JSON.Result [DiskIndex] of
446
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
447
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
448
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
449
           _ -> fail $ "Can't parse disk information as either list of disk"
450
                ++ " indices or list of disk parameters; value received:"
451
                ++ show (pp_value v)
452

    
453
instance JSON RecreateDisksInfo where
454
  readJSON = readRecreateDisks
455
  showJSON  RecreateDisksAll            = showJSON ()
456
  showJSON (RecreateDisksIndices idx)   = showJSON idx
457
  showJSON (RecreateDisksParams params) = showJSON params
458

    
459
-- | Simple type for old-style ddm changes.
460
data DdmOldChanges = DdmOldIndex (NonNegative Int)
461
                   | DdmOldMod DdmSimple
462
                     deriving (Eq, Show)
463

    
464
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
465
readDdmOldChanges v =
466
  case readJSON v::Text.JSON.Result (NonNegative Int) of
467
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
468
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
469
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
470
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
471
                ++ " either index or modification"
472

    
473
instance JSON DdmOldChanges where
474
  showJSON (DdmOldIndex i) = showJSON i
475
  showJSON (DdmOldMod m)   = showJSON m
476
  readJSON = readDdmOldChanges
477

    
478
-- | Instance disk or nic modifications.
479
data SetParamsMods a
480
  = SetParamsEmpty
481
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
482
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
483
    deriving (Eq, Show)
484

    
485
-- | Custom deserialiser for 'SetParamsMods'.
486
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
487
readSetParams (JSArray []) = return SetParamsEmpty
488
readSetParams v =
489
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
490
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
491
    _ -> liftM SetParamsNew $ readJSON v
492

    
493
instance (JSON a) => JSON (SetParamsMods a) where
494
  showJSON SetParamsEmpty = showJSON ()
495
  showJSON (SetParamsDeprecated v) = showJSON v
496
  showJSON (SetParamsNew v) = showJSON v
497
  readJSON = readSetParams
498

    
499
-- | Custom type for target_node parameter of OpBackupExport, which
500
-- varies depending on mode. FIXME: this uses an UncheckedList since
501
-- we don't care about individual rows (just like the Python code
502
-- tests). But the proper type could be parsed if we wanted.
503
data ExportTarget = ExportTargetLocal NonEmptyString
504
                  | ExportTargetRemote UncheckedList
505
                    deriving (Eq, Show)
506

    
507
-- | Custom reader for 'ExportTarget'.
508
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
509
readExportTarget (JSString s) = liftM ExportTargetLocal $
510
                                mkNonEmpty (fromJSString s)
511
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
512
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
513
                     show (pp_value v)
514

    
515
instance JSON ExportTarget where
516
  showJSON (ExportTargetLocal s)  = showJSON s
517
  showJSON (ExportTargetRemote l) = showJSON l
518
  readJSON = readExportTarget
519

    
520
-- * Parameters
521

    
522
-- | A required instance name (for single-instance LUs).
523
pInstanceName :: Field
524
pInstanceName = simpleField "instance_name" [t| String |]
525

    
526
-- | An instance UUID (for single-instance LUs).
527
pInstanceUuid :: Field
528
pInstanceUuid = optionalField $ simpleField "instance_uuid" [t| String |]
529

    
530
-- | A list of instances.
531
pInstances :: Field
532
pInstances = defaultField [| [] |] $
533
             simpleField "instances" [t| [NonEmptyString] |]
534

    
535
-- | A generic name.
536
pName :: Field
537
pName = simpleField "name" [t| NonEmptyString |]
538

    
539
-- | Tags list.
540
pTagsList :: Field
541
pTagsList = simpleField "tags" [t| [String] |]
542

    
543
-- | Tags object.
544
pTagsObject :: Field
545
pTagsObject =
546
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
547
  simpleField "kind" [t| TagObject |]
548

    
549
-- | Selected output fields.
550
pOutputFields :: Field
551
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
552

    
553
-- | How long to wait for instance to shut down.
554
pShutdownTimeout :: Field
555
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
556
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
557

    
558
-- | Another name for the shutdown timeout, because we like to be
559
-- inconsistent.
560
pShutdownTimeout' :: Field
561
pShutdownTimeout' =
562
  renameField "InstShutdownTimeout" .
563
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
564
  simpleField "timeout" [t| NonNegative Int |]
565

    
566
-- | Whether to shutdown the instance in backup-export.
567
pShutdownInstance :: Field
568
pShutdownInstance = defaultTrue "shutdown"
569

    
570
-- | Whether to force the operation.
571
pForce :: Field
572
pForce = defaultFalse "force"
573

    
574
-- | Whether to ignore offline nodes.
575
pIgnoreOfflineNodes :: Field
576
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
577

    
578
-- | A required node name (for single-node LUs).
579
pNodeName :: Field
580
pNodeName = simpleField "node_name" [t| NonEmptyString |]
581

    
582
-- | A node UUID (for single-node LUs).
583
pNodeUuid :: Field
584
pNodeUuid = optionalField $ simpleField "node_uuid" [t| NonEmptyString |]
585

    
586
-- | List of nodes.
587
pNodeNames :: Field
588
pNodeNames =
589
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
590

    
591
-- | List of node UUIDs.
592
pNodeUuids :: Field
593
pNodeUuids =
594
  optionalField $ simpleField "node_uuids" [t| [NonEmptyString] |]
595

    
596
-- | A required node group name (for single-group LUs).
597
pGroupName :: Field
598
pGroupName = simpleField "group_name" [t| NonEmptyString |]
599

    
600
-- | Migration type (live\/non-live).
601
pMigrationMode :: Field
602
pMigrationMode =
603
  renameField "MigrationMode" .
604
  optionalField $
605
  simpleField "mode" [t| MigrationMode |]
606

    
607
-- | Obsolete \'live\' migration mode (boolean).
608
pMigrationLive :: Field
609
pMigrationLive =
610
  renameField "OldLiveMode" . optionalField $ booleanField "live"
611

    
612
-- | Migration cleanup parameter.
613
pMigrationCleanup :: Field
614
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
615

    
616
-- | Whether to force an unknown OS variant.
617
pForceVariant :: Field
618
pForceVariant = defaultFalse "force_variant"
619

    
620
-- | Whether to wait for the disk to synchronize.
621
pWaitForSync :: Field
622
pWaitForSync = defaultTrue "wait_for_sync"
623

    
624
-- | Whether to wait for the disk to synchronize (defaults to false).
625
pWaitForSyncFalse :: Field
626
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
627

    
628
-- | Whether to ignore disk consistency
629
pIgnoreConsistency :: Field
630
pIgnoreConsistency = defaultFalse "ignore_consistency"
631

    
632
-- | Storage name.
633
pStorageName :: Field
634
pStorageName =
635
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
636

    
637
-- | Whether to use synchronization.
638
pUseLocking :: Field
639
pUseLocking = defaultFalse "use_locking"
640

    
641
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
642
-- locked by another opcode won't be considered for instance allocation (only
643
-- when an iallocator is used).
644
pOpportunisticLocking :: Field
645
pOpportunisticLocking = defaultFalse "opportunistic_locking"
646

    
647
-- | Whether to check name.
648
pNameCheck :: Field
649
pNameCheck = defaultTrue "name_check"
650

    
651
-- | Instance allocation policy.
652
pNodeGroupAllocPolicy :: Field
653
pNodeGroupAllocPolicy = optionalField $
654
                        simpleField "alloc_policy" [t| AllocPolicy |]
655

    
656
-- | Default node parameters for group.
657
pGroupNodeParams :: Field
658
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
659

    
660
-- | Resource(s) to query for.
661
pQueryWhat :: Field
662
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
663

    
664
-- | Whether to release locks as soon as possible.
665
pEarlyRelease :: Field
666
pEarlyRelease = defaultFalse "early_release"
667

    
668
-- | Whether to ensure instance's IP address is inactive.
669
pIpCheck :: Field
670
pIpCheck = defaultTrue "ip_check"
671

    
672
-- | Check for conflicting IPs.
673
pIpConflictsCheck :: Field
674
pIpConflictsCheck = defaultTrue "conflicts_check"
675

    
676
-- | Do not remember instance state changes.
677
pNoRemember :: Field
678
pNoRemember = defaultFalse "no_remember"
679

    
680
-- | Target node for instance migration/failover.
681
pMigrationTargetNode :: Field
682
pMigrationTargetNode = optionalNEStringField "target_node"
683

    
684
-- | Target node UUID for instance migration/failover.
685
pMigrationTargetNodeUuid :: Field
686
pMigrationTargetNodeUuid = optionalNEStringField "target_node_uuid"
687

    
688
-- | Target node for instance move (required).
689
pMoveTargetNode :: Field
690
pMoveTargetNode =
691
  renameField "MoveTargetNode" $
692
  simpleField "target_node" [t| NonEmptyString |]
693

    
694
-- | Target node UUID for instance move.
695
pMoveTargetNodeUuid :: Field
696
pMoveTargetNodeUuid =
697
  renameField "MoveTargetNodeUuid" . optionalField $
698
  simpleField "target_node_uuid" [t| NonEmptyString |]
699

    
700
-- | Pause instance at startup.
701
pStartupPaused :: Field
702
pStartupPaused = defaultFalse "startup_paused"
703

    
704
-- | Verbose mode.
705
pVerbose :: Field
706
pVerbose = defaultFalse "verbose"
707

    
708
-- ** Parameters for cluster verification
709

    
710
-- | Whether to simulate errors (useful for debugging).
711
pDebugSimulateErrors :: Field
712
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
713

    
714
-- | Error codes.
715
pErrorCodes :: Field
716
pErrorCodes = defaultFalse "error_codes"
717

    
718
-- | Which checks to skip.
719
pSkipChecks :: Field
720
pSkipChecks = defaultField [| Set.empty |] $
721
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
722

    
723
-- | List of error codes that should be treated as warnings.
724
pIgnoreErrors :: Field
725
pIgnoreErrors = defaultField [| Set.empty |] $
726
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
727

    
728
-- | Optional group name.
729
pOptGroupName :: Field
730
pOptGroupName = renameField "OptGroupName" .
731
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
732

    
733
-- | Disk templates' parameter defaults.
734
pDiskParams :: Field
735
pDiskParams = optionalField $
736
              simpleField "diskparams" [t| GenericContainer DiskTemplate
737
                                           UncheckedDict |]
738

    
739
-- * Parameters for node resource model
740

    
741
-- | Set hypervisor states.
742
pHvState :: Field
743
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
744

    
745
-- | Set disk states.
746
pDiskState :: Field
747
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
748

    
749
-- | Whether to ignore ipolicy violations.
750
pIgnoreIpolicy :: Field
751
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
752

    
753
-- | Allow runtime changes while migrating.
754
pAllowRuntimeChgs :: Field
755
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
756

    
757
-- | Utility type for OpClusterSetParams.
758
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
759

    
760
-- | Utility type of OsList.
761
type TestClusterOsList = [TestClusterOsListItem]
762

    
763
-- Utility type for NIC definitions.
764
--type TestNicDef = INicParams
765

    
766
-- | List of instance disks.
767
pInstDisks :: Field
768
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
769

    
770
-- | Instance disk template.
771
pDiskTemplate :: Field
772
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
773

    
774
-- | Instance disk template.
775
pOptDiskTemplate :: Field
776
pOptDiskTemplate =
777
  optionalField .
778
  renameField "OptDiskTemplate" $
779
  simpleField "disk_template" [t| DiskTemplate |]
780

    
781
-- | File driver.
782
pFileDriver :: Field
783
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
784

    
785
-- | Directory for storing file-backed disks.
786
pFileStorageDir :: Field
787
pFileStorageDir = optionalNEStringField "file_storage_dir"
788

    
789
-- | Volume group name.
790
pVgName :: Field
791
pVgName = optionalStringField "vg_name"
792

    
793
-- | List of enabled hypervisors.
794
pEnabledHypervisors :: Field
795
pEnabledHypervisors =
796
  optionalField $
797
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
798

    
799
-- | List of enabled disk templates.
800
pEnabledDiskTemplates :: Field
801
pEnabledDiskTemplates =
802
  optionalField $
803
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
804

    
805
-- | Selected hypervisor for an instance.
806
pHypervisor :: Field
807
pHypervisor =
808
  optionalField $
809
  simpleField "hypervisor" [t| Hypervisor |]
810

    
811
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
812
pClusterHvParams :: Field
813
pClusterHvParams =
814
  renameField "ClusterHvParams" .
815
  optionalField $
816
  simpleField "hvparams" [t| Container UncheckedDict |]
817

    
818
-- | Instance hypervisor parameters.
819
pInstHvParams :: Field
820
pInstHvParams =
821
  renameField "InstHvParams" .
822
  defaultField [| toJSObject [] |] $
823
  simpleField "hvparams" [t| UncheckedDict |]
824

    
825
-- | Cluster-wide beparams.
826
pClusterBeParams :: Field
827
pClusterBeParams =
828
  renameField "ClusterBeParams" .
829
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
830

    
831
-- | Instance beparams.
832
pInstBeParams :: Field
833
pInstBeParams =
834
  renameField "InstBeParams" .
835
  defaultField [| toJSObject [] |] $
836
  simpleField "beparams" [t| UncheckedDict |]
837

    
838
-- | Reset instance parameters to default if equal.
839
pResetDefaults :: Field
840
pResetDefaults = defaultFalse "identify_defaults"
841

    
842
-- | Cluster-wide per-OS hypervisor parameter defaults.
843
pOsHvp :: Field
844
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
845

    
846
-- | Cluster-wide OS parameter defaults.
847
pClusterOsParams :: Field
848
pClusterOsParams =
849
  renameField "ClusterOsParams" .
850
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
851

    
852
-- | Instance OS parameters.
853
pInstOsParams :: Field
854
pInstOsParams =
855
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
856
  simpleField "osparams" [t| UncheckedDict |]
857

    
858
-- | Temporary OS parameters (currently only in reinstall, might be
859
-- added to install as well).
860
pTempOsParams :: Field
861
pTempOsParams =
862
  renameField "TempOsParams" .
863
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
864

    
865
-- | Temporary hypervisor parameters, hypervisor-dependent.
866
pTempHvParams :: Field
867
pTempHvParams =
868
  renameField "TempHvParams" .
869
  defaultField [| toJSObject [] |] $
870
  simpleField "hvparams" [t| UncheckedDict |]
871

    
872
-- | Temporary backend parameters.
873
pTempBeParams :: Field
874
pTempBeParams =
875
  renameField "TempBeParams" .
876
  defaultField [| toJSObject [] |] $
877
  simpleField "beparams" [t| UncheckedDict |]
878

    
879
-- | Candidate pool size.
880
pCandidatePoolSize :: Field
881
pCandidatePoolSize =
882
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
883

    
884
-- | Set UID pool, must be list of lists describing UID ranges (two
885
-- items, start and end inclusive.
886
pUidPool :: Field
887
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
888

    
889
-- | Extend UID pool, must be list of lists describing UID ranges (two
890
-- items, start and end inclusive.
891
pAddUids :: Field
892
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
893

    
894
-- | Shrink UID pool, must be list of lists describing UID ranges (two
895
-- items, start and end inclusive) to be removed.
896
pRemoveUids :: Field
897
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
898

    
899
-- | Whether to automatically maintain node health.
900
pMaintainNodeHealth :: Field
901
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
902

    
903
-- | Whether to wipe disks before allocating them to instances.
904
pPreallocWipeDisks :: Field
905
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
906

    
907
-- | Cluster-wide NIC parameter defaults.
908
pNicParams :: Field
909
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
910

    
911
-- | Instance NIC definitions.
912
pInstNics :: Field
913
pInstNics = simpleField "nics" [t| [INicParams] |]
914

    
915
-- | Cluster-wide node parameter defaults.
916
pNdParams :: Field
917
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
918

    
919
-- | Cluster-wide ipolicy specs.
920
pIpolicy :: Field
921
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
922

    
923
-- | DRBD helper program.
924
pDrbdHelper :: Field
925
pDrbdHelper = optionalStringField "drbd_helper"
926

    
927
-- | Default iallocator for cluster.
928
pDefaultIAllocator :: Field
929
pDefaultIAllocator = optionalStringField "default_iallocator"
930

    
931
-- | Master network device.
932
pMasterNetdev :: Field
933
pMasterNetdev = optionalStringField "master_netdev"
934

    
935
-- | Netmask of the master IP.
936
pMasterNetmask :: Field
937
pMasterNetmask =
938
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
939

    
940
-- | List of reserved LVs.
941
pReservedLvs :: Field
942
pReservedLvs =
943
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
944

    
945
-- | Modify list of hidden operating systems: each modification must
946
-- have two items, the operation and the OS name; the operation can be
947
-- add or remove.
948
pHiddenOs :: Field
949
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
950

    
951
-- | Modify list of blacklisted operating systems: each modification
952
-- must have two items, the operation and the OS name; the operation
953
-- can be add or remove.
954
pBlacklistedOs :: Field
955
pBlacklistedOs =
956
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
957

    
958
-- | Whether to use an external master IP address setup script.
959
pUseExternalMipScript :: Field
960
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
961

    
962
-- | Requested fields.
963
pQueryFields :: Field
964
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
965

    
966
-- | Query filter.
967
pQueryFilter :: Field
968
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
969

    
970
-- | OOB command to run.
971
pOobCommand :: Field
972
pOobCommand = simpleField "command" [t| OobCommand |]
973

    
974
-- | Timeout before the OOB helper will be terminated.
975
pOobTimeout :: Field
976
pOobTimeout =
977
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
978

    
979
-- | Ignores the node offline status for power off.
980
pIgnoreStatus :: Field
981
pIgnoreStatus = defaultFalse "ignore_status"
982

    
983
-- | Time in seconds to wait between powering on nodes.
984
pPowerDelay :: Field
985
pPowerDelay =
986
  -- FIXME: we can't use the proper type "NonNegative Double", since
987
  -- the default constant is a plain Double, not a non-negative one.
988
  defaultField [| C.oobPowerDelay |] $
989
  simpleField "power_delay" [t| Double |]
990

    
991
-- | Primary IP address.
992
pPrimaryIp :: Field
993
pPrimaryIp = optionalStringField "primary_ip"
994

    
995
-- | Secondary IP address.
996
pSecondaryIp :: Field
997
pSecondaryIp = optionalNEStringField "secondary_ip"
998

    
999
-- | Whether node is re-added to cluster.
1000
pReadd :: Field
1001
pReadd = defaultFalse "readd"
1002

    
1003
-- | Initial node group.
1004
pNodeGroup :: Field
1005
pNodeGroup = optionalNEStringField "group"
1006

    
1007
-- | Whether node can become master or master candidate.
1008
pMasterCapable :: Field
1009
pMasterCapable = optionalField $ booleanField "master_capable"
1010

    
1011
-- | Whether node can host instances.
1012
pVmCapable :: Field
1013
pVmCapable = optionalField $ booleanField "vm_capable"
1014

    
1015
-- | List of names.
1016
pNames :: Field
1017
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1018

    
1019
-- | List of node names.
1020
pNodes :: Field
1021
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1022

    
1023
-- | Required list of node names.
1024
pRequiredNodes :: Field
1025
pRequiredNodes =
1026
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1027

    
1028
-- | Required list of node names.
1029
pRequiredNodeUuids :: Field
1030
pRequiredNodeUuids =
1031
  renameField "ReqNodeUuids " . optionalField $
1032
    simpleField "node_uuids" [t| [NonEmptyString] |]
1033

    
1034
-- | Storage type.
1035
pStorageType :: Field
1036
pStorageType = simpleField "storage_type" [t| StorageType |]
1037

    
1038
-- | Storage changes (unchecked).
1039
pStorageChanges :: Field
1040
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1041

    
1042
-- | Whether the node should become a master candidate.
1043
pMasterCandidate :: Field
1044
pMasterCandidate = optionalField $ booleanField "master_candidate"
1045

    
1046
-- | Whether the node should be marked as offline.
1047
pOffline :: Field
1048
pOffline = optionalField $ booleanField "offline"
1049

    
1050
-- | Whether the node should be marked as drained.
1051
pDrained ::Field
1052
pDrained = optionalField $ booleanField "drained"
1053

    
1054
-- | Whether node(s) should be promoted to master candidate if necessary.
1055
pAutoPromote :: Field
1056
pAutoPromote = defaultFalse "auto_promote"
1057

    
1058
-- | Whether the node should be marked as powered
1059
pPowered :: Field
1060
pPowered = optionalField $ booleanField "powered"
1061

    
1062
-- | Iallocator for deciding the target node for shared-storage
1063
-- instances during migrate and failover.
1064
pIallocator :: Field
1065
pIallocator = optionalNEStringField "iallocator"
1066

    
1067
-- | New secondary node.
1068
pRemoteNode :: Field
1069
pRemoteNode = optionalNEStringField "remote_node"
1070

    
1071
-- | New secondary node UUID.
1072
pRemoteNodeUuid :: Field
1073
pRemoteNodeUuid = optionalNEStringField "remote_node_uuid"
1074

    
1075
-- | Node evacuation mode.
1076
pEvacMode :: Field
1077
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1078

    
1079
-- | Instance creation mode.
1080
pInstCreateMode :: Field
1081
pInstCreateMode =
1082
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1083

    
1084
-- | Do not install the OS (will disable automatic start).
1085
pNoInstall :: Field
1086
pNoInstall = optionalField $ booleanField "no_install"
1087

    
1088
-- | OS type for instance installation.
1089
pInstOs :: Field
1090
pInstOs = optionalNEStringField "os_type"
1091

    
1092
-- | Primary node for an instance.
1093
pPrimaryNode :: Field
1094
pPrimaryNode = optionalNEStringField "pnode"
1095

    
1096
-- | Primary node UUID for an instance.
1097
pPrimaryNodeUuid :: Field
1098
pPrimaryNodeUuid = optionalNEStringField "pnode_uuid"
1099

    
1100
-- | Secondary node for an instance.
1101
pSecondaryNode :: Field
1102
pSecondaryNode = optionalNEStringField "snode"
1103

    
1104
-- | Secondary node UUID for an instance.
1105
pSecondaryNodeUuid :: Field
1106
pSecondaryNodeUuid = optionalNEStringField "snode_uuid"
1107

    
1108
-- | Signed handshake from source (remote import only).
1109
pSourceHandshake :: Field
1110
pSourceHandshake =
1111
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1112

    
1113
-- | Source instance name (remote import only).
1114
pSourceInstance :: Field
1115
pSourceInstance = optionalNEStringField "source_instance_name"
1116

    
1117
-- | How long source instance was given to shut down (remote import only).
1118
-- FIXME: non-negative int, whereas the constant is a plain int.
1119
pSourceShutdownTimeout :: Field
1120
pSourceShutdownTimeout =
1121
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1122
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1123

    
1124
-- | Source X509 CA in PEM format (remote import only).
1125
pSourceX509Ca :: Field
1126
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1127

    
1128
-- | Source node for import.
1129
pSrcNode :: Field
1130
pSrcNode = optionalNEStringField "src_node"
1131

    
1132
-- | Source node for import.
1133
pSrcNodeUuid :: Field
1134
pSrcNodeUuid = optionalNEStringField "src_node_uuid"
1135

    
1136
-- | Source directory for import.
1137
pSrcPath :: Field
1138
pSrcPath = optionalNEStringField "src_path"
1139

    
1140
-- | Whether to start instance after creation.
1141
pStartInstance :: Field
1142
pStartInstance = defaultTrue "start"
1143

    
1144
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1145
-- migrates to NonEmpty String.
1146
pInstTags :: Field
1147
pInstTags =
1148
  renameField "InstTags" .
1149
  defaultField [| [] |] $
1150
  simpleField "tags" [t| [NonEmptyString] |]
1151

    
1152
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1153
pMultiAllocInstances :: Field
1154
pMultiAllocInstances =
1155
  renameField "InstMultiAlloc" .
1156
  defaultField [| [] |] $
1157
  simpleField "instances"[t| UncheckedList |]
1158

    
1159
-- | Ignore failures parameter.
1160
pIgnoreFailures :: Field
1161
pIgnoreFailures = defaultFalse "ignore_failures"
1162

    
1163
-- | New instance or cluster name.
1164
pNewName :: Field
1165
pNewName = simpleField "new_name" [t| NonEmptyString |]
1166

    
1167
-- | Whether to start the instance even if secondary disks are failing.
1168
pIgnoreSecondaries :: Field
1169
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1170

    
1171
-- | How to reboot the instance.
1172
pRebootType :: Field
1173
pRebootType = simpleField "reboot_type" [t| RebootType |]
1174

    
1175
-- | Whether to ignore recorded disk size.
1176
pIgnoreDiskSize :: Field
1177
pIgnoreDiskSize = defaultFalse "ignore_size"
1178

    
1179
-- | Disk list for recreate disks.
1180
pRecreateDisksInfo :: Field
1181
pRecreateDisksInfo =
1182
  renameField "RecreateDisksInfo" .
1183
  defaultField [| RecreateDisksAll |] $
1184
  simpleField "disks" [t| RecreateDisksInfo |]
1185

    
1186
-- | Whether to only return configuration data without querying nodes.
1187
pStatic :: Field
1188
pStatic = defaultFalse "static"
1189

    
1190
-- | InstanceSetParams NIC changes.
1191
pInstParamsNicChanges :: Field
1192
pInstParamsNicChanges =
1193
  renameField "InstNicChanges" .
1194
  defaultField [| SetParamsEmpty |] $
1195
  simpleField "nics" [t| SetParamsMods INicParams |]
1196

    
1197
-- | InstanceSetParams Disk changes.
1198
pInstParamsDiskChanges :: Field
1199
pInstParamsDiskChanges =
1200
  renameField "InstDiskChanges" .
1201
  defaultField [| SetParamsEmpty |] $
1202
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1203

    
1204
-- | New runtime memory.
1205
pRuntimeMem :: Field
1206
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1207

    
1208
-- | Change the instance's OS without reinstalling the instance
1209
pOsNameChange :: Field
1210
pOsNameChange = optionalNEStringField "os_name"
1211

    
1212
-- | Disk index for e.g. grow disk.
1213
pDiskIndex :: Field
1214
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1215

    
1216
-- | Disk amount to add or grow to.
1217
pDiskChgAmount :: Field
1218
pDiskChgAmount =
1219
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1220

    
1221
-- | Whether the amount parameter is an absolute target or a relative one.
1222
pDiskChgAbsolute :: Field
1223
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1224

    
1225
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1226
pTargetGroups :: Field
1227
pTargetGroups =
1228
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1229

    
1230
-- | Export mode field.
1231
pExportMode :: Field
1232
pExportMode =
1233
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1234

    
1235
-- | Export target_node field, depends on mode.
1236
pExportTargetNode :: Field
1237
pExportTargetNode =
1238
  renameField "ExportTarget" $
1239
  simpleField "target_node" [t| ExportTarget |]
1240

    
1241
-- | Export target node UUID field.
1242
pExportTargetNodeUuid :: Field
1243
pExportTargetNodeUuid =
1244
  renameField "ExportTargetNodeUuid" . optionalField $
1245
  simpleField "target_node_uuid" [t| NonEmptyString |]
1246

    
1247
-- | Whether to remove instance after export.
1248
pRemoveInstance :: Field
1249
pRemoveInstance = defaultFalse "remove_instance"
1250

    
1251
-- | Whether to ignore failures while removing instances.
1252
pIgnoreRemoveFailures :: Field
1253
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1254

    
1255
-- | Name of X509 key (remote export only).
1256
pX509KeyName :: Field
1257
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1258

    
1259
-- | Destination X509 CA (remote export only).
1260
pX509DestCA :: Field
1261
pX509DestCA = optionalNEStringField "destination_x509_ca"
1262

    
1263
-- | Search pattern (regular expression). FIXME: this should be
1264
-- compiled at load time?
1265
pTagSearchPattern :: Field
1266
pTagSearchPattern =
1267
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1268

    
1269
-- | Restricted command name.
1270
pRestrictedCommand :: Field
1271
pRestrictedCommand =
1272
  renameField "RestrictedCommand" $
1273
  simpleField "command" [t| NonEmptyString |]
1274

    
1275
-- | Replace disks mode.
1276
pReplaceDisksMode :: Field
1277
pReplaceDisksMode =
1278
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1279

    
1280
-- | List of disk indices.
1281
pReplaceDisksList :: Field
1282
pReplaceDisksList =
1283
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1284

    
1285
-- | Whether do allow failover in migrations.
1286
pAllowFailover :: Field
1287
pAllowFailover = defaultFalse "allow_failover"
1288

    
1289
-- * Test opcode parameters
1290

    
1291
-- | Duration parameter for 'OpTestDelay'.
1292
pDelayDuration :: Field
1293
pDelayDuration =
1294
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1295

    
1296
-- | on_master field for 'OpTestDelay'.
1297
pDelayOnMaster :: Field
1298
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1299

    
1300
-- | on_nodes field for 'OpTestDelay'.
1301
pDelayOnNodes :: Field
1302
pDelayOnNodes =
1303
  renameField "DelayOnNodes" .
1304
  defaultField [| [] |] $
1305
  simpleField "on_nodes" [t| [NonEmptyString] |]
1306

    
1307
-- | on_node_uuids field for 'OpTestDelay'.
1308
pDelayOnNodeUuids :: Field
1309
pDelayOnNodeUuids =
1310
  renameField "DelayOnNodeUuids" . optionalField $
1311
  simpleField "on_node_uuids" [t| [NonEmptyString] |]
1312

    
1313
-- | Repeat parameter for OpTestDelay.
1314
pDelayRepeat :: Field
1315
pDelayRepeat =
1316
  renameField "DelayRepeat" .
1317
  defaultField [| forceNonNeg (0::Int) |] $
1318
  simpleField "repeat" [t| NonNegative Int |]
1319

    
1320
-- | IAllocator test direction.
1321
pIAllocatorDirection :: Field
1322
pIAllocatorDirection =
1323
  renameField "IAllocatorDirection" $
1324
  simpleField "direction" [t| IAllocatorTestDir |]
1325

    
1326
-- | IAllocator test mode.
1327
pIAllocatorMode :: Field
1328
pIAllocatorMode =
1329
  renameField "IAllocatorMode" $
1330
  simpleField "mode" [t| IAllocatorMode |]
1331

    
1332
-- | IAllocator target name (new instance, node to evac, etc.).
1333
pIAllocatorReqName :: Field
1334
pIAllocatorReqName =
1335
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1336

    
1337
-- | Custom OpTestIAllocator nics.
1338
pIAllocatorNics :: Field
1339
pIAllocatorNics =
1340
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1341

    
1342
-- | Custom OpTestAllocator disks.
1343
pIAllocatorDisks :: Field
1344
pIAllocatorDisks =
1345
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1346

    
1347
-- | IAllocator memory field.
1348
pIAllocatorMemory :: Field
1349
pIAllocatorMemory =
1350
  renameField "IAllocatorMem" .
1351
  optionalField $
1352
  simpleField "memory" [t| NonNegative Int |]
1353

    
1354
-- | IAllocator vcpus field.
1355
pIAllocatorVCpus :: Field
1356
pIAllocatorVCpus =
1357
  renameField "IAllocatorVCpus" .
1358
  optionalField $
1359
  simpleField "vcpus" [t| NonNegative Int |]
1360

    
1361
-- | IAllocator os field.
1362
pIAllocatorOs :: Field
1363
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1364

    
1365
-- | IAllocator instances field.
1366
pIAllocatorInstances :: Field
1367
pIAllocatorInstances =
1368
  renameField "IAllocatorInstances " .
1369
  optionalField $
1370
  simpleField "instances" [t| [NonEmptyString] |]
1371

    
1372
-- | IAllocator evac mode.
1373
pIAllocatorEvacMode :: Field
1374
pIAllocatorEvacMode =
1375
  renameField "IAllocatorEvacMode" .
1376
  optionalField $
1377
  simpleField "evac_mode" [t| NodeEvacMode |]
1378

    
1379
-- | IAllocator spindle use.
1380
pIAllocatorSpindleUse :: Field
1381
pIAllocatorSpindleUse =
1382
  renameField "IAllocatorSpindleUse" .
1383
  defaultField [| forceNonNeg (1::Int) |] $
1384
  simpleField "spindle_use" [t| NonNegative Int |]
1385

    
1386
-- | IAllocator count field.
1387
pIAllocatorCount :: Field
1388
pIAllocatorCount =
1389
  renameField "IAllocatorCount" .
1390
  defaultField [| forceNonNeg (1::Int) |] $
1391
  simpleField "count" [t| NonNegative Int |]
1392

    
1393
-- | 'OpTestJqueue' notify_waitlock.
1394
pJQueueNotifyWaitLock :: Field
1395
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1396

    
1397
-- | 'OpTestJQueue' notify_exec.
1398
pJQueueNotifyExec :: Field
1399
pJQueueNotifyExec = defaultFalse "notify_exec"
1400

    
1401
-- | 'OpTestJQueue' log_messages.
1402
pJQueueLogMessages :: Field
1403
pJQueueLogMessages =
1404
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1405

    
1406
-- | 'OpTestJQueue' fail attribute.
1407
pJQueueFail :: Field
1408
pJQueueFail =
1409
  renameField "JQueueFail" $ defaultFalse "fail"
1410

    
1411
-- | 'OpTestDummy' result field.
1412
pTestDummyResult :: Field
1413
pTestDummyResult =
1414
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1415

    
1416
-- | 'OpTestDummy' messages field.
1417
pTestDummyMessages :: Field
1418
pTestDummyMessages =
1419
  renameField "TestDummyMessages" $
1420
  simpleField "messages" [t| UncheckedValue |]
1421

    
1422
-- | 'OpTestDummy' fail field.
1423
pTestDummyFail :: Field
1424
pTestDummyFail =
1425
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1426

    
1427
-- | 'OpTestDummy' submit_jobs field.
1428
pTestDummySubmitJobs :: Field
1429
pTestDummySubmitJobs =
1430
  renameField "TestDummySubmitJobs" $
1431
  simpleField "submit_jobs" [t| UncheckedValue |]
1432

    
1433
-- * Network parameters
1434

    
1435
-- | Network name.
1436
pNetworkName :: Field
1437
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1438

    
1439
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1440
pNetworkAddress4 :: Field
1441
pNetworkAddress4 =
1442
  renameField "NetworkAddress4" $
1443
  simpleField "network" [t| NonEmptyString |]
1444

    
1445
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1446
pNetworkGateway4 :: Field
1447
pNetworkGateway4 =
1448
  renameField "NetworkGateway4" $
1449
  optionalNEStringField "gateway"
1450

    
1451
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1452
pNetworkAddress6 :: Field
1453
pNetworkAddress6 =
1454
  renameField "NetworkAddress6" $
1455
  optionalNEStringField "network6"
1456

    
1457
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1458
pNetworkGateway6 :: Field
1459
pNetworkGateway6 =
1460
  renameField "NetworkGateway6" $
1461
  optionalNEStringField "gateway6"
1462

    
1463
-- | Network specific mac prefix (that overrides the cluster one).
1464
pNetworkMacPrefix :: Field
1465
pNetworkMacPrefix =
1466
  renameField "NetMacPrefix" $
1467
  optionalNEStringField "mac_prefix"
1468

    
1469
-- | Network add reserved IPs.
1470
pNetworkAddRsvdIps :: Field
1471
pNetworkAddRsvdIps =
1472
  renameField "NetworkAddRsvdIps" .
1473
  optionalField $
1474
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1475

    
1476
-- | Network remove reserved IPs.
1477
pNetworkRemoveRsvdIps :: Field
1478
pNetworkRemoveRsvdIps =
1479
  renameField "NetworkRemoveRsvdIps" .
1480
  optionalField $
1481
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1482

    
1483
-- | Network mode when connecting to a group.
1484
pNetworkMode :: Field
1485
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1486

    
1487
-- | Network link when connecting to a group.
1488
pNetworkLink :: Field
1489
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1490

    
1491
-- * Common opcode parameters
1492

    
1493
-- | Run checks only, don't execute.
1494
pDryRun :: Field
1495
pDryRun = optionalField $ booleanField "dry_run"
1496

    
1497
-- | Debug level.
1498
pDebugLevel :: Field
1499
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1500

    
1501
-- | Opcode priority. Note: python uses a separate constant, we're
1502
-- using the actual value we know it's the default.
1503
pOpPriority :: Field
1504
pOpPriority =
1505
  defaultField [| OpPrioNormal |] $
1506
  simpleField "priority" [t| OpSubmitPriority |]
1507

    
1508
-- | Job dependencies.
1509
pDependencies :: Field
1510
pDependencies =
1511
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1512

    
1513
-- | Comment field.
1514
pComment :: Field
1515
pComment = optionalNullSerField $ stringField "comment"
1516

    
1517
-- | Reason trail field.
1518
pReason :: Field
1519
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1520

    
1521
-- * Entire opcode parameter list
1522

    
1523
-- | Old-style query opcode, with locking.
1524
dOldQuery :: [Field]
1525
dOldQuery =
1526
  [ pOutputFields
1527
  , pNames
1528
  , pUseLocking
1529
  ]
1530

    
1531
-- | Old-style query opcode, without locking.
1532
dOldQueryNoLocking :: [Field]
1533
dOldQueryNoLocking =
1534
  [ pOutputFields
1535
  , pNames
1536
  ]