Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ e7a77eb8

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

    
248
import Control.Monad (liftM)
249
import qualified Data.Set as Set
250
import Text.JSON (readJSON, showJSON, JSON, JSValue(..), fromJSString,
251
                  JSObject, toJSObject)
252
import qualified Text.JSON
253
import Text.JSON.Pretty (pp_value)
254

    
255
import Ganeti.BasicTypes
256
import qualified Ganeti.Constants as C
257
import Ganeti.THH
258
import Ganeti.JSON
259
import Ganeti.Types
260
import qualified Ganeti.Query.Language as Qlang
261

    
262
-- * Helper functions and types
263

    
264
-- * Type aliases
265

    
266
-- | Build a boolean field.
267
booleanField :: String -> Field
268
booleanField = flip simpleField [t| Bool |]
269

    
270
-- | Default a field to 'False'.
271
defaultFalse :: String -> Field
272
defaultFalse = defaultField [| False |] . booleanField
273

    
274
-- | Default a field to 'True'.
275
defaultTrue :: String -> Field
276
defaultTrue = defaultField [| True |] . booleanField
277

    
278
-- | An alias for a 'String' field.
279
stringField :: String -> Field
280
stringField = flip simpleField [t| String |]
281

    
282
-- | An alias for an optional string field.
283
optionalStringField :: String -> Field
284
optionalStringField = optionalField . stringField
285

    
286
-- | An alias for an optional non-empty string field.
287
optionalNEStringField :: String -> Field
288
optionalNEStringField = optionalField . flip simpleField [t| NonEmptyString |]
289

    
290
-- | Unchecked value, should be replaced by a better definition.
291
type UncheckedValue = JSValue
292

    
293
-- | Unchecked dict, should be replaced by a better definition.
294
type UncheckedDict = JSObject JSValue
295

    
296
-- | Unchecked list, shoild be replaced by a better definition.
297
type UncheckedList = [JSValue]
298

    
299
-- | Function to force a non-negative value, without returning via a
300
-- monad. This is needed for, and should be used /only/ in the case of
301
-- forcing constants. In case the constant is wrong (< 0), this will
302
-- become a runtime error.
303
forceNonNeg :: (Num a, Ord a, Show a) => a -> NonNegative a
304
forceNonNeg i = case mkNonNegative i of
305
                  Ok n -> n
306
                  Bad msg -> error msg
307

    
308
-- ** Tags
309

    
310
-- | Data type representing what items do the tag operations apply to.
311
$(declareSADT "TagType"
312
  [ ("TagTypeInstance", 'C.tagInstance)
313
  , ("TagTypeNode",     'C.tagNode)
314
  , ("TagTypeGroup",    'C.tagNodegroup)
315
  , ("TagTypeCluster",  'C.tagCluster)
316
  , ("TagTypeNetwork",  'C.tagNetwork)
317
  ])
318
$(makeJSONInstance ''TagType)
319

    
320
-- | Data type holding a tag object (type and object name).
321
data TagObject = TagInstance String
322
               | TagNode     String
323
               | TagGroup    String
324
               | TagNetwork  String
325
               | TagCluster
326
               deriving (Show, Eq)
327

    
328
-- | Tag type for a given tag object.
329
tagTypeOf :: TagObject -> TagType
330
tagTypeOf (TagInstance {}) = TagTypeInstance
331
tagTypeOf (TagNode     {}) = TagTypeNode
332
tagTypeOf (TagGroup    {}) = TagTypeGroup
333
tagTypeOf (TagCluster  {}) = TagTypeCluster
334
tagTypeOf (TagNetwork  {}) = TagTypeNetwork
335

    
336
-- | Gets the potential tag object name.
337
tagNameOf :: TagObject -> Maybe String
338
tagNameOf (TagInstance s) = Just s
339
tagNameOf (TagNode     s) = Just s
340
tagNameOf (TagGroup    s) = Just s
341
tagNameOf (TagNetwork  s) = Just s
342
tagNameOf  TagCluster     = Nothing
343

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

    
357
-- | Name of the tag \"name\" field.
358
tagNameField :: String
359
tagNameField = "name"
360

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

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

    
373
-- ** Disks
374

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

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

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

    
396
instance JSON DiskIndex where
397
  readJSON v = readJSON v >>= mkDiskIndex
398
  showJSON = showJSON . unDiskIndex
399

    
400
-- ** I* param types
401

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

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

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

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

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

    
450
instance JSON RecreateDisksInfo where
451
  readJSON = readRecreateDisks
452
  showJSON  RecreateDisksAll            = showJSON ()
453
  showJSON (RecreateDisksIndices idx)   = showJSON idx
454
  showJSON (RecreateDisksParams params) = showJSON params
455

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

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

    
470
instance JSON DdmOldChanges where
471
  showJSON (DdmOldIndex i) = showJSON i
472
  showJSON (DdmOldMod m)   = showJSON m
473
  readJSON = readDdmOldChanges
474

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

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

    
490
instance (JSON a) => JSON (SetParamsMods a) where
491
  showJSON SetParamsEmpty = showJSON ()
492
  showJSON (SetParamsDeprecated v) = showJSON v
493
  showJSON (SetParamsNew v) = showJSON v
494
  readJSON = readSetParams
495

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

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

    
512
instance JSON ExportTarget where
513
  showJSON (ExportTargetLocal s)  = showJSON s
514
  showJSON (ExportTargetRemote l) = showJSON l
515
  readJSON = readExportTarget
516

    
517
-- * Parameters
518

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

    
523
-- | A list of instances.
524
pInstances :: Field
525
pInstances = defaultField [| [] |] $
526
             simpleField "instances" [t| [NonEmptyString] |]
527

    
528
-- | A generic name.
529
pName :: Field
530
pName = simpleField "name" [t| NonEmptyString |]
531

    
532
-- | Tags list.
533
pTagsList :: Field
534
pTagsList = simpleField "tags" [t| [String] |]
535

    
536
-- | Tags object.
537
pTagsObject :: Field
538
pTagsObject =
539
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
540
  simpleField "kind" [t| TagObject |]
541

    
542
-- | Selected output fields.
543
pOutputFields :: Field
544
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
545

    
546
-- | How long to wait for instance to shut down.
547
pShutdownTimeout :: Field
548
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
549
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
550

    
551
-- | Another name for the shutdown timeout, because we like to be
552
-- inconsistent.
553
pShutdownTimeout' :: Field
554
pShutdownTimeout' =
555
  renameField "InstShutdownTimeout" .
556
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
557
  simpleField "timeout" [t| NonNegative Int |]
558

    
559
-- | Whether to shutdown the instance in backup-export.
560
pShutdownInstance :: Field
561
pShutdownInstance = defaultTrue "shutdown"
562

    
563
-- | Whether to force the operation.
564
pForce :: Field
565
pForce = defaultFalse "force"
566

    
567
-- | Whether to ignore offline nodes.
568
pIgnoreOfflineNodes :: Field
569
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
570

    
571
-- | A required node name (for single-node LUs).
572
pNodeName :: Field
573
pNodeName = simpleField "node_name" [t| NonEmptyString |]
574

    
575
-- | List of nodes.
576
pNodeNames :: Field
577
pNodeNames =
578
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
579

    
580
-- | A required node group name (for single-group LUs).
581
pGroupName :: Field
582
pGroupName = simpleField "group_name" [t| NonEmptyString |]
583

    
584
-- | Migration type (live\/non-live).
585
pMigrationMode :: Field
586
pMigrationMode =
587
  renameField "MigrationMode" .
588
  optionalField $
589
  simpleField "mode" [t| MigrationMode |]
590

    
591
-- | Obsolete \'live\' migration mode (boolean).
592
pMigrationLive :: Field
593
pMigrationLive =
594
  renameField "OldLiveMode" . optionalField $ booleanField "live"
595

    
596
-- | Migration cleanup parameter.
597
pMigrationCleanup :: Field
598
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
599

    
600
-- | Whether to force an unknown OS variant.
601
pForceVariant :: Field
602
pForceVariant = defaultFalse "force_variant"
603

    
604
-- | Whether to wait for the disk to synchronize.
605
pWaitForSync :: Field
606
pWaitForSync = defaultTrue "wait_for_sync"
607

    
608
-- | Whether to wait for the disk to synchronize (defaults to false).
609
pWaitForSyncFalse :: Field
610
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
611

    
612
-- | Whether to ignore disk consistency
613
pIgnoreConsistency :: Field
614
pIgnoreConsistency = defaultFalse "ignore_consistency"
615

    
616
-- | Storage name.
617
pStorageName :: Field
618
pStorageName =
619
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
620

    
621
-- | Whether to use synchronization.
622
pUseLocking :: Field
623
pUseLocking = defaultFalse "use_locking"
624

    
625
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
626
-- locked by another opcode won't be considered for instance allocation (only
627
-- when an iallocator is used).
628
pOpportunisticLocking :: Field
629
pOpportunisticLocking = defaultFalse "opportunistic_locking"
630

    
631
-- | Whether to check name.
632
pNameCheck :: Field
633
pNameCheck = defaultTrue "name_check"
634

    
635
-- | Instance allocation policy.
636
pNodeGroupAllocPolicy :: Field
637
pNodeGroupAllocPolicy = optionalField $
638
                        simpleField "alloc_policy" [t| AllocPolicy |]
639

    
640
-- | Default node parameters for group.
641
pGroupNodeParams :: Field
642
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
643

    
644
-- | Resource(s) to query for.
645
pQueryWhat :: Field
646
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
647

    
648
-- | Whether to release locks as soon as possible.
649
pEarlyRelease :: Field
650
pEarlyRelease = defaultFalse "early_release"
651

    
652
-- | Whether to ensure instance's IP address is inactive.
653
pIpCheck :: Field
654
pIpCheck = defaultTrue "ip_check"
655

    
656
-- | Check for conflicting IPs.
657
pIpConflictsCheck :: Field
658
pIpConflictsCheck = defaultTrue "conflicts_check"
659

    
660
-- | Do not remember instance state changes.
661
pNoRemember :: Field
662
pNoRemember = defaultFalse "no_remember"
663

    
664
-- | Target node for instance migration/failover.
665
pMigrationTargetNode :: Field
666
pMigrationTargetNode = optionalNEStringField "target_node"
667

    
668
-- | Target node for instance move (required).
669
pMoveTargetNode :: Field
670
pMoveTargetNode =
671
  renameField "MoveTargetNode" $
672
  simpleField "target_node" [t| NonEmptyString |]
673

    
674
-- | Pause instance at startup.
675
pStartupPaused :: Field
676
pStartupPaused = defaultFalse "startup_paused"
677

    
678
-- | Verbose mode.
679
pVerbose :: Field
680
pVerbose = defaultFalse "verbose"
681

    
682
-- ** Parameters for cluster verification
683

    
684
-- | Whether to simulate errors (useful for debugging).
685
pDebugSimulateErrors :: Field
686
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
687

    
688
-- | Error codes.
689
pErrorCodes :: Field
690
pErrorCodes = defaultFalse "error_codes"
691

    
692
-- | Which checks to skip.
693
pSkipChecks :: Field
694
pSkipChecks = defaultField [| Set.empty |] $
695
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
696

    
697
-- | List of error codes that should be treated as warnings.
698
pIgnoreErrors :: Field
699
pIgnoreErrors = defaultField [| Set.empty |] $
700
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
701

    
702
-- | Optional group name.
703
pOptGroupName :: Field
704
pOptGroupName = renameField "OptGroupName" .
705
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
706

    
707
-- | Disk templates' parameter defaults.
708
pDiskParams :: Field
709
pDiskParams = optionalField $
710
              simpleField "diskparams" [t| GenericContainer DiskTemplate
711
                                           UncheckedDict |]
712

    
713
-- | Whether to hotplug device.
714
pHotplug :: Field
715
pHotplug = defaultFalse "hotplug"
716

    
717
pHotplugIfPossible :: Field
718
pHotplugIfPossible = defaultFalse "hotplug_if_possible"
719

    
720
-- * Parameters for node resource model
721

    
722
-- | Set hypervisor states.
723
pHvState :: Field
724
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
725

    
726
-- | Set disk states.
727
pDiskState :: Field
728
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
729

    
730
-- | Whether to ignore ipolicy violations.
731
pIgnoreIpolicy :: Field
732
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
733

    
734
-- | Allow runtime changes while migrating.
735
pAllowRuntimeChgs :: Field
736
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
737

    
738
-- | Utility type for OpClusterSetParams.
739
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
740

    
741
-- | Utility type of OsList.
742
type TestClusterOsList = [TestClusterOsListItem]
743

    
744
-- Utility type for NIC definitions.
745
--type TestNicDef = INicParams
746

    
747
-- | List of instance disks.
748
pInstDisks :: Field
749
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
750

    
751
-- | Instance disk template.
752
pDiskTemplate :: Field
753
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
754

    
755
-- | Instance disk template.
756
pOptDiskTemplate :: Field
757
pOptDiskTemplate =
758
  optionalField .
759
  renameField "OptDiskTemplate" $
760
  simpleField "disk_template" [t| DiskTemplate |]
761

    
762
-- | File driver.
763
pFileDriver :: Field
764
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
765

    
766
-- | Directory for storing file-backed disks.
767
pFileStorageDir :: Field
768
pFileStorageDir = optionalNEStringField "file_storage_dir"
769

    
770
-- | Volume group name.
771
pVgName :: Field
772
pVgName = optionalStringField "vg_name"
773

    
774
-- | List of enabled hypervisors.
775
pEnabledHypervisors :: Field
776
pEnabledHypervisors =
777
  optionalField $
778
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
779

    
780
-- | List of enabled disk templates.
781
pEnabledDiskTemplates :: Field
782
pEnabledDiskTemplates =
783
  optionalField $
784
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
785

    
786
-- | Selected hypervisor for an instance.
787
pHypervisor :: Field
788
pHypervisor =
789
  optionalField $
790
  simpleField "hypervisor" [t| Hypervisor |]
791

    
792
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
793
pClusterHvParams :: Field
794
pClusterHvParams =
795
  renameField "ClusterHvParams" .
796
  optionalField $
797
  simpleField "hvparams" [t| Container UncheckedDict |]
798

    
799
-- | Instance hypervisor parameters.
800
pInstHvParams :: Field
801
pInstHvParams =
802
  renameField "InstHvParams" .
803
  defaultField [| toJSObject [] |] $
804
  simpleField "hvparams" [t| UncheckedDict |]
805

    
806
-- | Cluster-wide beparams.
807
pClusterBeParams :: Field
808
pClusterBeParams =
809
  renameField "ClusterBeParams" .
810
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
811

    
812
-- | Instance beparams.
813
pInstBeParams :: Field
814
pInstBeParams =
815
  renameField "InstBeParams" .
816
  defaultField [| toJSObject [] |] $
817
  simpleField "beparams" [t| UncheckedDict |]
818

    
819
-- | Reset instance parameters to default if equal.
820
pResetDefaults :: Field
821
pResetDefaults = defaultFalse "identify_defaults"
822

    
823
-- | Cluster-wide per-OS hypervisor parameter defaults.
824
pOsHvp :: Field
825
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
826

    
827
-- | Cluster-wide OS parameter defaults.
828
pClusterOsParams :: Field
829
pClusterOsParams =
830
  renameField "ClusterOsParams" .
831
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
832

    
833
-- | Instance OS parameters.
834
pInstOsParams :: Field
835
pInstOsParams =
836
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
837
  simpleField "osparams" [t| UncheckedDict |]
838

    
839
-- | Temporary OS parameters (currently only in reinstall, might be
840
-- added to install as well).
841
pTempOsParams :: Field
842
pTempOsParams =
843
  renameField "TempOsParams" .
844
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
845

    
846
-- | Temporary hypervisor parameters, hypervisor-dependent.
847
pTempHvParams :: Field
848
pTempHvParams =
849
  renameField "TempHvParams" .
850
  defaultField [| toJSObject [] |] $
851
  simpleField "hvparams" [t| UncheckedDict |]
852

    
853
-- | Temporary backend parameters.
854
pTempBeParams :: Field
855
pTempBeParams =
856
  renameField "TempBeParams" .
857
  defaultField [| toJSObject [] |] $
858
  simpleField "beparams" [t| UncheckedDict |]
859

    
860
-- | Candidate pool size.
861
pCandidatePoolSize :: Field
862
pCandidatePoolSize =
863
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
864

    
865
-- | Set UID pool, must be list of lists describing UID ranges (two
866
-- items, start and end inclusive.
867
pUidPool :: Field
868
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
869

    
870
-- | Extend UID pool, must be list of lists describing UID ranges (two
871
-- items, start and end inclusive.
872
pAddUids :: Field
873
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
874

    
875
-- | Shrink UID pool, must be list of lists describing UID ranges (two
876
-- items, start and end inclusive) to be removed.
877
pRemoveUids :: Field
878
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
879

    
880
-- | Whether to automatically maintain node health.
881
pMaintainNodeHealth :: Field
882
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
883

    
884
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
885
pModifyEtcHosts :: Field
886
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
887

    
888
-- | Whether to wipe disks before allocating them to instances.
889
pPreallocWipeDisks :: Field
890
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
891

    
892
-- | Cluster-wide NIC parameter defaults.
893
pNicParams :: Field
894
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
895

    
896
-- | Instance NIC definitions.
897
pInstNics :: Field
898
pInstNics = simpleField "nics" [t| [INicParams] |]
899

    
900
-- | Cluster-wide node parameter defaults.
901
pNdParams :: Field
902
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
903

    
904
-- | Cluster-wide ipolicy specs.
905
pIpolicy :: Field
906
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
907

    
908
-- | DRBD helper program.
909
pDrbdHelper :: Field
910
pDrbdHelper = optionalStringField "drbd_helper"
911

    
912
-- | Default iallocator for cluster.
913
pDefaultIAllocator :: Field
914
pDefaultIAllocator = optionalStringField "default_iallocator"
915

    
916
-- | Master network device.
917
pMasterNetdev :: Field
918
pMasterNetdev = optionalStringField "master_netdev"
919

    
920
-- | Netmask of the master IP.
921
pMasterNetmask :: Field
922
pMasterNetmask =
923
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
924

    
925
-- | List of reserved LVs.
926
pReservedLvs :: Field
927
pReservedLvs =
928
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
929

    
930
-- | Modify list of hidden operating systems: each modification must
931
-- have two items, the operation and the OS name; the operation can be
932
-- add or remove.
933
pHiddenOs :: Field
934
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
935

    
936
-- | Modify list of blacklisted operating systems: each modification
937
-- must have two items, the operation and the OS name; the operation
938
-- can be add or remove.
939
pBlacklistedOs :: Field
940
pBlacklistedOs =
941
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
942

    
943
-- | Whether to use an external master IP address setup script.
944
pUseExternalMipScript :: Field
945
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
946

    
947
-- | Requested fields.
948
pQueryFields :: Field
949
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
950

    
951
-- | Query filter.
952
pQueryFilter :: Field
953
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
954

    
955
-- | OOB command to run.
956
pOobCommand :: Field
957
pOobCommand = simpleField "command" [t| OobCommand |]
958

    
959
-- | Timeout before the OOB helper will be terminated.
960
pOobTimeout :: Field
961
pOobTimeout =
962
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
963

    
964
-- | Ignores the node offline status for power off.
965
pIgnoreStatus :: Field
966
pIgnoreStatus = defaultFalse "ignore_status"
967

    
968
-- | Time in seconds to wait between powering on nodes.
969
pPowerDelay :: Field
970
pPowerDelay =
971
  -- FIXME: we can't use the proper type "NonNegative Double", since
972
  -- the default constant is a plain Double, not a non-negative one.
973
  defaultField [| C.oobPowerDelay |] $
974
  simpleField "power_delay" [t| Double |]
975

    
976
-- | Primary IP address.
977
pPrimaryIp :: Field
978
pPrimaryIp = optionalStringField "primary_ip"
979

    
980
-- | Secondary IP address.
981
pSecondaryIp :: Field
982
pSecondaryIp = optionalNEStringField "secondary_ip"
983

    
984
-- | Whether node is re-added to cluster.
985
pReadd :: Field
986
pReadd = defaultFalse "readd"
987

    
988
-- | Initial node group.
989
pNodeGroup :: Field
990
pNodeGroup = optionalNEStringField "group"
991

    
992
-- | Whether node can become master or master candidate.
993
pMasterCapable :: Field
994
pMasterCapable = optionalField $ booleanField "master_capable"
995

    
996
-- | Whether node can host instances.
997
pVmCapable :: Field
998
pVmCapable = optionalField $ booleanField "vm_capable"
999

    
1000
-- | List of names.
1001
pNames :: Field
1002
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1003

    
1004
-- | List of node names.
1005
pNodes :: Field
1006
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1007

    
1008
-- | Required list of node names.
1009
pRequiredNodes :: Field
1010
pRequiredNodes =
1011
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1012

    
1013
-- | Storage type.
1014
pStorageType :: Field
1015
pStorageType = simpleField "storage_type" [t| StorageType |]
1016

    
1017
-- | Storage changes (unchecked).
1018
pStorageChanges :: Field
1019
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1020

    
1021
-- | Whether the node should become a master candidate.
1022
pMasterCandidate :: Field
1023
pMasterCandidate = optionalField $ booleanField "master_candidate"
1024

    
1025
-- | Whether the node should be marked as offline.
1026
pOffline :: Field
1027
pOffline = optionalField $ booleanField "offline"
1028

    
1029
-- | Whether the node should be marked as drained.
1030
pDrained ::Field
1031
pDrained = optionalField $ booleanField "drained"
1032

    
1033
-- | Whether node(s) should be promoted to master candidate if necessary.
1034
pAutoPromote :: Field
1035
pAutoPromote = defaultFalse "auto_promote"
1036

    
1037
-- | Whether the node should be marked as powered
1038
pPowered :: Field
1039
pPowered = optionalField $ booleanField "powered"
1040

    
1041
-- | Iallocator for deciding the target node for shared-storage
1042
-- instances during migrate and failover.
1043
pIallocator :: Field
1044
pIallocator = optionalNEStringField "iallocator"
1045

    
1046
-- | New secondary node.
1047
pRemoteNode :: Field
1048
pRemoteNode = optionalNEStringField "remote_node"
1049

    
1050
-- | Node evacuation mode.
1051
pEvacMode :: Field
1052
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1053

    
1054
-- | Instance creation mode.
1055
pInstCreateMode :: Field
1056
pInstCreateMode =
1057
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1058

    
1059
-- | Do not install the OS (will disable automatic start).
1060
pNoInstall :: Field
1061
pNoInstall = optionalField $ booleanField "no_install"
1062

    
1063
-- | OS type for instance installation.
1064
pInstOs :: Field
1065
pInstOs = optionalNEStringField "os_type"
1066

    
1067
-- | Primary node for an instance.
1068
pPrimaryNode :: Field
1069
pPrimaryNode = optionalNEStringField "pnode"
1070

    
1071
-- | Secondary node for an instance.
1072
pSecondaryNode :: Field
1073
pSecondaryNode = optionalNEStringField "snode"
1074

    
1075
-- | Signed handshake from source (remote import only).
1076
pSourceHandshake :: Field
1077
pSourceHandshake =
1078
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1079

    
1080
-- | Source instance name (remote import only).
1081
pSourceInstance :: Field
1082
pSourceInstance = optionalNEStringField "source_instance_name"
1083

    
1084
-- | How long source instance was given to shut down (remote import only).
1085
-- FIXME: non-negative int, whereas the constant is a plain int.
1086
pSourceShutdownTimeout :: Field
1087
pSourceShutdownTimeout =
1088
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1089
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1090

    
1091
-- | Source X509 CA in PEM format (remote import only).
1092
pSourceX509Ca :: Field
1093
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1094

    
1095
-- | Source node for import.
1096
pSrcNode :: Field
1097
pSrcNode = optionalNEStringField "src_node"
1098

    
1099
-- | Source directory for import.
1100
pSrcPath :: Field
1101
pSrcPath = optionalNEStringField "src_path"
1102

    
1103
-- | Whether to start instance after creation.
1104
pStartInstance :: Field
1105
pStartInstance = defaultTrue "start"
1106

    
1107
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1108
-- migrates to NonEmpty String.
1109
pInstTags :: Field
1110
pInstTags =
1111
  renameField "InstTags" .
1112
  defaultField [| [] |] $
1113
  simpleField "tags" [t| [NonEmptyString] |]
1114

    
1115
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1116
pMultiAllocInstances :: Field
1117
pMultiAllocInstances =
1118
  renameField "InstMultiAlloc" .
1119
  defaultField [| [] |] $
1120
  simpleField "instances"[t| UncheckedList |]
1121

    
1122
-- | Ignore failures parameter.
1123
pIgnoreFailures :: Field
1124
pIgnoreFailures = defaultFalse "ignore_failures"
1125

    
1126
-- | New instance or cluster name.
1127
pNewName :: Field
1128
pNewName = simpleField "new_name" [t| NonEmptyString |]
1129

    
1130
-- | Whether to start the instance even if secondary disks are failing.
1131
pIgnoreSecondaries :: Field
1132
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1133

    
1134
-- | How to reboot the instance.
1135
pRebootType :: Field
1136
pRebootType = simpleField "reboot_type" [t| RebootType |]
1137

    
1138
-- | Whether to ignore recorded disk size.
1139
pIgnoreDiskSize :: Field
1140
pIgnoreDiskSize = defaultFalse "ignore_size"
1141

    
1142
-- | Disk list for recreate disks.
1143
pRecreateDisksInfo :: Field
1144
pRecreateDisksInfo =
1145
  renameField "RecreateDisksInfo" .
1146
  defaultField [| RecreateDisksAll |] $
1147
  simpleField "disks" [t| RecreateDisksInfo |]
1148

    
1149
-- | Whether to only return configuration data without querying nodes.
1150
pStatic :: Field
1151
pStatic = defaultFalse "static"
1152

    
1153
-- | InstanceSetParams NIC changes.
1154
pInstParamsNicChanges :: Field
1155
pInstParamsNicChanges =
1156
  renameField "InstNicChanges" .
1157
  defaultField [| SetParamsEmpty |] $
1158
  simpleField "nics" [t| SetParamsMods INicParams |]
1159

    
1160
-- | InstanceSetParams Disk changes.
1161
pInstParamsDiskChanges :: Field
1162
pInstParamsDiskChanges =
1163
  renameField "InstDiskChanges" .
1164
  defaultField [| SetParamsEmpty |] $
1165
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1166

    
1167
-- | New runtime memory.
1168
pRuntimeMem :: Field
1169
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1170

    
1171
-- | Change the instance's OS without reinstalling the instance
1172
pOsNameChange :: Field
1173
pOsNameChange = optionalNEStringField "os_name"
1174

    
1175
-- | Disk index for e.g. grow disk.
1176
pDiskIndex :: Field
1177
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1178

    
1179
-- | Disk amount to add or grow to.
1180
pDiskChgAmount :: Field
1181
pDiskChgAmount =
1182
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1183

    
1184
-- | Whether the amount parameter is an absolute target or a relative one.
1185
pDiskChgAbsolute :: Field
1186
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1187

    
1188
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1189
pTargetGroups :: Field
1190
pTargetGroups =
1191
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1192

    
1193
-- | Export mode field.
1194
pExportMode :: Field
1195
pExportMode =
1196
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1197

    
1198
-- | Export target_node field, depends on mode.
1199
pExportTargetNode :: Field
1200
pExportTargetNode =
1201
  renameField "ExportTarget" $
1202
  simpleField "target_node" [t| ExportTarget |]
1203

    
1204
-- | Whether to remove instance after export.
1205
pRemoveInstance :: Field
1206
pRemoveInstance = defaultFalse "remove_instance"
1207

    
1208
-- | Whether to ignore failures while removing instances.
1209
pIgnoreRemoveFailures :: Field
1210
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1211

    
1212
-- | Name of X509 key (remote export only).
1213
pX509KeyName :: Field
1214
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1215

    
1216
-- | Destination X509 CA (remote export only).
1217
pX509DestCA :: Field
1218
pX509DestCA = optionalNEStringField "destination_x509_ca"
1219

    
1220
-- | Search pattern (regular expression). FIXME: this should be
1221
-- compiled at load time?
1222
pTagSearchPattern :: Field
1223
pTagSearchPattern =
1224
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1225

    
1226
-- | Restricted command name.
1227
pRestrictedCommand :: Field
1228
pRestrictedCommand =
1229
  renameField "RestrictedCommand" $
1230
  simpleField "command" [t| NonEmptyString |]
1231

    
1232
-- | Replace disks mode.
1233
pReplaceDisksMode :: Field
1234
pReplaceDisksMode =
1235
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1236

    
1237
-- | List of disk indices.
1238
pReplaceDisksList :: Field
1239
pReplaceDisksList =
1240
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1241

    
1242
-- | Whether do allow failover in migrations.
1243
pAllowFailover :: Field
1244
pAllowFailover = defaultFalse "allow_failover"
1245

    
1246
-- * Test opcode parameters
1247

    
1248
-- | Duration parameter for 'OpTestDelay'.
1249
pDelayDuration :: Field
1250
pDelayDuration =
1251
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1252

    
1253
-- | on_master field for 'OpTestDelay'.
1254
pDelayOnMaster :: Field
1255
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1256

    
1257
-- | on_nodes field for 'OpTestDelay'.
1258
pDelayOnNodes :: Field
1259
pDelayOnNodes =
1260
  renameField "DelayOnNodes" .
1261
  defaultField [| [] |] $
1262
  simpleField "on_nodes" [t| [NonEmptyString] |]
1263

    
1264
-- | Repeat parameter for OpTestDelay.
1265
pDelayRepeat :: Field
1266
pDelayRepeat =
1267
  renameField "DelayRepeat" .
1268
  defaultField [| forceNonNeg (0::Int) |] $
1269
  simpleField "repeat" [t| NonNegative Int |]
1270

    
1271
-- | IAllocator test direction.
1272
pIAllocatorDirection :: Field
1273
pIAllocatorDirection =
1274
  renameField "IAllocatorDirection" $
1275
  simpleField "direction" [t| IAllocatorTestDir |]
1276

    
1277
-- | IAllocator test mode.
1278
pIAllocatorMode :: Field
1279
pIAllocatorMode =
1280
  renameField "IAllocatorMode" $
1281
  simpleField "mode" [t| IAllocatorMode |]
1282

    
1283
-- | IAllocator target name (new instance, node to evac, etc.).
1284
pIAllocatorReqName :: Field
1285
pIAllocatorReqName =
1286
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1287

    
1288
-- | Custom OpTestIAllocator nics.
1289
pIAllocatorNics :: Field
1290
pIAllocatorNics =
1291
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1292

    
1293
-- | Custom OpTestAllocator disks.
1294
pIAllocatorDisks :: Field
1295
pIAllocatorDisks =
1296
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1297

    
1298
-- | IAllocator memory field.
1299
pIAllocatorMemory :: Field
1300
pIAllocatorMemory =
1301
  renameField "IAllocatorMem" .
1302
  optionalField $
1303
  simpleField "memory" [t| NonNegative Int |]
1304

    
1305
-- | IAllocator vcpus field.
1306
pIAllocatorVCpus :: Field
1307
pIAllocatorVCpus =
1308
  renameField "IAllocatorVCpus" .
1309
  optionalField $
1310
  simpleField "vcpus" [t| NonNegative Int |]
1311

    
1312
-- | IAllocator os field.
1313
pIAllocatorOs :: Field
1314
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1315

    
1316
-- | IAllocator instances field.
1317
pIAllocatorInstances :: Field
1318
pIAllocatorInstances =
1319
  renameField "IAllocatorInstances " .
1320
  optionalField $
1321
  simpleField "instances" [t| [NonEmptyString] |]
1322

    
1323
-- | IAllocator evac mode.
1324
pIAllocatorEvacMode :: Field
1325
pIAllocatorEvacMode =
1326
  renameField "IAllocatorEvacMode" .
1327
  optionalField $
1328
  simpleField "evac_mode" [t| NodeEvacMode |]
1329

    
1330
-- | IAllocator spindle use.
1331
pIAllocatorSpindleUse :: Field
1332
pIAllocatorSpindleUse =
1333
  renameField "IAllocatorSpindleUse" .
1334
  defaultField [| forceNonNeg (1::Int) |] $
1335
  simpleField "spindle_use" [t| NonNegative Int |]
1336

    
1337
-- | IAllocator count field.
1338
pIAllocatorCount :: Field
1339
pIAllocatorCount =
1340
  renameField "IAllocatorCount" .
1341
  defaultField [| forceNonNeg (1::Int) |] $
1342
  simpleField "count" [t| NonNegative Int |]
1343

    
1344
-- | 'OpTestJqueue' notify_waitlock.
1345
pJQueueNotifyWaitLock :: Field
1346
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1347

    
1348
-- | 'OpTestJQueue' notify_exec.
1349
pJQueueNotifyExec :: Field
1350
pJQueueNotifyExec = defaultFalse "notify_exec"
1351

    
1352
-- | 'OpTestJQueue' log_messages.
1353
pJQueueLogMessages :: Field
1354
pJQueueLogMessages =
1355
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1356

    
1357
-- | 'OpTestJQueue' fail attribute.
1358
pJQueueFail :: Field
1359
pJQueueFail =
1360
  renameField "JQueueFail" $ defaultFalse "fail"
1361

    
1362
-- | 'OpTestDummy' result field.
1363
pTestDummyResult :: Field
1364
pTestDummyResult =
1365
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1366

    
1367
-- | 'OpTestDummy' messages field.
1368
pTestDummyMessages :: Field
1369
pTestDummyMessages =
1370
  renameField "TestDummyMessages" $
1371
  simpleField "messages" [t| UncheckedValue |]
1372

    
1373
-- | 'OpTestDummy' fail field.
1374
pTestDummyFail :: Field
1375
pTestDummyFail =
1376
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1377

    
1378
-- | 'OpTestDummy' submit_jobs field.
1379
pTestDummySubmitJobs :: Field
1380
pTestDummySubmitJobs =
1381
  renameField "TestDummySubmitJobs" $
1382
  simpleField "submit_jobs" [t| UncheckedValue |]
1383

    
1384
-- * Network parameters
1385

    
1386
-- | Network name.
1387
pNetworkName :: Field
1388
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1389

    
1390
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1391
pNetworkAddress4 :: Field
1392
pNetworkAddress4 =
1393
  renameField "NetworkAddress4" $
1394
  simpleField "network" [t| NonEmptyString |]
1395

    
1396
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1397
pNetworkGateway4 :: Field
1398
pNetworkGateway4 =
1399
  renameField "NetworkGateway4" $
1400
  optionalNEStringField "gateway"
1401

    
1402
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1403
pNetworkAddress6 :: Field
1404
pNetworkAddress6 =
1405
  renameField "NetworkAddress6" $
1406
  optionalNEStringField "network6"
1407

    
1408
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1409
pNetworkGateway6 :: Field
1410
pNetworkGateway6 =
1411
  renameField "NetworkGateway6" $
1412
  optionalNEStringField "gateway6"
1413

    
1414
-- | Network specific mac prefix (that overrides the cluster one).
1415
pNetworkMacPrefix :: Field
1416
pNetworkMacPrefix =
1417
  renameField "NetMacPrefix" $
1418
  optionalNEStringField "mac_prefix"
1419

    
1420
-- | Network add reserved IPs.
1421
pNetworkAddRsvdIps :: Field
1422
pNetworkAddRsvdIps =
1423
  renameField "NetworkAddRsvdIps" .
1424
  optionalField $
1425
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1426

    
1427
-- | Network remove reserved IPs.
1428
pNetworkRemoveRsvdIps :: Field
1429
pNetworkRemoveRsvdIps =
1430
  renameField "NetworkRemoveRsvdIps" .
1431
  optionalField $
1432
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1433

    
1434
-- | Network mode when connecting to a group.
1435
pNetworkMode :: Field
1436
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1437

    
1438
-- | Network link when connecting to a group.
1439
pNetworkLink :: Field
1440
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1441

    
1442
-- * Common opcode parameters
1443

    
1444
-- | Run checks only, don't execute.
1445
pDryRun :: Field
1446
pDryRun = optionalField $ booleanField "dry_run"
1447

    
1448
-- | Debug level.
1449
pDebugLevel :: Field
1450
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1451

    
1452
-- | Opcode priority. Note: python uses a separate constant, we're
1453
-- using the actual value we know it's the default.
1454
pOpPriority :: Field
1455
pOpPriority =
1456
  defaultField [| OpPrioNormal |] $
1457
  simpleField "priority" [t| OpSubmitPriority |]
1458

    
1459
-- | Job dependencies.
1460
pDependencies :: Field
1461
pDependencies =
1462
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1463

    
1464
-- | Comment field.
1465
pComment :: Field
1466
pComment = optionalNullSerField $ stringField "comment"
1467

    
1468
-- | Reason trail field.
1469
pReason :: Field
1470
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1471

    
1472
-- * Entire opcode parameter list
1473

    
1474
-- | Old-style query opcode, with locking.
1475
dOldQuery :: [Field]
1476
dOldQuery =
1477
  [ pOutputFields
1478
  , pNames
1479
  , pUseLocking
1480
  ]
1481

    
1482
-- | Old-style query opcode, without locking.
1483
dOldQueryNoLocking :: [Field]
1484
dOldQueryNoLocking =
1485
  [ pOutputFields
1486
  , pNames
1487
  ]