Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / OpParams.hs @ f0e4b2a4

History | View | Annotate | Download (42.6 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
  , pAllowRuntimeChgs
98
  , pInstDisks
99
  , pDiskTemplate
100
  , pOptDiskTemplate
101
  , pFileDriver
102
  , pFileStorageDir
103
  , pVgName
104
  , pEnabledHypervisors
105
  , pHypervisor
106
  , pClusterHvParams
107
  , pInstHvParams
108
  , pClusterBeParams
109
  , pInstBeParams
110
  , pResetDefaults
111
  , pOsHvp
112
  , pClusterOsParams
113
  , pInstOsParams
114
  , pCandidatePoolSize
115
  , pUidPool
116
  , pAddUids
117
  , pRemoveUids
118
  , pMaintainNodeHealth
119
  , pPreallocWipeDisks
120
  , pNicParams
121
  , pInstNics
122
  , pNdParams
123
  , pIpolicy
124
  , pDrbdHelper
125
  , pDefaultIAllocator
126
  , pMasterNetdev
127
  , pMasterNetmask
128
  , pReservedLvs
129
  , pHiddenOs
130
  , pBlacklistedOs
131
  , pUseExternalMipScript
132
  , pQueryFields
133
  , pQueryFilter
134
  , pOobCommand
135
  , pOobTimeout
136
  , pIgnoreStatus
137
  , pPowerDelay
138
  , pPrimaryIp
139
  , pSecondaryIp
140
  , pReadd
141
  , pNodeGroup
142
  , pMasterCapable
143
  , pVmCapable
144
  , pNames
145
  , pNodes
146
  , pRequiredNodes
147
  , pStorageType
148
  , pStorageChanges
149
  , pMasterCandidate
150
  , pOffline
151
  , pDrained
152
  , pAutoPromote
153
  , pPowered
154
  , pIallocator
155
  , pRemoteNode
156
  , pEvacMode
157
  , pInstCreateMode
158
  , pNoInstall
159
  , pInstOs
160
  , pPrimaryNode
161
  , pSecondaryNode
162
  , pSourceHandshake
163
  , pSourceInstance
164
  , pSourceShutdownTimeout
165
  , pSourceX509Ca
166
  , pSrcNode
167
  , pSrcPath
168
  , pStartInstance
169
  , pInstTags
170
  , pMultiAllocInstances
171
  , pTempOsParams
172
  , pTempHvParams
173
  , pTempBeParams
174
  , pIgnoreFailures
175
  , pNewName
176
  , pIgnoreSecondaries
177
  , pRebootType
178
  , pIgnoreDiskSize
179
  , pRecreateDisksInfo
180
  , pStatic
181
  , pInstParamsNicChanges
182
  , pInstParamsDiskChanges
183
  , pRuntimeMem
184
  , pOsNameChange
185
  , pDiskIndex
186
  , pDiskChgAmount
187
  , pDiskChgAbsolute
188
  , pTargetGroups
189
  , pExportMode
190
  , pExportTargetNode
191
  , pRemoveInstance
192
  , pIgnoreRemoveFailures
193
  , pX509KeyName
194
  , pX509DestCA
195
  , pTagSearchPattern
196
  , pRestrictedCommand
197
  , pReplaceDisksMode
198
  , pReplaceDisksList
199
  , pAllowFailover
200
  , pDelayDuration
201
  , pDelayOnMaster
202
  , pDelayOnNodes
203
  , pDelayRepeat
204
  , pIAllocatorDirection
205
  , pIAllocatorMode
206
  , pIAllocatorReqName
207
  , pIAllocatorNics
208
  , pIAllocatorDisks
209
  , pIAllocatorMemory
210
  , pIAllocatorVCpus
211
  , pIAllocatorOs
212
  , pIAllocatorInstances
213
  , pIAllocatorEvacMode
214
  , pIAllocatorSpindleUse
215
  , pIAllocatorCount
216
  , pJQueueNotifyWaitLock
217
  , pJQueueNotifyExec
218
  , pJQueueLogMessages
219
  , pJQueueFail
220
  , pTestDummyResult
221
  , pTestDummyMessages
222
  , pTestDummyFail
223
  , pTestDummySubmitJobs
224
  , pNetworkName
225
  , pNetworkAddress4
226
  , pNetworkGateway4
227
  , pNetworkAddress6
228
  , pNetworkGateway6
229
  , pNetworkMacPrefix
230
  , pNetworkAddRsvdIps
231
  , pNetworkRemoveRsvdIps
232
  , pNetworkMode
233
  , pNetworkLink
234
  , pDryRun
235
  , pDebugLevel
236
  , pOpPriority
237
  , pDependencies
238
  , pComment
239
  , pReason
240
  , pEnabledStorageTypes
241
  , dOldQuery
242
  , dOldQueryNoLocking
243
  ) where
244

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

    
252
import Ganeti.BasicTypes
253
import qualified Ganeti.Constants as C
254
import Ganeti.THH
255
import Ganeti.JSON
256
import Ganeti.Types
257
import qualified Ganeti.Query.Language as Qlang
258

    
259
-- * Helper functions and types
260

    
261
-- * Type aliases
262

    
263
-- | Build a boolean field.
264
booleanField :: String -> Field
265
booleanField = flip simpleField [t| Bool |]
266

    
267
-- | Default a field to 'False'.
268
defaultFalse :: String -> Field
269
defaultFalse = defaultField [| False |] . booleanField
270

    
271
-- | Default a field to 'True'.
272
defaultTrue :: String -> Field
273
defaultTrue = defaultField [| True |] . booleanField
274

    
275
-- | An alias for a 'String' field.
276
stringField :: String -> Field
277
stringField = flip simpleField [t| String |]
278

    
279
-- | An alias for an optional string field.
280
optionalStringField :: String -> Field
281
optionalStringField = optionalField . stringField
282

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

    
287
-- | Unchecked value, should be replaced by a better definition.
288
type UncheckedValue = JSValue
289

    
290
-- | Unchecked dict, should be replaced by a better definition.
291
type UncheckedDict = JSObject JSValue
292

    
293
-- | Unchecked list, shoild be replaced by a better definition.
294
type UncheckedList = [JSValue]
295

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

    
305
-- ** Tags
306

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

    
316
-- | Data type holding a tag object (type and object name).
317
data TagObject = TagInstance String
318
               | TagNode     String
319
               | TagGroup    String
320
               | TagCluster
321
               deriving (Show, Eq)
322

    
323
-- | Tag type for a given tag object.
324
tagTypeOf :: TagObject -> TagType
325
tagTypeOf (TagInstance {}) = TagTypeInstance
326
tagTypeOf (TagNode     {}) = TagTypeNode
327
tagTypeOf (TagGroup    {}) = TagTypeGroup
328
tagTypeOf (TagCluster  {}) = TagTypeCluster
329

    
330
-- | Gets the potential tag object name.
331
tagNameOf :: TagObject -> Maybe String
332
tagNameOf (TagInstance s) = Just s
333
tagNameOf (TagNode     s) = Just s
334
tagNameOf (TagGroup    s) = Just s
335
tagNameOf  TagCluster     = Nothing
336

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

    
348
-- | Name of the tag \"name\" field.
349
tagNameField :: String
350
tagNameField = "name"
351

    
352
-- | Custom encoder for 'TagObject' as represented in an opcode.
353
encodeTagObject :: TagObject -> (JSValue, [(String, JSValue)])
354
encodeTagObject t = ( showJSON (tagTypeOf t)
355
                    , [(tagNameField, maybe JSNull showJSON (tagNameOf t))] )
356

    
357
-- | Custom decoder for 'TagObject' as represented in an opcode.
358
decodeTagObject :: (Monad m) => [(String, JSValue)] -> JSValue -> m TagObject
359
decodeTagObject obj kind = do
360
  ttype <- fromJVal kind
361
  tname <- fromObj obj tagNameField
362
  tagObjectFrom ttype tname
363

    
364
-- ** Disks
365

    
366
-- | Replace disks type.
367
$(declareSADT "ReplaceDisksMode"
368
  [ ("ReplaceOnPrimary",    'C.replaceDiskPri)
369
  , ("ReplaceOnSecondary",  'C.replaceDiskSec)
370
  , ("ReplaceNewSecondary", 'C.replaceDiskChg)
371
  , ("ReplaceAuto",         'C.replaceDiskAuto)
372
  ])
373
$(makeJSONInstance ''ReplaceDisksMode)
374

    
375
-- | Disk index type (embedding constraints on the index value via a
376
-- smart constructor).
377
newtype DiskIndex = DiskIndex { unDiskIndex :: Int }
378
  deriving (Show, Eq, Ord)
379

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

    
387
instance JSON DiskIndex where
388
  readJSON v = readJSON v >>= mkDiskIndex
389
  showJSON = showJSON . unDiskIndex
390

    
391
-- ** I* param types
392

    
393
-- | Type holding disk access modes.
394
$(declareSADT "DiskAccess"
395
  [ ("DiskReadOnly",  'C.diskRdonly)
396
  , ("DiskReadWrite", 'C.diskRdwr)
397
  ])
398
$(makeJSONInstance ''DiskAccess)
399

    
400
-- | NIC modification definition.
401
$(buildObject "INicParams" "inic"
402
  [ optionalField $ simpleField C.inicMac  [t| NonEmptyString |]
403
  , optionalField $ simpleField C.inicIp   [t| String         |]
404
  , optionalField $ simpleField C.inicMode [t| NonEmptyString |]
405
  , optionalField $ simpleField C.inicLink [t| NonEmptyString |]
406
  ])
407

    
408
-- | Disk modification definition. FIXME: disksize should be VTYPE_UNIT.
409
$(buildObject "IDiskParams" "idisk"
410
  [ optionalField $ simpleField C.idiskSize   [t| Int            |]
411
  , optionalField $ simpleField C.idiskMode   [t| DiskAccess     |]
412
  , optionalField $ simpleField C.idiskAdopt  [t| NonEmptyString |]
413
  , optionalField $ simpleField C.idiskVg     [t| NonEmptyString |]
414
  , optionalField $ simpleField C.idiskMetavg [t| NonEmptyString |]
415
  ])
416

    
417
-- | Disk changes type for OpInstanceRecreateDisks. This is a bit
418
-- strange, because the type in Python is something like Either
419
-- [DiskIndex] [DiskChanges], but we can't represent the type of an
420
-- empty list in JSON, so we have to add a custom case for the empty
421
-- list.
422
data RecreateDisksInfo
423
  = RecreateDisksAll
424
  | RecreateDisksIndices (NonEmpty DiskIndex)
425
  | RecreateDisksParams (NonEmpty (DiskIndex, IDiskParams))
426
    deriving (Eq, Show)
427

    
428
readRecreateDisks :: JSValue -> Text.JSON.Result RecreateDisksInfo
429
readRecreateDisks (JSArray []) = return RecreateDisksAll
430
readRecreateDisks v =
431
  case readJSON v::Text.JSON.Result [DiskIndex] of
432
    Text.JSON.Ok indices -> liftM RecreateDisksIndices (mkNonEmpty indices)
433
    _ -> case readJSON v::Text.JSON.Result [(DiskIndex, IDiskParams)] of
434
           Text.JSON.Ok params -> liftM RecreateDisksParams (mkNonEmpty params)
435
           _ -> fail $ "Can't parse disk information as either list of disk"
436
                ++ " indices or list of disk parameters; value received:"
437
                ++ show (pp_value v)
438

    
439
instance JSON RecreateDisksInfo where
440
  readJSON = readRecreateDisks
441
  showJSON  RecreateDisksAll            = showJSON ()
442
  showJSON (RecreateDisksIndices idx)   = showJSON idx
443
  showJSON (RecreateDisksParams params) = showJSON params
444

    
445
-- | Simple type for old-style ddm changes.
446
data DdmOldChanges = DdmOldIndex (NonNegative Int)
447
                   | DdmOldMod DdmSimple
448
                     deriving (Eq, Show)
449

    
450
readDdmOldChanges :: JSValue -> Text.JSON.Result DdmOldChanges
451
readDdmOldChanges v =
452
  case readJSON v::Text.JSON.Result (NonNegative Int) of
453
    Text.JSON.Ok nn -> return $ DdmOldIndex nn
454
    _ -> case readJSON v::Text.JSON.Result DdmSimple of
455
           Text.JSON.Ok ddms -> return $ DdmOldMod ddms
456
           _ -> fail $ "Can't parse value '" ++ show (pp_value v) ++ "' as"
457
                ++ " either index or modification"
458

    
459
instance JSON DdmOldChanges where
460
  showJSON (DdmOldIndex i) = showJSON i
461
  showJSON (DdmOldMod m)   = showJSON m
462
  readJSON = readDdmOldChanges
463

    
464
-- | Instance disk or nic modifications.
465
data SetParamsMods a
466
  = SetParamsEmpty
467
  | SetParamsDeprecated (NonEmpty (DdmOldChanges, a))
468
  | SetParamsNew (NonEmpty (DdmFull, Int, a))
469
    deriving (Eq, Show)
470

    
471
-- | Custom deserialiser for 'SetParamsMods'.
472
readSetParams :: (JSON a) => JSValue -> Text.JSON.Result (SetParamsMods a)
473
readSetParams (JSArray []) = return SetParamsEmpty
474
readSetParams v =
475
  case readJSON v::Text.JSON.Result [(DdmOldChanges, JSValue)] of
476
    Text.JSON.Ok _ -> liftM SetParamsDeprecated $ readJSON v
477
    _ -> liftM SetParamsNew $ readJSON v
478

    
479
instance (JSON a) => JSON (SetParamsMods a) where
480
  showJSON SetParamsEmpty = showJSON ()
481
  showJSON (SetParamsDeprecated v) = showJSON v
482
  showJSON (SetParamsNew v) = showJSON v
483
  readJSON = readSetParams
484

    
485
-- | Custom type for target_node parameter of OpBackupExport, which
486
-- varies depending on mode. FIXME: this uses an UncheckedList since
487
-- we don't care about individual rows (just like the Python code
488
-- tests). But the proper type could be parsed if we wanted.
489
data ExportTarget = ExportTargetLocal NonEmptyString
490
                  | ExportTargetRemote UncheckedList
491
                    deriving (Eq, Show)
492

    
493
-- | Custom reader for 'ExportTarget'.
494
readExportTarget :: JSValue -> Text.JSON.Result ExportTarget
495
readExportTarget (JSString s) = liftM ExportTargetLocal $
496
                                mkNonEmpty (fromJSString s)
497
readExportTarget (JSArray arr) = return $ ExportTargetRemote arr
498
readExportTarget v = fail $ "Invalid value received for 'target_node': " ++
499
                     show (pp_value v)
500

    
501
instance JSON ExportTarget where
502
  showJSON (ExportTargetLocal s)  = showJSON s
503
  showJSON (ExportTargetRemote l) = showJSON l
504
  readJSON = readExportTarget
505

    
506
-- * Parameters
507

    
508
-- | A required instance name (for single-instance LUs).
509
pInstanceName :: Field
510
pInstanceName = simpleField "instance_name" [t| String |]
511

    
512
-- | A list of instances.
513
pInstances :: Field
514
pInstances = defaultField [| [] |] $
515
             simpleField "instances" [t| [NonEmptyString] |]
516

    
517
-- | A generic name.
518
pName :: Field
519
pName = simpleField "name" [t| NonEmptyString |]
520

    
521
-- | Tags list.
522
pTagsList :: Field
523
pTagsList = simpleField "tags" [t| [String] |]
524

    
525
-- | Tags object.
526
pTagsObject :: Field
527
pTagsObject =
528
  customField 'decodeTagObject 'encodeTagObject [tagNameField] $
529
  simpleField "kind" [t| TagObject |]
530

    
531
-- | Selected output fields.
532
pOutputFields :: Field
533
pOutputFields = simpleField "output_fields" [t| [NonEmptyString] |]
534

    
535
-- | How long to wait for instance to shut down.
536
pShutdownTimeout :: Field
537
pShutdownTimeout = defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
538
                   simpleField "shutdown_timeout" [t| NonNegative Int |]
539

    
540
-- | Another name for the shutdown timeout, because we like to be
541
-- inconsistent.
542
pShutdownTimeout' :: Field
543
pShutdownTimeout' =
544
  renameField "InstShutdownTimeout" .
545
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
546
  simpleField "timeout" [t| NonNegative Int |]
547

    
548
-- | Whether to shutdown the instance in backup-export.
549
pShutdownInstance :: Field
550
pShutdownInstance = defaultTrue "shutdown"
551

    
552
-- | Whether to force the operation.
553
pForce :: Field
554
pForce = defaultFalse "force"
555

    
556
-- | Whether to ignore offline nodes.
557
pIgnoreOfflineNodes :: Field
558
pIgnoreOfflineNodes = defaultFalse "ignore_offline_nodes"
559

    
560
-- | A required node name (for single-node LUs).
561
pNodeName :: Field
562
pNodeName = simpleField "node_name" [t| NonEmptyString |]
563

    
564
-- | List of nodes.
565
pNodeNames :: Field
566
pNodeNames =
567
  defaultField [| [] |] $ simpleField "node_names" [t| [NonEmptyString] |]
568

    
569
-- | A required node group name (for single-group LUs).
570
pGroupName :: Field
571
pGroupName = simpleField "group_name" [t| NonEmptyString |]
572

    
573
-- | Migration type (live\/non-live).
574
pMigrationMode :: Field
575
pMigrationMode =
576
  renameField "MigrationMode" .
577
  optionalField $
578
  simpleField "mode" [t| MigrationMode |]
579

    
580
-- | Obsolete \'live\' migration mode (boolean).
581
pMigrationLive :: Field
582
pMigrationLive =
583
  renameField "OldLiveMode" . optionalField $ booleanField "live"
584

    
585
-- | Migration cleanup parameter.
586
pMigrationCleanup :: Field
587
pMigrationCleanup = renameField "MigrationCleanup" $ defaultFalse "cleanup"
588

    
589
-- | Whether to force an unknown OS variant.
590
pForceVariant :: Field
591
pForceVariant = defaultFalse "force_variant"
592

    
593
-- | Whether to wait for the disk to synchronize.
594
pWaitForSync :: Field
595
pWaitForSync = defaultTrue "wait_for_sync"
596

    
597
-- | Whether to wait for the disk to synchronize (defaults to false).
598
pWaitForSyncFalse :: Field
599
pWaitForSyncFalse = defaultField [| False |] pWaitForSync
600

    
601
-- | Whether to ignore disk consistency
602
pIgnoreConsistency :: Field
603
pIgnoreConsistency = defaultFalse "ignore_consistency"
604

    
605
-- | Storage name.
606
pStorageName :: Field
607
pStorageName =
608
  renameField "StorageName" $ simpleField "name" [t| NonEmptyString |]
609

    
610
-- | Whether to use synchronization.
611
pUseLocking :: Field
612
pUseLocking = defaultFalse "use_locking"
613

    
614
-- | Whether to employ opportunistic locking for nodes, meaning nodes already
615
-- locked by another opcode won't be considered for instance allocation (only
616
-- when an iallocator is used).
617
pOpportunisticLocking :: Field
618
pOpportunisticLocking = defaultFalse "opportunistic_locking"
619

    
620
-- | Whether to check name.
621
pNameCheck :: Field
622
pNameCheck = defaultTrue "name_check"
623

    
624
-- | Instance allocation policy.
625
pNodeGroupAllocPolicy :: Field
626
pNodeGroupAllocPolicy = optionalField $
627
                        simpleField "alloc_policy" [t| AllocPolicy |]
628

    
629
-- | Default node parameters for group.
630
pGroupNodeParams :: Field
631
pGroupNodeParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
632

    
633
-- | Resource(s) to query for.
634
pQueryWhat :: Field
635
pQueryWhat = simpleField "what" [t| Qlang.QueryTypeOp |]
636

    
637
-- | Whether to release locks as soon as possible.
638
pEarlyRelease :: Field
639
pEarlyRelease = defaultFalse "early_release"
640

    
641
-- | Whether to ensure instance's IP address is inactive.
642
pIpCheck :: Field
643
pIpCheck = defaultTrue "ip_check"
644

    
645
-- | Check for conflicting IPs.
646
pIpConflictsCheck :: Field
647
pIpConflictsCheck = defaultTrue "conflicts_check"
648

    
649
-- | Do not remember instance state changes.
650
pNoRemember :: Field
651
pNoRemember = defaultFalse "no_remember"
652

    
653
-- | Target node for instance migration/failover.
654
pMigrationTargetNode :: Field
655
pMigrationTargetNode = optionalNEStringField "target_node"
656

    
657
-- | Target node for instance move (required).
658
pMoveTargetNode :: Field
659
pMoveTargetNode =
660
  renameField "MoveTargetNode" $
661
  simpleField "target_node" [t| NonEmptyString |]
662

    
663
-- | Pause instance at startup.
664
pStartupPaused :: Field
665
pStartupPaused = defaultFalse "startup_paused"
666

    
667
-- | Verbose mode.
668
pVerbose :: Field
669
pVerbose = defaultFalse "verbose"
670

    
671
-- ** Parameters for cluster verification
672

    
673
-- | Whether to simulate errors (useful for debugging).
674
pDebugSimulateErrors :: Field
675
pDebugSimulateErrors = defaultFalse "debug_simulate_errors"
676

    
677
-- | Error codes.
678
pErrorCodes :: Field
679
pErrorCodes = defaultFalse "error_codes"
680

    
681
-- | Which checks to skip.
682
pSkipChecks :: Field
683
pSkipChecks = defaultField [| Set.empty |] $
684
              simpleField "skip_checks" [t| Set.Set VerifyOptionalChecks |]
685

    
686
-- | List of error codes that should be treated as warnings.
687
pIgnoreErrors :: Field
688
pIgnoreErrors = defaultField [| Set.empty |] $
689
                simpleField "ignore_errors" [t| Set.Set CVErrorCode |]
690

    
691
-- | Optional group name.
692
pOptGroupName :: Field
693
pOptGroupName = renameField "OptGroupName" .
694
                optionalField $ simpleField "group_name" [t| NonEmptyString |]
695

    
696
-- | Disk templates' parameter defaults.
697
pDiskParams :: Field
698
pDiskParams = optionalField $
699
              simpleField "diskparams" [t| GenericContainer DiskTemplate
700
                                           UncheckedDict |]
701

    
702
-- * Parameters for node resource model
703

    
704
-- | Set hypervisor states.
705
pHvState :: Field
706
pHvState = optionalField $ simpleField "hv_state" [t| UncheckedDict |]
707

    
708
-- | Set disk states.
709
pDiskState :: Field
710
pDiskState = optionalField $ simpleField "disk_state" [t| UncheckedDict |]
711

    
712
-- | Whether to ignore ipolicy violations.
713
pIgnoreIpolicy :: Field
714
pIgnoreIpolicy = defaultFalse "ignore_ipolicy"
715

    
716
-- | Allow runtime changes while migrating.
717
pAllowRuntimeChgs :: Field
718
pAllowRuntimeChgs = defaultTrue "allow_runtime_changes"
719

    
720
-- | Utility type for OpClusterSetParams.
721
type TestClusterOsListItem = (DdmSimple, NonEmptyString)
722

    
723
-- | Utility type of OsList.
724
type TestClusterOsList = [TestClusterOsListItem]
725

    
726
-- Utility type for NIC definitions.
727
--type TestNicDef = INicParams
728

    
729
-- | List of instance disks.
730
pInstDisks :: Field
731
pInstDisks = renameField "instDisks" $ simpleField "disks" [t| [IDiskParams] |]
732

    
733
-- | Instance disk template.
734
pDiskTemplate :: Field
735
pDiskTemplate = simpleField "disk_template" [t| DiskTemplate |]
736

    
737
-- | Instance disk template.
738
pOptDiskTemplate :: Field
739
pOptDiskTemplate =
740
  optionalField .
741
  renameField "OptDiskTemplate" $
742
  simpleField "disk_template" [t| DiskTemplate |]
743

    
744
-- | File driver.
745
pFileDriver :: Field
746
pFileDriver = optionalField $ simpleField "file_driver" [t| FileDriver |]
747

    
748
-- | Directory for storing file-backed disks.
749
pFileStorageDir :: Field
750
pFileStorageDir = optionalNEStringField "file_storage_dir"
751

    
752
-- | Volume group name.
753
pVgName :: Field
754
pVgName = optionalStringField "vg_name"
755

    
756
-- | List of enabled hypervisors.
757
pEnabledHypervisors :: Field
758
pEnabledHypervisors =
759
  optionalField $
760
  simpleField "enabled_hypervisors" [t| NonEmpty Hypervisor |]
761

    
762
-- | List of enabled storage methods.
763
pEnabledStorageTypes :: Field
764
pEnabledStorageTypes =
765
  optionalField $
766
  simpleField "enabled_storage_types" [t| NonEmpty StorageType |]
767

    
768
-- | Selected hypervisor for an instance.
769
pHypervisor :: Field
770
pHypervisor =
771
  optionalField $
772
  simpleField "hypervisor" [t| Hypervisor |]
773

    
774
-- | Cluster-wide hypervisor parameters, hypervisor-dependent.
775
pClusterHvParams :: Field
776
pClusterHvParams =
777
  renameField "ClusterHvParams" .
778
  optionalField $
779
  simpleField "hvparams" [t| Container UncheckedDict |]
780

    
781
-- | Instance hypervisor parameters.
782
pInstHvParams :: Field
783
pInstHvParams =
784
  renameField "InstHvParams" .
785
  defaultField [| toJSObject [] |] $
786
  simpleField "hvparams" [t| UncheckedDict |]
787

    
788
-- | Cluster-wide beparams.
789
pClusterBeParams :: Field
790
pClusterBeParams =
791
  renameField "ClusterBeParams" .
792
  optionalField $ simpleField "beparams" [t| UncheckedDict |]
793

    
794
-- | Instance beparams.
795
pInstBeParams :: Field
796
pInstBeParams =
797
  renameField "InstBeParams" .
798
  defaultField [| toJSObject [] |] $
799
  simpleField "beparams" [t| UncheckedDict |]
800

    
801
-- | Reset instance parameters to default if equal.
802
pResetDefaults :: Field
803
pResetDefaults = defaultFalse "identify_defaults"
804

    
805
-- | Cluster-wide per-OS hypervisor parameter defaults.
806
pOsHvp :: Field
807
pOsHvp = optionalField $ simpleField "os_hvp" [t| Container UncheckedDict |]
808

    
809
-- | Cluster-wide OS parameter defaults.
810
pClusterOsParams :: Field
811
pClusterOsParams =
812
  renameField "ClusterOsParams" .
813
  optionalField $ simpleField "osparams" [t| Container UncheckedDict |]
814

    
815
-- | Instance OS parameters.
816
pInstOsParams :: Field
817
pInstOsParams =
818
  renameField "InstOsParams" . defaultField [| toJSObject [] |] $
819
  simpleField "osparams" [t| UncheckedDict |]
820

    
821
-- | Temporary OS parameters (currently only in reinstall, might be
822
-- added to install as well).
823
pTempOsParams :: Field
824
pTempOsParams =
825
  renameField "TempOsParams" .
826
  optionalField $ simpleField "osparams" [t| UncheckedDict |]
827

    
828
-- | Temporary hypervisor parameters, hypervisor-dependent.
829
pTempHvParams :: Field
830
pTempHvParams =
831
  renameField "TempHvParams" .
832
  defaultField [| toJSObject [] |] $
833
  simpleField "hvparams" [t| UncheckedDict |]
834

    
835
-- | Temporary backend parameters.
836
pTempBeParams :: Field
837
pTempBeParams =
838
  renameField "TempBeParams" .
839
  defaultField [| toJSObject [] |] $
840
  simpleField "beparams" [t| UncheckedDict |]
841

    
842
-- | Candidate pool size.
843
pCandidatePoolSize :: Field
844
pCandidatePoolSize =
845
  optionalField $ simpleField "candidate_pool_size" [t| Positive Int |]
846

    
847
-- | Set UID pool, must be list of lists describing UID ranges (two
848
-- items, start and end inclusive.
849
pUidPool :: Field
850
pUidPool = optionalField $ simpleField "uid_pool" [t| [[(Int, Int)]] |]
851

    
852
-- | Extend UID pool, must be list of lists describing UID ranges (two
853
-- items, start and end inclusive.
854
pAddUids :: Field
855
pAddUids = optionalField $ simpleField "add_uids" [t| [[(Int, Int)]] |]
856

    
857
-- | Shrink UID pool, must be list of lists describing UID ranges (two
858
-- items, start and end inclusive) to be removed.
859
pRemoveUids :: Field
860
pRemoveUids = optionalField $ simpleField "remove_uids" [t| [[(Int, Int)]] |]
861

    
862
-- | Whether to automatically maintain node health.
863
pMaintainNodeHealth :: Field
864
pMaintainNodeHealth = optionalField $ booleanField "maintain_node_health"
865

    
866
-- | Whether to wipe disks before allocating them to instances.
867
pPreallocWipeDisks :: Field
868
pPreallocWipeDisks = optionalField $ booleanField "prealloc_wipe_disks"
869

    
870
-- | Cluster-wide NIC parameter defaults.
871
pNicParams :: Field
872
pNicParams = optionalField $ simpleField "nicparams" [t| INicParams |]
873

    
874
-- | Instance NIC definitions.
875
pInstNics :: Field
876
pInstNics = simpleField "nics" [t| [INicParams] |]
877

    
878
-- | Cluster-wide node parameter defaults.
879
pNdParams :: Field
880
pNdParams = optionalField $ simpleField "ndparams" [t| UncheckedDict |]
881

    
882
-- | Cluster-wide ipolicy specs.
883
pIpolicy :: Field
884
pIpolicy = optionalField $ simpleField "ipolicy" [t| UncheckedDict |]
885

    
886
-- | DRBD helper program.
887
pDrbdHelper :: Field
888
pDrbdHelper = optionalStringField "drbd_helper"
889

    
890
-- | Default iallocator for cluster.
891
pDefaultIAllocator :: Field
892
pDefaultIAllocator = optionalStringField "default_iallocator"
893

    
894
-- | Master network device.
895
pMasterNetdev :: Field
896
pMasterNetdev = optionalStringField "master_netdev"
897

    
898
-- | Netmask of the master IP.
899
pMasterNetmask :: Field
900
pMasterNetmask =
901
  optionalField $ simpleField "master_netmask" [t| NonNegative Int |]
902

    
903
-- | List of reserved LVs.
904
pReservedLvs :: Field
905
pReservedLvs =
906
  optionalField $ simpleField "reserved_lvs" [t| [NonEmptyString] |]
907

    
908
-- | Modify list of hidden operating systems: each modification must
909
-- have two items, the operation and the OS name; the operation can be
910
-- add or remove.
911
pHiddenOs :: Field
912
pHiddenOs = optionalField $ simpleField "hidden_os" [t| TestClusterOsList |]
913

    
914
-- | Modify list of blacklisted operating systems: each modification
915
-- must have two items, the operation and the OS name; the operation
916
-- can be add or remove.
917
pBlacklistedOs :: Field
918
pBlacklistedOs =
919
  optionalField $ simpleField "blacklisted_os" [t| TestClusterOsList |]
920

    
921
-- | Whether to use an external master IP address setup script.
922
pUseExternalMipScript :: Field
923
pUseExternalMipScript = optionalField $ booleanField "use_external_mip_script"
924

    
925
-- | Requested fields.
926
pQueryFields :: Field
927
pQueryFields = simpleField "fields" [t| [NonEmptyString] |]
928

    
929
-- | Query filter.
930
pQueryFilter :: Field
931
pQueryFilter = simpleField "qfilter" [t| Qlang.Filter String |]
932

    
933
-- | OOB command to run.
934
pOobCommand :: Field
935
pOobCommand = simpleField "command" [t| OobCommand |]
936

    
937
-- | Timeout before the OOB helper will be terminated.
938
pOobTimeout :: Field
939
pOobTimeout =
940
  defaultField [| C.oobTimeout |] $ simpleField "timeout" [t| Int |]
941

    
942
-- | Ignores the node offline status for power off.
943
pIgnoreStatus :: Field
944
pIgnoreStatus = defaultFalse "ignore_status"
945

    
946
-- | Time in seconds to wait between powering on nodes.
947
pPowerDelay :: Field
948
pPowerDelay =
949
  -- FIXME: we can't use the proper type "NonNegative Double", since
950
  -- the default constant is a plain Double, not a non-negative one.
951
  defaultField [| C.oobPowerDelay |] $
952
  simpleField "power_delay" [t| Double |]
953

    
954
-- | Primary IP address.
955
pPrimaryIp :: Field
956
pPrimaryIp = optionalStringField "primary_ip"
957

    
958
-- | Secondary IP address.
959
pSecondaryIp :: Field
960
pSecondaryIp = optionalNEStringField "secondary_ip"
961

    
962
-- | Whether node is re-added to cluster.
963
pReadd :: Field
964
pReadd = defaultFalse "readd"
965

    
966
-- | Initial node group.
967
pNodeGroup :: Field
968
pNodeGroup = optionalNEStringField "group"
969

    
970
-- | Whether node can become master or master candidate.
971
pMasterCapable :: Field
972
pMasterCapable = optionalField $ booleanField "master_capable"
973

    
974
-- | Whether node can host instances.
975
pVmCapable :: Field
976
pVmCapable = optionalField $ booleanField "vm_capable"
977

    
978
-- | List of names.
979
pNames :: Field
980
pNames = defaultField [| [] |] $ simpleField "names" [t| [NonEmptyString] |]
981

    
982
-- | List of node names.
983
pNodes :: Field
984
pNodes = defaultField [| [] |] $ simpleField "nodes" [t| [NonEmptyString] |]
985

    
986
-- | Required list of node names.
987
pRequiredNodes :: Field
988
pRequiredNodes =
989
  renameField "ReqNodes " $ simpleField "nodes" [t| [NonEmptyString] |]
990

    
991
-- | Storage type.
992
pStorageType :: Field
993
pStorageType = simpleField "storage_type" [t| StorageType |]
994

    
995
-- | Storage changes (unchecked).
996
pStorageChanges :: Field
997
pStorageChanges = simpleField "changes" [t| UncheckedDict |]
998

    
999
-- | Whether the node should become a master candidate.
1000
pMasterCandidate :: Field
1001
pMasterCandidate = optionalField $ booleanField "master_candidate"
1002

    
1003
-- | Whether the node should be marked as offline.
1004
pOffline :: Field
1005
pOffline = optionalField $ booleanField "offline"
1006

    
1007
-- | Whether the node should be marked as drained.
1008
pDrained ::Field
1009
pDrained = optionalField $ booleanField "drained"
1010

    
1011
-- | Whether node(s) should be promoted to master candidate if necessary.
1012
pAutoPromote :: Field
1013
pAutoPromote = defaultFalse "auto_promote"
1014

    
1015
-- | Whether the node should be marked as powered
1016
pPowered :: Field
1017
pPowered = optionalField $ booleanField "powered"
1018

    
1019
-- | Iallocator for deciding the target node for shared-storage
1020
-- instances during migrate and failover.
1021
pIallocator :: Field
1022
pIallocator = optionalNEStringField "iallocator"
1023

    
1024
-- | New secondary node.
1025
pRemoteNode :: Field
1026
pRemoteNode = optionalNEStringField "remote_node"
1027

    
1028
-- | Node evacuation mode.
1029
pEvacMode :: Field
1030
pEvacMode = renameField "EvacMode" $ simpleField "mode" [t| NodeEvacMode |]
1031

    
1032
-- | Instance creation mode.
1033
pInstCreateMode :: Field
1034
pInstCreateMode =
1035
  renameField "InstCreateMode" $ simpleField "mode" [t| InstCreateMode |]
1036

    
1037
-- | Do not install the OS (will disable automatic start).
1038
pNoInstall :: Field
1039
pNoInstall = optionalField $ booleanField "no_install"
1040

    
1041
-- | OS type for instance installation.
1042
pInstOs :: Field
1043
pInstOs = optionalNEStringField "os_type"
1044

    
1045
-- | Primary node for an instance.
1046
pPrimaryNode :: Field
1047
pPrimaryNode = optionalNEStringField "pnode"
1048

    
1049
-- | Secondary node for an instance.
1050
pSecondaryNode :: Field
1051
pSecondaryNode = optionalNEStringField "snode"
1052

    
1053
-- | Signed handshake from source (remote import only).
1054
pSourceHandshake :: Field
1055
pSourceHandshake =
1056
  optionalField $ simpleField "source_handshake" [t| UncheckedList |]
1057

    
1058
-- | Source instance name (remote import only).
1059
pSourceInstance :: Field
1060
pSourceInstance = optionalNEStringField "source_instance_name"
1061

    
1062
-- | How long source instance was given to shut down (remote import only).
1063
-- FIXME: non-negative int, whereas the constant is a plain int.
1064
pSourceShutdownTimeout :: Field
1065
pSourceShutdownTimeout =
1066
  defaultField [| forceNonNeg C.defaultShutdownTimeout |] $
1067
  simpleField "source_shutdown_timeout" [t| NonNegative Int |]
1068

    
1069
-- | Source X509 CA in PEM format (remote import only).
1070
pSourceX509Ca :: Field
1071
pSourceX509Ca = optionalNEStringField "source_x509_ca"
1072

    
1073
-- | Source node for import.
1074
pSrcNode :: Field
1075
pSrcNode = optionalNEStringField "src_node"
1076

    
1077
-- | Source directory for import.
1078
pSrcPath :: Field
1079
pSrcPath = optionalNEStringField "src_path"
1080

    
1081
-- | Whether to start instance after creation.
1082
pStartInstance :: Field
1083
pStartInstance = defaultTrue "start"
1084

    
1085
-- | Instance tags. FIXME: unify/simplify with pTags, once that
1086
-- migrates to NonEmpty String.
1087
pInstTags :: Field
1088
pInstTags =
1089
  renameField "InstTags" .
1090
  defaultField [| [] |] $
1091
  simpleField "tags" [t| [NonEmptyString] |]
1092

    
1093
-- | Unchecked list of OpInstanceCreate, used in OpInstanceMultiAlloc.
1094
pMultiAllocInstances :: Field
1095
pMultiAllocInstances =
1096
  renameField "InstMultiAlloc" .
1097
  defaultField [| [] |] $
1098
  simpleField "instances"[t| UncheckedList |]
1099

    
1100
-- | Ignore failures parameter.
1101
pIgnoreFailures :: Field
1102
pIgnoreFailures = defaultFalse "ignore_failures"
1103

    
1104
-- | New instance or cluster name.
1105
pNewName :: Field
1106
pNewName = simpleField "new_name" [t| NonEmptyString |]
1107

    
1108
-- | Whether to start the instance even if secondary disks are failing.
1109
pIgnoreSecondaries :: Field
1110
pIgnoreSecondaries = defaultFalse "ignore_secondaries"
1111

    
1112
-- | How to reboot the instance.
1113
pRebootType :: Field
1114
pRebootType = simpleField "reboot_type" [t| RebootType |]
1115

    
1116
-- | Whether to ignore recorded disk size.
1117
pIgnoreDiskSize :: Field
1118
pIgnoreDiskSize = defaultFalse "ignore_size"
1119

    
1120
-- | Disk list for recreate disks.
1121
pRecreateDisksInfo :: Field
1122
pRecreateDisksInfo =
1123
  renameField "RecreateDisksInfo" .
1124
  defaultField [| RecreateDisksAll |] $
1125
  simpleField "disks" [t| RecreateDisksInfo |]
1126

    
1127
-- | Whether to only return configuration data without querying nodes.
1128
pStatic :: Field
1129
pStatic = defaultFalse "static"
1130

    
1131
-- | InstanceSetParams NIC changes.
1132
pInstParamsNicChanges :: Field
1133
pInstParamsNicChanges =
1134
  renameField "InstNicChanges" .
1135
  defaultField [| SetParamsEmpty |] $
1136
  simpleField "nics" [t| SetParamsMods INicParams |]
1137

    
1138
-- | InstanceSetParams Disk changes.
1139
pInstParamsDiskChanges :: Field
1140
pInstParamsDiskChanges =
1141
  renameField "InstDiskChanges" .
1142
  defaultField [| SetParamsEmpty |] $
1143
  simpleField "disks" [t| SetParamsMods IDiskParams |]
1144

    
1145
-- | New runtime memory.
1146
pRuntimeMem :: Field
1147
pRuntimeMem = optionalField $ simpleField "runtime_mem" [t| Positive Int |]
1148

    
1149
-- | Change the instance's OS without reinstalling the instance
1150
pOsNameChange :: Field
1151
pOsNameChange = optionalNEStringField "os_name"
1152

    
1153
-- | Disk index for e.g. grow disk.
1154
pDiskIndex :: Field
1155
pDiskIndex = renameField "DiskIndex " $ simpleField "disk" [t| DiskIndex |]
1156

    
1157
-- | Disk amount to add or grow to.
1158
pDiskChgAmount :: Field
1159
pDiskChgAmount =
1160
  renameField "DiskChgAmount" $ simpleField "amount" [t| NonNegative Int |]
1161

    
1162
-- | Whether the amount parameter is an absolute target or a relative one.
1163
pDiskChgAbsolute :: Field
1164
pDiskChgAbsolute = renameField "DiskChkAbsolute" $ defaultFalse "absolute"
1165

    
1166
-- | Destination group names or UUIDs (defaults to \"all but current group\".
1167
pTargetGroups :: Field
1168
pTargetGroups =
1169
  optionalField $ simpleField "target_groups" [t| [NonEmptyString] |]
1170

    
1171
-- | Export mode field.
1172
pExportMode :: Field
1173
pExportMode =
1174
  renameField "ExportMode" $ simpleField "mode" [t| ExportMode |]
1175

    
1176
-- | Export target_node field, depends on mode.
1177
pExportTargetNode :: Field
1178
pExportTargetNode =
1179
  renameField "ExportTarget" $
1180
  simpleField "target_node" [t| ExportTarget |]
1181

    
1182
-- | Whether to remove instance after export.
1183
pRemoveInstance :: Field
1184
pRemoveInstance = defaultFalse "remove_instance"
1185

    
1186
-- | Whether to ignore failures while removing instances.
1187
pIgnoreRemoveFailures :: Field
1188
pIgnoreRemoveFailures = defaultFalse "ignore_remove_failures"
1189

    
1190
-- | Name of X509 key (remote export only).
1191
pX509KeyName :: Field
1192
pX509KeyName = optionalField $ simpleField "x509_key_name" [t| UncheckedList |]
1193

    
1194
-- | Destination X509 CA (remote export only).
1195
pX509DestCA :: Field
1196
pX509DestCA = optionalNEStringField "destination_x509_ca"
1197

    
1198
-- | Search pattern (regular expression). FIXME: this should be
1199
-- compiled at load time?
1200
pTagSearchPattern :: Field
1201
pTagSearchPattern =
1202
  renameField "TagSearchPattern" $ simpleField "pattern" [t| NonEmptyString |]
1203

    
1204
-- | Restricted command name.
1205
pRestrictedCommand :: Field
1206
pRestrictedCommand =
1207
  renameField "RestrictedCommand" $
1208
  simpleField "command" [t| NonEmptyString |]
1209

    
1210
-- | Replace disks mode.
1211
pReplaceDisksMode :: Field
1212
pReplaceDisksMode =
1213
  renameField "ReplaceDisksMode" $ simpleField "mode" [t| ReplaceDisksMode |]
1214

    
1215
-- | List of disk indices.
1216
pReplaceDisksList :: Field
1217
pReplaceDisksList =
1218
  renameField "ReplaceDisksList" $ simpleField "disks" [t| [DiskIndex] |]
1219

    
1220
-- | Whether do allow failover in migrations.
1221
pAllowFailover :: Field
1222
pAllowFailover = defaultFalse "allow_failover"
1223

    
1224
-- * Test opcode parameters
1225

    
1226
-- | Duration parameter for 'OpTestDelay'.
1227
pDelayDuration :: Field
1228
pDelayDuration =
1229
  renameField "DelayDuration" $ simpleField "duration" [t| Double |]
1230

    
1231
-- | on_master field for 'OpTestDelay'.
1232
pDelayOnMaster :: Field
1233
pDelayOnMaster = renameField "DelayOnMaster" $ defaultTrue "on_master"
1234

    
1235
-- | on_nodes field for 'OpTestDelay'.
1236
pDelayOnNodes :: Field
1237
pDelayOnNodes =
1238
  renameField "DelayOnNodes" .
1239
  defaultField [| [] |] $
1240
  simpleField "on_nodes" [t| [NonEmptyString] |]
1241

    
1242
-- | Repeat parameter for OpTestDelay.
1243
pDelayRepeat :: Field
1244
pDelayRepeat =
1245
  renameField "DelayRepeat" .
1246
  defaultField [| forceNonNeg (0::Int) |] $
1247
  simpleField "repeat" [t| NonNegative Int |]
1248

    
1249
-- | IAllocator test direction.
1250
pIAllocatorDirection :: Field
1251
pIAllocatorDirection =
1252
  renameField "IAllocatorDirection" $
1253
  simpleField "direction" [t| IAllocatorTestDir |]
1254

    
1255
-- | IAllocator test mode.
1256
pIAllocatorMode :: Field
1257
pIAllocatorMode =
1258
  renameField "IAllocatorMode" $
1259
  simpleField "mode" [t| IAllocatorMode |]
1260

    
1261
-- | IAllocator target name (new instance, node to evac, etc.).
1262
pIAllocatorReqName :: Field
1263
pIAllocatorReqName =
1264
  renameField "IAllocatorReqName" $ simpleField "name" [t| NonEmptyString |]
1265

    
1266
-- | Custom OpTestIAllocator nics.
1267
pIAllocatorNics :: Field
1268
pIAllocatorNics =
1269
  renameField "IAllocatorNics" $ simpleField "nics" [t| [UncheckedDict] |]
1270

    
1271
-- | Custom OpTestAllocator disks.
1272
pIAllocatorDisks :: Field
1273
pIAllocatorDisks =
1274
  renameField "IAllocatorDisks" $ simpleField "disks" [t| UncheckedList |]
1275

    
1276
-- | IAllocator memory field.
1277
pIAllocatorMemory :: Field
1278
pIAllocatorMemory =
1279
  renameField "IAllocatorMem" .
1280
  optionalField $
1281
  simpleField "memory" [t| NonNegative Int |]
1282

    
1283
-- | IAllocator vcpus field.
1284
pIAllocatorVCpus :: Field
1285
pIAllocatorVCpus =
1286
  renameField "IAllocatorVCpus" .
1287
  optionalField $
1288
  simpleField "vcpus" [t| NonNegative Int |]
1289

    
1290
-- | IAllocator os field.
1291
pIAllocatorOs :: Field
1292
pIAllocatorOs = renameField "IAllocatorOs" $ optionalNEStringField "os"
1293

    
1294
-- | IAllocator instances field.
1295
pIAllocatorInstances :: Field
1296
pIAllocatorInstances =
1297
  renameField "IAllocatorInstances " .
1298
  optionalField $
1299
  simpleField "instances" [t| [NonEmptyString] |]
1300

    
1301
-- | IAllocator evac mode.
1302
pIAllocatorEvacMode :: Field
1303
pIAllocatorEvacMode =
1304
  renameField "IAllocatorEvacMode" .
1305
  optionalField $
1306
  simpleField "evac_mode" [t| NodeEvacMode |]
1307

    
1308
-- | IAllocator spindle use.
1309
pIAllocatorSpindleUse :: Field
1310
pIAllocatorSpindleUse =
1311
  renameField "IAllocatorSpindleUse" .
1312
  defaultField [| forceNonNeg (1::Int) |] $
1313
  simpleField "spindle_use" [t| NonNegative Int |]
1314

    
1315
-- | IAllocator count field.
1316
pIAllocatorCount :: Field
1317
pIAllocatorCount =
1318
  renameField "IAllocatorCount" .
1319
  defaultField [| forceNonNeg (1::Int) |] $
1320
  simpleField "count" [t| NonNegative Int |]
1321

    
1322
-- | 'OpTestJqueue' notify_waitlock.
1323
pJQueueNotifyWaitLock :: Field
1324
pJQueueNotifyWaitLock = defaultFalse "notify_waitlock"
1325

    
1326
-- | 'OpTestJQueue' notify_exec.
1327
pJQueueNotifyExec :: Field
1328
pJQueueNotifyExec = defaultFalse "notify_exec"
1329

    
1330
-- | 'OpTestJQueue' log_messages.
1331
pJQueueLogMessages :: Field
1332
pJQueueLogMessages =
1333
  defaultField [| [] |] $ simpleField "log_messages" [t| [String] |]
1334

    
1335
-- | 'OpTestJQueue' fail attribute.
1336
pJQueueFail :: Field
1337
pJQueueFail =
1338
  renameField "JQueueFail" $ defaultFalse "fail"
1339

    
1340
-- | 'OpTestDummy' result field.
1341
pTestDummyResult :: Field
1342
pTestDummyResult =
1343
  renameField "TestDummyResult" $ simpleField "result" [t| UncheckedValue |]
1344

    
1345
-- | 'OpTestDummy' messages field.
1346
pTestDummyMessages :: Field
1347
pTestDummyMessages =
1348
  renameField "TestDummyMessages" $
1349
  simpleField "messages" [t| UncheckedValue |]
1350

    
1351
-- | 'OpTestDummy' fail field.
1352
pTestDummyFail :: Field
1353
pTestDummyFail =
1354
  renameField "TestDummyFail" $ simpleField "fail" [t| UncheckedValue |]
1355

    
1356
-- | 'OpTestDummy' submit_jobs field.
1357
pTestDummySubmitJobs :: Field
1358
pTestDummySubmitJobs =
1359
  renameField "TestDummySubmitJobs" $
1360
  simpleField "submit_jobs" [t| UncheckedValue |]
1361

    
1362
-- * Network parameters
1363

    
1364
-- | Network name.
1365
pNetworkName :: Field
1366
pNetworkName = simpleField "network_name" [t| NonEmptyString |]
1367

    
1368
-- | Network address (IPv4 subnet). FIXME: no real type for this.
1369
pNetworkAddress4 :: Field
1370
pNetworkAddress4 =
1371
  renameField "NetworkAddress4" $
1372
  simpleField "network" [t| NonEmptyString |]
1373

    
1374
-- | Network gateway (IPv4 address). FIXME: no real type for this.
1375
pNetworkGateway4 :: Field
1376
pNetworkGateway4 =
1377
  renameField "NetworkGateway4" $
1378
  optionalNEStringField "gateway"
1379

    
1380
-- | Network address (IPv6 subnet). FIXME: no real type for this.
1381
pNetworkAddress6 :: Field
1382
pNetworkAddress6 =
1383
  renameField "NetworkAddress6" $
1384
  optionalNEStringField "network6"
1385

    
1386
-- | Network gateway (IPv6 address). FIXME: no real type for this.
1387
pNetworkGateway6 :: Field
1388
pNetworkGateway6 =
1389
  renameField "NetworkGateway6" $
1390
  optionalNEStringField "gateway6"
1391

    
1392
-- | Network specific mac prefix (that overrides the cluster one).
1393
pNetworkMacPrefix :: Field
1394
pNetworkMacPrefix =
1395
  renameField "NetMacPrefix" $
1396
  optionalNEStringField "mac_prefix"
1397

    
1398
-- | Network add reserved IPs.
1399
pNetworkAddRsvdIps :: Field
1400
pNetworkAddRsvdIps =
1401
  renameField "NetworkAddRsvdIps" .
1402
  optionalField $
1403
  simpleField "add_reserved_ips" [t| [NonEmptyString] |]
1404

    
1405
-- | Network remove reserved IPs.
1406
pNetworkRemoveRsvdIps :: Field
1407
pNetworkRemoveRsvdIps =
1408
  renameField "NetworkRemoveRsvdIps" .
1409
  optionalField $
1410
  simpleField "remove_reserved_ips" [t| [NonEmptyString] |]
1411

    
1412
-- | Network mode when connecting to a group.
1413
pNetworkMode :: Field
1414
pNetworkMode = simpleField "network_mode" [t| NICMode |]
1415

    
1416
-- | Network link when connecting to a group.
1417
pNetworkLink :: Field
1418
pNetworkLink = simpleField "network_link" [t| NonEmptyString |]
1419

    
1420
-- * Common opcode parameters
1421

    
1422
-- | Run checks only, don't execute.
1423
pDryRun :: Field
1424
pDryRun = optionalField $ booleanField "dry_run"
1425

    
1426
-- | Debug level.
1427
pDebugLevel :: Field
1428
pDebugLevel = optionalField $ simpleField "debug_level" [t| NonNegative Int |]
1429

    
1430
-- | Opcode priority. Note: python uses a separate constant, we're
1431
-- using the actual value we know it's the default.
1432
pOpPriority :: Field
1433
pOpPriority =
1434
  defaultField [| OpPrioNormal |] $
1435
  simpleField "priority" [t| OpSubmitPriority |]
1436

    
1437
-- | Job dependencies.
1438
pDependencies :: Field
1439
pDependencies =
1440
  optionalNullSerField $ simpleField "depends" [t| [JobDependency] |]
1441

    
1442
-- | Comment field.
1443
pComment :: Field
1444
pComment = optionalNullSerField $ stringField "comment"
1445

    
1446
-- | The description of the state change reason.
1447
pReason :: Field
1448
pReason = simpleField "reason" [t| (InstReasonSrc, NonEmptyString) |]
1449

    
1450
-- * Entire opcode parameter list
1451

    
1452
-- | Old-style query opcode, with locking.
1453
dOldQuery :: [Field]
1454
dOldQuery =
1455
  [ pOutputFields
1456
  , pNames
1457
  , pUseLocking
1458
  ]
1459

    
1460
-- | Old-style query opcode, without locking.
1461
dOldQueryNoLocking :: [Field]
1462
dOldQueryNoLocking =
1463
  [ pOutputFields
1464
  , pNames
1465
  ]