Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ 3a9fe2bc

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

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

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

    
264
-- * Helper functions and types
265

    
266
-- * Type aliases
267

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

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

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

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

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

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

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

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

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

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

    
310
-- ** Tags
311

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

    
321
-- | Data type holding a tag object (type and object name).
322
data TagObject = TagInstance String
323
               | TagNode     String
324
               | TagGroup    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

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

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

    
353
-- | Name of the tag \"name\" field.
354
tagNameField :: String
355
tagNameField = "name"
356

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

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

    
369
-- ** Disks
370

    
371
-- | Replace disks type.
372
$(declareSADT "ReplaceDisksMode"
373
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
374
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
375
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
376
  , ("ReplaceAuto",         'C.replaceDiskAuto)
377
  ])
378
$(makeJSONInstance ''ReplaceDisksMode)
379

    
380
-- | Disk index type (embedding constraints on the index value via a
381
-- smart constructor).
382
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
383
  deriving (Show, Eq, Ord)
384

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

    
392
instance JSON DiskIndex where
393
  readJSON v = readJSON v >>= mkDiskIndex
394
  showJSON = showJSON . unDiskIndex
395

    
396
-- ** I* param types
397

    
398
-- | Type holding disk access modes.
399
$(declareSADT "DiskAccess"
400
  [ ("DiskReadOnly",  'C.diskRdonly)
401
  , ("DiskReadWrite", 'C.diskRdwr)
402
  ])
403
$(makeJSONInstance ''DiskAccess)
404

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

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

    
424
-- | Disk snapshot definition.
425
$(buildObject "ISnapParams" "snapshot"
426
  [ optionalField $ simpleField C.idiskName [t| String |]])
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
-- | Whether to remove disks.
718
pKeepDisks :: Field
719
pKeepDisks = defaultFalse "keep_disks"
720

    
721
-- * Parameters for node resource model
722

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

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

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

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

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

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

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

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

    
752
-- | List of instance snaps.
753
pInstSnaps :: Field
754
pInstSnaps =
755
  renameField "instSnaps" $
756
  simpleField "disks" [t| SetParamsMods ISnapParams |]
757

    
758
-- | Instance disk template.
759
pDiskTemplate :: Field
760
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
761

    
762
-- | Instance disk template.
763
pOptDiskTemplate :: Field
764
pOptDiskTemplate =
765
  optionalField .
766
  renameField "OptDiskTemplate" $
767
  simpleField "disk_template" [t| DiskTemplate |]
768

    
769
-- | File driver.
770
pFileDriver :: Field
771
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
772

    
773
-- | Directory for storing file-backed disks.
774
pFileStorageDir :: Field
775
pFileStorageDir = optionalNEStringField "file_storage_dir"
776

    
777
-- | Volume group name.
778
pVgName :: Field
779
pVgName = optionalStringField "vg_name"
780

    
781
-- | List of enabled hypervisors.
782
pEnabledHypervisors :: Field
783
pEnabledHypervisors =
784
  optionalField $
785
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
786

    
787
-- | List of enabled disk templates.
788
pEnabledDiskTemplates :: Field
789
pEnabledDiskTemplates =
790
  optionalField $
791
  simpleField "enabled_disk_templates" [t| NonEmpty DiskTemplate |]
792

    
793
-- | Selected hypervisor for an instance.
794
pHypervisor :: Field
795
pHypervisor =
796
  optionalField $
797
  simpleField "hypervisor" [t| Hypervisor |]
798

    
799
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
800
pClusterHvParams :: Field
801
pClusterHvParams =
802
  renameField "ClusterHvParams" .
803
  optionalField $
804
  simpleField "hvparams" [t| Container UncheckedDict |]
805

    
806
-- | Instance hypervisor parameters.
807
pInstHvParams :: Field
808
pInstHvParams =
809
  renameField "InstHvParams" .
810
  defaultField [| toJSObject [] |] $
811
  simpleField "hvparams" [t| UncheckedDict |]
812

    
813
-- | Cluster-wide beparams.
814
pClusterBeParams :: Field
815
pClusterBeParams =
816
  renameField "ClusterBeParams" .
817
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
818

    
819
-- | Instance beparams.
820
pInstBeParams :: Field
821
pInstBeParams =
822
  renameField "InstBeParams" .
823
  defaultField [| toJSObject [] |] $
824
  simpleField "beparams" [t| UncheckedDict |]
825

    
826
-- | Reset instance parameters to default if equal.
827
pResetDefaults :: Field
828
pResetDefaults = defaultFalse "identify_defaults"
829

    
830
-- | Cluster-wide per-OS hypervisor parameter defaults.
831
pOsHvp :: Field
832
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
833

    
834
-- | Cluster-wide OS parameter defaults.
835
pClusterOsParams :: Field
836
pClusterOsParams =
837
  renameField "ClusterOsParams" .
838
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
839

    
840
-- | Instance OS parameters.
841
pInstOsParams :: Field
842
pInstOsParams =
843
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
844
  simpleField "osparams" [t| UncheckedDict |]
845

    
846
-- | Temporary OS parameters (currently only in reinstall, might be
847
-- added to install as well).
848
pTempOsParams :: Field
849
pTempOsParams =
850
  renameField "TempOsParams" .
851
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
852

    
853
-- | Temporary hypervisor parameters, hypervisor-dependent.
854
pTempHvParams :: Field
855
pTempHvParams =
856
  renameField "TempHvParams" .
857
  defaultField [| toJSObject [] |] $
858
  simpleField "hvparams" [t| UncheckedDict |]
859

    
860
-- | Temporary backend parameters.
861
pTempBeParams :: Field
862
pTempBeParams =
863
  renameField "TempBeParams" .
864
  defaultField [| toJSObject [] |] $
865
  simpleField "beparams" [t| UncheckedDict |]
866

    
867
-- | Candidate pool size.
868
pCandidatePoolSize :: Field
869
pCandidatePoolSize =
870
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
871

    
872
-- | Set UID pool, must be list of lists describing UID ranges (two
873
-- items, start and end inclusive.
874
pUidPool :: Field
875
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
876

    
877
-- | Extend UID pool, must be list of lists describing UID ranges (two
878
-- items, start and end inclusive.
879
pAddUids :: Field
880
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
881

    
882
-- | Shrink UID pool, must be list of lists describing UID ranges (two
883
-- items, start and end inclusive) to be removed.
884
pRemoveUids :: Field
885
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
886

    
887
-- | Whether to automatically maintain node health.
888
pMaintainNodeHealth :: Field
889
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
890

    
891
-- | Whether to modify and keep in sync the @/etc/hosts@ files of nodes.
892
pModifyEtcHosts :: Field
893
pModifyEtcHosts = optionalField $ booleanField "modify_etc_hosts"
894

    
895
-- | Whether to wipe disks before allocating them to instances.
896
pPreallocWipeDisks :: Field
897
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
898

    
899
-- | Cluster-wide NIC parameter defaults.
900
pNicParams :: Field
901
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
902

    
903
-- | Instance NIC definitions.
904
pInstNics :: Field
905
pInstNics = simpleField "nics" [t| [INicParams] |]
906

    
907
-- | Cluster-wide node parameter defaults.
908
pNdParams :: Field
909
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
910

    
911
-- | Cluster-wide ipolicy specs.
912
pIpolicy :: Field
913
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
914

    
915
-- | DRBD helper program.
916
pDrbdHelper :: Field
917
pDrbdHelper = optionalStringField "drbd_helper"
918

    
919
-- | Default iallocator for cluster.
920
pDefaultIAllocator :: Field
921
pDefaultIAllocator = optionalStringField "default_iallocator"
922

    
923
-- | Master network device.
924
pMasterNetdev :: Field
925
pMasterNetdev = optionalStringField "master_netdev"
926

    
927
-- | Netmask of the master IP.
928
pMasterNetmask :: Field
929
pMasterNetmask =
930
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
931

    
932
-- | List of reserved LVs.
933
pReservedLvs :: Field
934
pReservedLvs =
935
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
936

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

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

    
950
-- | Whether to use an external master IP address setup script.
951
pUseExternalMipScript :: Field
952
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
953

    
954
-- | Requested fields.
955
pQueryFields :: Field
956
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
957

    
958
-- | Query filter.
959
pQueryFilter :: Field
960
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
961

    
962
-- | OOB command to run.
963
pOobCommand :: Field
964
pOobCommand = simpleField "command" [t| OobCommand |]
965

    
966
-- | Timeout before the OOB helper will be terminated.
967
pOobTimeout :: Field
968
pOobTimeout =
969
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
970

    
971
-- | Ignores the node offline status for power off.
972
pIgnoreStatus :: Field
973
pIgnoreStatus = defaultFalse "ignore_status"
974

    
975
-- | Time in seconds to wait between powering on nodes.
976
pPowerDelay :: Field
977
pPowerDelay =
978
  -- FIXME: we can't use the proper type "NonNegative Double", since
979
  -- the default constant is a plain Double, not a non-negative one.
980
  defaultField [| C.oobPowerDelay |] $
981
  simpleField "power_delay" [t| Double |]
982

    
983
-- | Primary IP address.
984
pPrimaryIp :: Field
985
pPrimaryIp = optionalStringField "primary_ip"
986

    
987
-- | Secondary IP address.
988
pSecondaryIp :: Field
989
pSecondaryIp = optionalNEStringField "secondary_ip"
990

    
991
-- | Whether node is re-added to cluster.
992
pReadd :: Field
993
pReadd = defaultFalse "readd"
994

    
995
-- | Initial node group.
996
pNodeGroup :: Field
997
pNodeGroup = optionalNEStringField "group"
998

    
999
-- | Whether node can become master or master candidate.
1000
pMasterCapable :: Field
1001
pMasterCapable = optionalField $ booleanField "master_capable"
1002

    
1003
-- | Whether node can host instances.
1004
pVmCapable :: Field
1005
pVmCapable = optionalField $ booleanField "vm_capable"
1006

    
1007
-- | List of names.
1008
pNames :: Field
1009
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
1010

    
1011
-- | List of node names.
1012
pNodes :: Field
1013
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
1014

    
1015
-- | Required list of node names.
1016
pRequiredNodes :: Field
1017
pRequiredNodes =
1018
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
1019

    
1020
-- | Storage type.
1021
pStorageType :: Field
1022
pStorageType = simpleField "storage_type" [t| StorageType |]
1023

    
1024
-- | Storage changes (unchecked).
1025
pStorageChanges :: Field
1026
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
1027

    
1028
-- | Whether the node should become a master candidate.
1029
pMasterCandidate :: Field
1030
pMasterCandidate = optionalField $ booleanField "master_candidate"
1031

    
1032
-- | Whether the node should be marked as offline.
1033
pOffline :: Field
1034
pOffline = optionalField $ booleanField "offline"
1035

    
1036
-- | Whether the node should be marked as drained.
1037
pDrained ::Field
1038
pDrained = optionalField $ booleanField "drained"
1039

    
1040
-- | Whether node(s) should be promoted to master candidate if necessary.
1041
pAutoPromote :: Field
1042
pAutoPromote = defaultFalse "auto_promote"
1043

    
1044
-- | Whether the node should be marked as powered
1045
pPowered :: Field
1046
pPowered = optionalField $ booleanField "powered"
1047

    
1048
-- | Iallocator for deciding the target node for shared-storage
1049
-- instances during migrate and failover.
1050
pIallocator :: Field
1051
pIallocator = optionalNEStringField "iallocator"
1052

    
1053
-- | New secondary node.
1054
pRemoteNode :: Field
1055
pRemoteNode = optionalNEStringField "remote_node"
1056

    
1057
-- | Node evacuation mode.
1058
pEvacMode :: Field
1059
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1060

    
1061
-- | Instance creation mode.
1062
pInstCreateMode :: Field
1063
pInstCreateMode =
1064
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1065

    
1066
-- | Do not install the OS (will disable automatic start).
1067
pNoInstall :: Field
1068
pNoInstall = optionalField $ booleanField "no_install"
1069

    
1070
-- | OS type for instance installation.
1071
pInstOs :: Field
1072
pInstOs = optionalNEStringField "os_type"
1073

    
1074
-- | Primary node for an instance.
1075
pPrimaryNode :: Field
1076
pPrimaryNode = optionalNEStringField "pnode"
1077

    
1078
-- | Secondary node for an instance.
1079
pSecondaryNode :: Field
1080
pSecondaryNode = optionalNEStringField "snode"
1081

    
1082
-- | Signed handshake from source (remote import only).
1083
pSourceHandshake :: Field
1084
pSourceHandshake =
1085
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1086

    
1087
-- | Source instance name (remote import only).
1088
pSourceInstance :: Field
1089
pSourceInstance = optionalNEStringField "source_instance_name"
1090

    
1091
-- | How long source instance was given to shut down (remote import only).
1092
-- FIXME: non-negative int, whereas the constant is a plain int.
1093
pSourceShutdownTimeout :: Field
1094
pSourceShutdownTimeout =
1095
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1096
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1097

    
1098
-- | Source X509 CA in PEM format (remote import only).
1099
pSourceX509Ca :: Field
1100
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1101

    
1102
-- | Source node for import.
1103
pSrcNode :: Field
1104
pSrcNode = optionalNEStringField "src_node"
1105

    
1106
-- | Source directory for import.
1107
pSrcPath :: Field
1108
pSrcPath = optionalNEStringField "src_path"
1109

    
1110
-- | Whether to start instance after creation.
1111
pStartInstance :: Field
1112
pStartInstance = defaultTrue "start"
1113

    
1114
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1115
-- migrates to NonEmpty String.
1116
pInstTags :: Field
1117
pInstTags =
1118
  renameField "InstTags" .
1119
  defaultField [| [] |] $
1120
  simpleField "tags" [t| [NonEmptyString] |]
1121

    
1122
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1123
pMultiAllocInstances :: Field
1124
pMultiAllocInstances =
1125
  renameField "InstMultiAlloc" .
1126
  defaultField [| [] |] $
1127
  simpleField "instances"[t| UncheckedList |]
1128

    
1129
-- | Ignore failures parameter.
1130
pIgnoreFailures :: Field
1131
pIgnoreFailures = defaultFalse "ignore_failures"
1132

    
1133
-- | New instance or cluster name.
1134
pNewName :: Field
1135
pNewName = simpleField "new_name" [t| NonEmptyString |]
1136

    
1137
-- | Whether to start the instance even if secondary disks are failing.
1138
pIgnoreSecondaries :: Field
1139
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1140

    
1141
-- | How to reboot the instance.
1142
pRebootType :: Field
1143
pRebootType = simpleField "reboot_type" [t| RebootType |]
1144

    
1145
-- | Whether to ignore recorded disk size.
1146
pIgnoreDiskSize :: Field
1147
pIgnoreDiskSize = defaultFalse "ignore_size"
1148

    
1149
-- | Disk list for recreate disks.
1150
pRecreateDisksInfo :: Field
1151
pRecreateDisksInfo =
1152
  renameField "RecreateDisksInfo" .
1153
  defaultField [| RecreateDisksAll |] $
1154
  simpleField "disks" [t| RecreateDisksInfo |]
1155

    
1156
-- | Whether to only return configuration data without querying nodes.
1157
pStatic :: Field
1158
pStatic = defaultFalse "static"
1159

    
1160
-- | InstanceSetParams NIC changes.
1161
pInstParamsNicChanges :: Field
1162
pInstParamsNicChanges =
1163
  renameField "InstNicChanges" .
1164
  defaultField [| SetParamsEmpty |] $
1165
  simpleField "nics" [t| SetParamsMods INicParams |]
1166

    
1167
-- | InstanceSetParams Disk changes.
1168
pInstParamsDiskChanges :: Field
1169
pInstParamsDiskChanges =
1170
  renameField "InstDiskChanges" .
1171
  defaultField [| SetParamsEmpty |] $
1172
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1173

    
1174
-- | New runtime memory.
1175
pRuntimeMem :: Field
1176
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1177

    
1178
-- | Change the instance's OS without reinstalling the instance
1179
pOsNameChange :: Field
1180
pOsNameChange = optionalNEStringField "os_name"
1181

    
1182
-- | Disk index for e.g. grow disk.
1183
pDiskIndex :: Field
1184
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1185

    
1186
-- | Disk amount to add or grow to.
1187
pDiskChgAmount :: Field
1188
pDiskChgAmount =
1189
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1190

    
1191
-- | Whether the amount parameter is an absolute target or a relative one.
1192
pDiskChgAbsolute :: Field
1193
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1194

    
1195
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1196
pTargetGroups :: Field
1197
pTargetGroups =
1198
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1199

    
1200
-- | Export mode field.
1201
pExportMode :: Field
1202
pExportMode =
1203
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1204

    
1205
-- | Export target_node field, depends on mode.
1206
pExportTargetNode :: Field
1207
pExportTargetNode =
1208
  renameField "ExportTarget" $
1209
  simpleField "target_node" [t| ExportTarget |]
1210

    
1211
-- | Whether to remove instance after export.
1212
pRemoveInstance :: Field
1213
pRemoveInstance = defaultFalse "remove_instance"
1214

    
1215
-- | Whether to ignore failures while removing instances.
1216
pIgnoreRemoveFailures :: Field
1217
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1218

    
1219
-- | Name of X509 key (remote export only).
1220
pX509KeyName :: Field
1221
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1222

    
1223
-- | Destination X509 CA (remote export only).
1224
pX509DestCA :: Field
1225
pX509DestCA = optionalNEStringField "destination_x509_ca"
1226

    
1227
-- | Search pattern (regular expression). FIXME: this should be
1228
-- compiled at load time?
1229
pTagSearchPattern :: Field
1230
pTagSearchPattern =
1231
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1232

    
1233
-- | Restricted command name.
1234
pRestrictedCommand :: Field
1235
pRestrictedCommand =
1236
  renameField "RestrictedCommand" $
1237
  simpleField "command" [t| NonEmptyString |]
1238

    
1239
-- | Replace disks mode.
1240
pReplaceDisksMode :: Field
1241
pReplaceDisksMode =
1242
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1243

    
1244
-- | List of disk indices.
1245
pReplaceDisksList :: Field
1246
pReplaceDisksList =
1247
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1248

    
1249
-- | Whether do allow failover in migrations.
1250
pAllowFailover :: Field
1251
pAllowFailover = defaultFalse "allow_failover"
1252

    
1253
-- * Test opcode parameters
1254

    
1255
-- | Duration parameter for 'OpTestDelay'.
1256
pDelayDuration :: Field
1257
pDelayDuration =
1258
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1259

    
1260
-- | on_master field for 'OpTestDelay'.
1261
pDelayOnMaster :: Field
1262
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1263

    
1264
-- | on_nodes field for 'OpTestDelay'.
1265
pDelayOnNodes :: Field
1266
pDelayOnNodes =
1267
  renameField "DelayOnNodes" .
1268
  defaultField [| [] |] $
1269
  simpleField "on_nodes" [t| [NonEmptyString] |]
1270

    
1271
-- | Repeat parameter for OpTestDelay.
1272
pDelayRepeat :: Field
1273
pDelayRepeat =
1274
  renameField "DelayRepeat" .
1275
  defaultField [| forceNonNeg (0::Int) |] $
1276
  simpleField "repeat" [t| NonNegative Int |]
1277

    
1278
-- | IAllocator test direction.
1279
pIAllocatorDirection :: Field
1280
pIAllocatorDirection =
1281
  renameField "IAllocatorDirection" $
1282
  simpleField "direction" [t| IAllocatorTestDir |]
1283

    
1284
-- | IAllocator test mode.
1285
pIAllocatorMode :: Field
1286
pIAllocatorMode =
1287
  renameField "IAllocatorMode" $
1288
  simpleField "mode" [t| IAllocatorMode |]
1289

    
1290
-- | IAllocator target name (new instance, node to evac, etc.).
1291
pIAllocatorReqName :: Field
1292
pIAllocatorReqName =
1293
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1294

    
1295
-- | Custom OpTestIAllocator nics.
1296
pIAllocatorNics :: Field
1297
pIAllocatorNics =
1298
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1299

    
1300
-- | Custom OpTestAllocator disks.
1301
pIAllocatorDisks :: Field
1302
pIAllocatorDisks =
1303
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1304

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

    
1312
-- | IAllocator vcpus field.
1313
pIAllocatorVCpus :: Field
1314
pIAllocatorVCpus =
1315
  renameField "IAllocatorVCpus" .
1316
  optionalField $
1317
  simpleField "vcpus" [t| NonNegative Int |]
1318

    
1319
-- | IAllocator os field.
1320
pIAllocatorOs :: Field
1321
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1322

    
1323
-- | IAllocator instances field.
1324
pIAllocatorInstances :: Field
1325
pIAllocatorInstances =
1326
  renameField "IAllocatorInstances " .
1327
  optionalField $
1328
  simpleField "instances" [t| [NonEmptyString] |]
1329

    
1330
-- | IAllocator evac mode.
1331
pIAllocatorEvacMode :: Field
1332
pIAllocatorEvacMode =
1333
  renameField "IAllocatorEvacMode" .
1334
  optionalField $
1335
  simpleField "evac_mode" [t| NodeEvacMode |]
1336

    
1337
-- | IAllocator spindle use.
1338
pIAllocatorSpindleUse :: Field
1339
pIAllocatorSpindleUse =
1340
  renameField "IAllocatorSpindleUse" .
1341
  defaultField [| forceNonNeg (1::Int) |] $
1342
  simpleField "spindle_use" [t| NonNegative Int |]
1343

    
1344
-- | IAllocator count field.
1345
pIAllocatorCount :: Field
1346
pIAllocatorCount =
1347
  renameField "IAllocatorCount" .
1348
  defaultField [| forceNonNeg (1::Int) |] $
1349
  simpleField "count" [t| NonNegative Int |]
1350

    
1351
-- | 'OpTestJqueue' notify_waitlock.
1352
pJQueueNotifyWaitLock :: Field
1353
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1354

    
1355
-- | 'OpTestJQueue' notify_exec.
1356
pJQueueNotifyExec :: Field
1357
pJQueueNotifyExec = defaultFalse "notify_exec"
1358

    
1359
-- | 'OpTestJQueue' log_messages.
1360
pJQueueLogMessages :: Field
1361
pJQueueLogMessages =
1362
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1363

    
1364
-- | 'OpTestJQueue' fail attribute.
1365
pJQueueFail :: Field
1366
pJQueueFail =
1367
  renameField "JQueueFail" $ defaultFalse "fail"
1368

    
1369
-- | 'OpTestDummy' result field.
1370
pTestDummyResult :: Field
1371
pTestDummyResult =
1372
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1373

    
1374
-- | 'OpTestDummy' messages field.
1375
pTestDummyMessages :: Field
1376
pTestDummyMessages =
1377
  renameField "TestDummyMessages" $
1378
  simpleField "messages" [t| UncheckedValue |]
1379

    
1380
-- | 'OpTestDummy' fail field.
1381
pTestDummyFail :: Field
1382
pTestDummyFail =
1383
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1384

    
1385
-- | 'OpTestDummy' submit_jobs field.
1386
pTestDummySubmitJobs :: Field
1387
pTestDummySubmitJobs =
1388
  renameField "TestDummySubmitJobs" $
1389
  simpleField "submit_jobs" [t| UncheckedValue |]
1390

    
1391
-- * Network parameters
1392

    
1393
-- | Network name.
1394
pNetworkName :: Field
1395
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1396

    
1397
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1398
pNetworkAddress4 :: Field
1399
pNetworkAddress4 =
1400
  renameField "NetworkAddress4" $
1401
  simpleField "network" [t| NonEmptyString |]
1402

    
1403
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1404
pNetworkGateway4 :: Field
1405
pNetworkGateway4 =
1406
  renameField "NetworkGateway4" $
1407
  optionalNEStringField "gateway"
1408

    
1409
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1410
pNetworkAddress6 :: Field
1411
pNetworkAddress6 =
1412
  renameField "NetworkAddress6" $
1413
  optionalNEStringField "network6"
1414

    
1415
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1416
pNetworkGateway6 :: Field
1417
pNetworkGateway6 =
1418
  renameField "NetworkGateway6" $
1419
  optionalNEStringField "gateway6"
1420

    
1421
-- | Network specific mac prefix (that overrides the cluster one).
1422
pNetworkMacPrefix :: Field
1423
pNetworkMacPrefix =
1424
  renameField "NetMacPrefix" $
1425
  optionalNEStringField "mac_prefix"
1426

    
1427
-- | Network add reserved IPs.
1428
pNetworkAddRsvdIps :: Field
1429
pNetworkAddRsvdIps =
1430
  renameField "NetworkAddRsvdIps" .
1431
  optionalField $
1432
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1433

    
1434
-- | Network remove reserved IPs.
1435
pNetworkRemoveRsvdIps :: Field
1436
pNetworkRemoveRsvdIps =
1437
  renameField "NetworkRemoveRsvdIps" .
1438
  optionalField $
1439
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1440

    
1441
-- | Network mode when connecting to a group.
1442
pNetworkMode :: Field
1443
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1444

    
1445
-- | Network link when connecting to a group.
1446
pNetworkLink :: Field
1447
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1448

    
1449
-- * Common opcode parameters
1450

    
1451
-- | Run checks only, don't execute.
1452
pDryRun :: Field
1453
pDryRun = optionalField $ booleanField "dry_run"
1454

    
1455
-- | Debug level.
1456
pDebugLevel :: Field
1457
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1458

    
1459
-- | Opcode priority. Note: python uses a separate constant, we're
1460
-- using the actual value we know it's the default.
1461
pOpPriority :: Field
1462
pOpPriority =
1463
  defaultField [| OpPrioNormal |] $
1464
  simpleField "priority" [t| OpSubmitPriority |]
1465

    
1466
-- | Job dependencies.
1467
pDependencies :: Field
1468
pDependencies =
1469
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1470

    
1471
-- | Comment field.
1472
pComment :: Field
1473
pComment = optionalNullSerField $ stringField "comment"
1474

    
1475
-- | Reason trail field.
1476
pReason :: Field
1477
pReason = simpleField C.opcodeReason [t| ReasonTrail |]
1478

    
1479
-- * Entire opcode parameter list
1480

    
1481
-- | Old-style query opcode, with locking.
1482
dOldQuery :: [Field]
1483
dOldQuery =
1484
  [ pOutputFields
1485
  , pNames
1486
  , pUseLocking
1487
  ]
1488

    
1489
-- | Old-style query opcode, without locking.
1490
dOldQueryNoLocking :: [Field]
1491
dOldQueryNoLocking =
1492
  [ pOutputFields
1493
  , pNames
1494
  ]