Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 2e12944a

History | View | Annotate | Download (12.6 kB)

1 b1e81520 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 b1e81520 Iustin Pop
3 b1e81520 Iustin Pop
{-| Implementation of the Ganeti config objects.
4 b1e81520 Iustin Pop
5 b1e81520 Iustin Pop
Some object fields are not implemented yet, and as such they are
6 b1e81520 Iustin Pop
commented out below.
7 b1e81520 Iustin Pop
8 b1e81520 Iustin Pop
-}
9 b1e81520 Iustin Pop
10 b1e81520 Iustin Pop
{-
11 b1e81520 Iustin Pop
12 b1e81520 Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
13 b1e81520 Iustin Pop
14 b1e81520 Iustin Pop
This program is free software; you can redistribute it and/or modify
15 b1e81520 Iustin Pop
it under the terms of the GNU General Public License as published by
16 b1e81520 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
17 b1e81520 Iustin Pop
(at your option) any later version.
18 b1e81520 Iustin Pop
19 b1e81520 Iustin Pop
This program is distributed in the hope that it will be useful, but
20 b1e81520 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
21 b1e81520 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
22 b1e81520 Iustin Pop
General Public License for more details.
23 b1e81520 Iustin Pop
24 b1e81520 Iustin Pop
You should have received a copy of the GNU General Public License
25 b1e81520 Iustin Pop
along with this program; if not, write to the Free Software
26 b1e81520 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
27 b1e81520 Iustin Pop
02110-1301, USA.
28 b1e81520 Iustin Pop
29 b1e81520 Iustin Pop
-}
30 b1e81520 Iustin Pop
31 b1e81520 Iustin Pop
module Ganeti.Objects
32 b1e81520 Iustin Pop
  ( NICMode(..)
33 b1e81520 Iustin Pop
  , PartialNICParams(..)
34 b1e81520 Iustin Pop
  , FilledNICParams(..)
35 b1e81520 Iustin Pop
  , fillNICParams
36 b1e81520 Iustin Pop
  , PartialNIC(..)
37 b1e81520 Iustin Pop
  , DiskMode(..)
38 b1e81520 Iustin Pop
  , DiskType(..)
39 2e12944a Iustin Pop
  , DiskLogicalId(..)
40 b1e81520 Iustin Pop
  , Disk(..)
41 b1e81520 Iustin Pop
  , DiskTemplate(..)
42 b1e81520 Iustin Pop
  , PartialBEParams(..)
43 b1e81520 Iustin Pop
  , FilledBEParams(..)
44 b1e81520 Iustin Pop
  , fillBEParams
45 b1e81520 Iustin Pop
  , Instance(..)
46 b1e81520 Iustin Pop
  , toDictInstance
47 b1e81520 Iustin Pop
  , PartialNDParams(..)
48 b1e81520 Iustin Pop
  , FilledNDParams(..)
49 b1e81520 Iustin Pop
  , fillNDParams
50 b1e81520 Iustin Pop
  , Node(..)
51 b1e81520 Iustin Pop
  , AllocPolicy(..)
52 b1e81520 Iustin Pop
  , NodeGroup(..)
53 b1e81520 Iustin Pop
  , Cluster(..)
54 b1e81520 Iustin Pop
  , ConfigData(..)
55 b1e81520 Iustin Pop
  ) where
56 b1e81520 Iustin Pop
57 b1e81520 Iustin Pop
import Data.Maybe
58 2e12944a Iustin Pop
import Text.JSON (makeObj, showJSON, readJSON, JSON, JSValue(..))
59 2e12944a Iustin Pop
import qualified Text.JSON as J
60 b1e81520 Iustin Pop
61 b1e81520 Iustin Pop
import qualified Ganeti.Constants as C
62 b1e81520 Iustin Pop
import Ganeti.HTools.JSON
63 b1e81520 Iustin Pop
64 b1e81520 Iustin Pop
import Ganeti.THH
65 b1e81520 Iustin Pop
66 b1e81520 Iustin Pop
-- * NIC definitions
67 b1e81520 Iustin Pop
68 b1e81520 Iustin Pop
$(declareSADT "NICMode"
69 b1e81520 Iustin Pop
  [ ("NMBridged", 'C.nicModeBridged)
70 b1e81520 Iustin Pop
  , ("NMRouted",  'C.nicModeRouted)
71 b1e81520 Iustin Pop
  ])
72 b1e81520 Iustin Pop
$(makeJSONInstance ''NICMode)
73 b1e81520 Iustin Pop
74 b1e81520 Iustin Pop
$(buildParam "NIC" "nicp"
75 b1e81520 Iustin Pop
  [ simpleField "mode" [t| NICMode |]
76 b1e81520 Iustin Pop
  , simpleField "link" [t| String  |]
77 b1e81520 Iustin Pop
  ])
78 b1e81520 Iustin Pop
79 b1e81520 Iustin Pop
$(buildObject "PartialNIC" "nic"
80 b1e81520 Iustin Pop
  [ simpleField "mac" [t| String |]
81 b1e81520 Iustin Pop
  , optionalField $ simpleField "ip" [t| String |]
82 b1e81520 Iustin Pop
  , simpleField "nicparams" [t| PartialNICParams |]
83 b1e81520 Iustin Pop
  ])
84 b1e81520 Iustin Pop
85 b1e81520 Iustin Pop
-- * Disk definitions
86 b1e81520 Iustin Pop
87 b1e81520 Iustin Pop
$(declareSADT "DiskMode"
88 b1e81520 Iustin Pop
  [ ("DiskRdOnly", 'C.diskRdonly)
89 b1e81520 Iustin Pop
  , ("DiskRdWr",   'C.diskRdwr)
90 b1e81520 Iustin Pop
  ])
91 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskMode)
92 b1e81520 Iustin Pop
93 b1e81520 Iustin Pop
$(declareSADT "DiskType"
94 b1e81520 Iustin Pop
  [ ("LD_LV",       'C.ldLv)
95 b1e81520 Iustin Pop
  , ("LD_DRBD8",    'C.ldDrbd8)
96 b1e81520 Iustin Pop
  , ("LD_FILE",     'C.ldFile)
97 b1e81520 Iustin Pop
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
98 2e12944a Iustin Pop
  , ("LD_RADOS",    'C.ldRbd)
99 b1e81520 Iustin Pop
  ])
100 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskType)
101 b1e81520 Iustin Pop
102 2e12944a Iustin Pop
-- | The file driver type.
103 2e12944a Iustin Pop
$(declareSADT "FileDriver"
104 2e12944a Iustin Pop
  [ ("FileLoop",   'C.fdLoop)
105 2e12944a Iustin Pop
  , ("FileBlktap", 'C.fdBlktap)
106 2e12944a Iustin Pop
  ])
107 2e12944a Iustin Pop
$(makeJSONInstance ''FileDriver)
108 2e12944a Iustin Pop
109 2e12944a Iustin Pop
-- | The persistent block driver type. Currently only one type is allowed.
110 2e12944a Iustin Pop
$(declareSADT "BlockDriver"
111 2e12944a Iustin Pop
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
112 2e12944a Iustin Pop
  ])
113 2e12944a Iustin Pop
$(makeJSONInstance ''BlockDriver)
114 2e12944a Iustin Pop
115 2e12944a Iustin Pop
-- | Constant for the dev_type key entry in the disk config.
116 2e12944a Iustin Pop
devType :: String
117 2e12944a Iustin Pop
devType = "dev_type"
118 2e12944a Iustin Pop
119 2e12944a Iustin Pop
-- | The disk configuration type. This includes the disk type itself,
120 2e12944a Iustin Pop
-- for a more complete consistency. Note that since in the Python
121 2e12944a Iustin Pop
-- code-base there's no authoritative place where we document the
122 2e12944a Iustin Pop
-- logical id, this is probably a good reference point.
123 2e12944a Iustin Pop
data DiskLogicalId
124 2e12944a Iustin Pop
  = LIDPlain String String  -- ^ Volume group, logical volume
125 2e12944a Iustin Pop
  | LIDDrbd8 String String Int Int Int String
126 2e12944a Iustin Pop
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
127 2e12944a Iustin Pop
  | LIDFile FileDriver String -- ^ Driver, path
128 2e12944a Iustin Pop
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
129 2e12944a Iustin Pop
  | LIDRados String String -- ^ Unused, path
130 2e12944a Iustin Pop
    deriving (Read, Show, Eq)
131 2e12944a Iustin Pop
132 2e12944a Iustin Pop
-- | Mapping from a logical id to a disk type.
133 2e12944a Iustin Pop
lidDiskType :: DiskLogicalId -> DiskType
134 2e12944a Iustin Pop
lidDiskType (LIDPlain {}) = LD_LV
135 2e12944a Iustin Pop
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
136 2e12944a Iustin Pop
lidDiskType (LIDFile  {}) = LD_FILE
137 2e12944a Iustin Pop
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
138 2e12944a Iustin Pop
lidDiskType (LIDRados {}) = LD_RADOS
139 2e12944a Iustin Pop
140 2e12944a Iustin Pop
-- | Builds the extra disk_type field for a given logical id.
141 2e12944a Iustin Pop
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
142 2e12944a Iustin Pop
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
143 2e12944a Iustin Pop
144 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId (logical id only).
145 2e12944a Iustin Pop
encodeDLId :: DiskLogicalId -> JSValue
146 2e12944a Iustin Pop
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
147 2e12944a Iustin Pop
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
148 2e12944a Iustin Pop
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
149 2e12944a Iustin Pop
          , showJSON minorA, showJSON minorB, showJSON key ]
150 2e12944a Iustin Pop
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
151 2e12944a Iustin Pop
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
152 2e12944a Iustin Pop
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
153 2e12944a Iustin Pop
154 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId, composing both the logical id
155 2e12944a Iustin Pop
-- and the extra disk_type field.
156 2e12944a Iustin Pop
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
157 2e12944a Iustin Pop
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
158 2e12944a Iustin Pop
159 2e12944a Iustin Pop
-- | Custom decoder for DiskLogicalId. This is manual for now, since
160 2e12944a Iustin Pop
-- we don't have yet automation for separate-key style fields.
161 2e12944a Iustin Pop
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
162 2e12944a Iustin Pop
decodeDLId obj lid = do
163 2e12944a Iustin Pop
  dtype <- fromObj obj devType
164 2e12944a Iustin Pop
  case dtype of
165 2e12944a Iustin Pop
    LD_DRBD8 ->
166 2e12944a Iustin Pop
      case lid of
167 2e12944a Iustin Pop
        JSArray [nA, nB, p, mA, mB, k] -> do
168 2e12944a Iustin Pop
          nA' <- readJSON nA
169 2e12944a Iustin Pop
          nB' <- readJSON nB
170 2e12944a Iustin Pop
          p'  <- readJSON p
171 2e12944a Iustin Pop
          mA' <- readJSON mA
172 2e12944a Iustin Pop
          mB' <- readJSON mB
173 2e12944a Iustin Pop
          k'  <- readJSON k
174 2e12944a Iustin Pop
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
175 2e12944a Iustin Pop
        _ -> fail $ "Can't read logical_id for DRBD8 type"
176 2e12944a Iustin Pop
    LD_LV ->
177 2e12944a Iustin Pop
      case lid of
178 2e12944a Iustin Pop
        JSArray [vg, lv] -> do
179 2e12944a Iustin Pop
          vg' <- readJSON vg
180 2e12944a Iustin Pop
          lv' <- readJSON lv
181 2e12944a Iustin Pop
          return $ LIDPlain vg' lv'
182 2e12944a Iustin Pop
        _ -> fail $ "Can't read logical_id for plain type"
183 2e12944a Iustin Pop
    LD_FILE ->
184 2e12944a Iustin Pop
      case lid of
185 2e12944a Iustin Pop
        JSArray [driver, path] -> do
186 2e12944a Iustin Pop
          driver' <- readJSON driver
187 2e12944a Iustin Pop
          path'   <- readJSON path
188 2e12944a Iustin Pop
          return $ LIDFile driver' path'
189 2e12944a Iustin Pop
        _ -> fail $ "Can't read logical_id for file type"
190 2e12944a Iustin Pop
    LD_BLOCKDEV ->
191 2e12944a Iustin Pop
      case lid of
192 2e12944a Iustin Pop
        JSArray [driver, path] -> do
193 2e12944a Iustin Pop
          driver' <- readJSON driver
194 2e12944a Iustin Pop
          path'   <- readJSON path
195 2e12944a Iustin Pop
          return $ LIDBlockDev driver' path'
196 2e12944a Iustin Pop
        _ -> fail $ "Can't read logical_id for blockdev type"
197 2e12944a Iustin Pop
    LD_RADOS ->
198 2e12944a Iustin Pop
      case lid of
199 2e12944a Iustin Pop
        JSArray [driver, path] -> do
200 2e12944a Iustin Pop
          driver' <- readJSON driver
201 2e12944a Iustin Pop
          path'   <- readJSON path
202 2e12944a Iustin Pop
          return $ LIDRados driver' path'
203 2e12944a Iustin Pop
        _ -> fail $ "Can't read logical_id for rdb type"
204 2e12944a Iustin Pop
205 b1e81520 Iustin Pop
-- | Disk data structure.
206 b1e81520 Iustin Pop
--
207 b1e81520 Iustin Pop
-- This is declared manually as it's a recursive structure, and our TH
208 b1e81520 Iustin Pop
-- code currently can't build it.
209 b1e81520 Iustin Pop
data Disk = Disk
210 2e12944a Iustin Pop
  { diskLogicalId  :: DiskLogicalId
211 b1e81520 Iustin Pop
--  , diskPhysicalId :: String
212 b1e81520 Iustin Pop
  , diskChildren   :: [Disk]
213 b1e81520 Iustin Pop
  , diskIvName     :: String
214 b1e81520 Iustin Pop
  , diskSize       :: Int
215 b1e81520 Iustin Pop
  , diskMode       :: DiskMode
216 b1e81520 Iustin Pop
  } deriving (Read, Show, Eq)
217 b1e81520 Iustin Pop
218 b1e81520 Iustin Pop
$(buildObjectSerialisation "Disk"
219 2e12944a Iustin Pop
  [ customField 'decodeDLId 'encodeFullDLId $
220 2e12944a Iustin Pop
      simpleField "logical_id"    [t| DiskLogicalId   |]
221 b1e81520 Iustin Pop
--  , simpleField "physical_id" [t| String   |]
222 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
223 b1e81520 Iustin Pop
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
224 b1e81520 Iustin Pop
  , simpleField "size" [t| Int |]
225 b1e81520 Iustin Pop
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
226 b1e81520 Iustin Pop
  ])
227 b1e81520 Iustin Pop
228 b1e81520 Iustin Pop
-- * Instance definitions
229 b1e81520 Iustin Pop
230 b1e81520 Iustin Pop
-- | Instance disk template type. **Copied from HTools/Types.hs**
231 b1e81520 Iustin Pop
$(declareSADT "DiskTemplate"
232 b1e81520 Iustin Pop
  [ ("DTDiskless",   'C.dtDiskless)
233 b1e81520 Iustin Pop
  , ("DTFile",       'C.dtFile)
234 b1e81520 Iustin Pop
  , ("DTSharedFile", 'C.dtSharedFile)
235 b1e81520 Iustin Pop
  , ("DTPlain",      'C.dtPlain)
236 b1e81520 Iustin Pop
  , ("DTBlock",      'C.dtBlock)
237 b1e81520 Iustin Pop
  , ("DTDrbd8",      'C.dtDrbd8)
238 b1e81520 Iustin Pop
  ])
239 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskTemplate)
240 b1e81520 Iustin Pop
241 b1e81520 Iustin Pop
$(declareSADT "AdminState"
242 b1e81520 Iustin Pop
  [ ("AdminOffline", 'C.adminstOffline)
243 b1e81520 Iustin Pop
  , ("AdminDown",    'C.adminstDown)
244 b1e81520 Iustin Pop
  , ("AdminUp",      'C.adminstUp)
245 b1e81520 Iustin Pop
  ])
246 b1e81520 Iustin Pop
$(makeJSONInstance ''AdminState)
247 b1e81520 Iustin Pop
248 b1e81520 Iustin Pop
$(buildParam "BE" "bep" $
249 b1e81520 Iustin Pop
  [ simpleField "minmem"       [t| Int  |]
250 b1e81520 Iustin Pop
  , simpleField "maxmem"       [t| Int  |]
251 b1e81520 Iustin Pop
  , simpleField "vcpus"        [t| Int  |]
252 b1e81520 Iustin Pop
  , simpleField "auto_balance" [t| Bool |]
253 b1e81520 Iustin Pop
  ])
254 b1e81520 Iustin Pop
255 b1e81520 Iustin Pop
$(buildObject "Instance" "inst" $
256 b1e81520 Iustin Pop
  [ simpleField "name"           [t| String             |]
257 b1e81520 Iustin Pop
  , simpleField "primary_node"   [t| String             |]
258 b1e81520 Iustin Pop
  , simpleField "os"             [t| String             |]
259 b1e81520 Iustin Pop
  , simpleField "hypervisor"     [t| String             |]
260 b1e81520 Iustin Pop
--  , simpleField "hvparams"     [t| [(String, String)] |]
261 b1e81520 Iustin Pop
  , simpleField "beparams"       [t| PartialBEParams |]
262 b1e81520 Iustin Pop
--  , simpleField "osparams"     [t| [(String, String)] |]
263 b1e81520 Iustin Pop
  , simpleField "admin_state"    [t| AdminState         |]
264 b1e81520 Iustin Pop
  , simpleField "nics"           [t| [PartialNIC]              |]
265 b1e81520 Iustin Pop
  , simpleField "disks"          [t| [Disk]             |]
266 b1e81520 Iustin Pop
  , simpleField "disk_template"  [t| DiskTemplate       |]
267 b1e81520 Iustin Pop
  , optionalField $ simpleField "network_port" [t| Int |]
268 b1e81520 Iustin Pop
  ]
269 b1e81520 Iustin Pop
  ++ timeStampFields
270 b1e81520 Iustin Pop
  ++ uuidFields
271 b1e81520 Iustin Pop
  ++ serialFields)
272 b1e81520 Iustin Pop
273 b1e81520 Iustin Pop
-- * Node definitions
274 b1e81520 Iustin Pop
275 b1e81520 Iustin Pop
$(buildParam "ND" "ndp" $
276 b1e81520 Iustin Pop
  [ simpleField "oob_program" [t| String |]
277 b1e81520 Iustin Pop
  ])
278 b1e81520 Iustin Pop
279 b1e81520 Iustin Pop
$(buildObject "Node" "node" $
280 b1e81520 Iustin Pop
  [ simpleField "name"             [t| String |]
281 b1e81520 Iustin Pop
  , simpleField "primary_ip"       [t| String |]
282 b1e81520 Iustin Pop
  , simpleField "secondary_ip"     [t| String |]
283 b1e81520 Iustin Pop
  , simpleField "master_candidate" [t| Bool   |]
284 b1e81520 Iustin Pop
  , simpleField "offline"          [t| Bool   |]
285 b1e81520 Iustin Pop
  , simpleField "drained"          [t| Bool   |]
286 b1e81520 Iustin Pop
  , simpleField "group"            [t| String |]
287 b1e81520 Iustin Pop
  , simpleField "master_capable"   [t| Bool   |]
288 b1e81520 Iustin Pop
  , simpleField "vm_capable"       [t| Bool   |]
289 b1e81520 Iustin Pop
--  , simpleField "ndparams"       [t| PartialNDParams |]
290 b1e81520 Iustin Pop
  , simpleField "powered"          [t| Bool   |]
291 b1e81520 Iustin Pop
  ]
292 b1e81520 Iustin Pop
  ++ timeStampFields
293 b1e81520 Iustin Pop
  ++ uuidFields
294 b1e81520 Iustin Pop
  ++ serialFields)
295 b1e81520 Iustin Pop
296 b1e81520 Iustin Pop
-- * NodeGroup definitions
297 b1e81520 Iustin Pop
298 b1e81520 Iustin Pop
-- | The Group allocation policy type.
299 b1e81520 Iustin Pop
--
300 b1e81520 Iustin Pop
-- Note that the order of constructors is important as the automatic
301 b1e81520 Iustin Pop
-- Ord instance will order them in the order they are defined, so when
302 b1e81520 Iustin Pop
-- changing this data type be careful about the interaction with the
303 b1e81520 Iustin Pop
-- desired sorting order.
304 b1e81520 Iustin Pop
--
305 b1e81520 Iustin Pop
-- FIXME: COPIED from Types.hs; we need to eliminate this duplication later
306 b1e81520 Iustin Pop
$(declareSADT "AllocPolicy"
307 b1e81520 Iustin Pop
  [ ("AllocPreferred",   'C.allocPolicyPreferred)
308 b1e81520 Iustin Pop
  , ("AllocLastResort",  'C.allocPolicyLastResort)
309 b1e81520 Iustin Pop
  , ("AllocUnallocable", 'C.allocPolicyUnallocable)
310 b1e81520 Iustin Pop
  ])
311 b1e81520 Iustin Pop
$(makeJSONInstance ''AllocPolicy)
312 b1e81520 Iustin Pop
313 b1e81520 Iustin Pop
$(buildObject "NodeGroup" "group" $
314 b1e81520 Iustin Pop
  [ simpleField "name"         [t| String |]
315 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
316 b1e81520 Iustin Pop
--  , simpleField "ndparams"   [t| PartialNDParams |]
317 b1e81520 Iustin Pop
  , simpleField "alloc_policy" [t| AllocPolicy |]
318 b1e81520 Iustin Pop
  ]
319 b1e81520 Iustin Pop
  ++ timeStampFields
320 b1e81520 Iustin Pop
  ++ uuidFields
321 b1e81520 Iustin Pop
  ++ serialFields)
322 b1e81520 Iustin Pop
323 b1e81520 Iustin Pop
-- * Cluster definitions
324 b1e81520 Iustin Pop
$(buildObject "Cluster" "cluster" $
325 b1e81520 Iustin Pop
  [ simpleField "rsahostkeypub"             [t| String   |]
326 b1e81520 Iustin Pop
  , simpleField "highest_used_port"         [t| Int      |]
327 b1e81520 Iustin Pop
  , simpleField "tcpudp_port_pool"          [t| [Int]    |]
328 b1e81520 Iustin Pop
  , simpleField "mac_prefix"                [t| String   |]
329 b1e81520 Iustin Pop
  , simpleField "volume_group_name"         [t| String   |]
330 b1e81520 Iustin Pop
  , simpleField "reserved_lvs"              [t| [String] |]
331 b1e81520 Iustin Pop
--  , simpleField "drbd_usermode_helper"      [t| String   |]
332 b1e81520 Iustin Pop
-- , simpleField "default_bridge"          [t| String   |]
333 b1e81520 Iustin Pop
-- , simpleField "default_hypervisor"      [t| String   |]
334 b1e81520 Iustin Pop
  , simpleField "master_node"               [t| String   |]
335 b1e81520 Iustin Pop
  , simpleField "master_ip"                 [t| String   |]
336 b1e81520 Iustin Pop
  , simpleField "master_netdev"             [t| String   |]
337 b1e81520 Iustin Pop
-- , simpleField "master_netmask"          [t| String   |]
338 b1e81520 Iustin Pop
  , simpleField "cluster_name"              [t| String   |]
339 b1e81520 Iustin Pop
  , simpleField "file_storage_dir"          [t| String   |]
340 b1e81520 Iustin Pop
-- , simpleField "shared_file_storage_dir" [t| String   |]
341 b1e81520 Iustin Pop
  , simpleField "enabled_hypervisors"       [t| [String] |]
342 b1e81520 Iustin Pop
-- , simpleField "hvparams"                [t| [(String, [(String, String)])] |]
343 b1e81520 Iustin Pop
-- , simpleField "os_hvp"                  [t| [(String, String)] |]
344 b1e81520 Iustin Pop
  , containerField $ simpleField "beparams" [t| FilledBEParams |]
345 b1e81520 Iustin Pop
-- , simpleField "osparams"                [t| [(String, String)] |]
346 b1e81520 Iustin Pop
  , containerField $ simpleField "nicparams" [t| FilledNICParams    |]
347 b1e81520 Iustin Pop
--  , simpleField "ndparams"                  [t| FilledNDParams |]
348 b1e81520 Iustin Pop
  , simpleField "candidate_pool_size"       [t| Int                |]
349 b1e81520 Iustin Pop
  , simpleField "modify_etc_hosts"          [t| Bool               |]
350 b1e81520 Iustin Pop
  , simpleField "modify_ssh_setup"          [t| Bool               |]
351 b1e81520 Iustin Pop
  , simpleField "maintain_node_health"      [t| Bool               |]
352 b1e81520 Iustin Pop
  , simpleField "uid_pool"                  [t| [Int]              |]
353 b1e81520 Iustin Pop
  , simpleField "default_iallocator"        [t| String             |]
354 b1e81520 Iustin Pop
  , simpleField "hidden_os"                 [t| [String]           |]
355 b1e81520 Iustin Pop
  , simpleField "blacklisted_os"            [t| [String]           |]
356 b1e81520 Iustin Pop
  , simpleField "primary_ip_family"         [t| Int                |]
357 b1e81520 Iustin Pop
  , simpleField "prealloc_wipe_disks"       [t| Bool               |]
358 b1e81520 Iustin Pop
 ]
359 b1e81520 Iustin Pop
 ++ serialFields)
360 b1e81520 Iustin Pop
361 b1e81520 Iustin Pop
-- * ConfigData definitions
362 b1e81520 Iustin Pop
363 b1e81520 Iustin Pop
$(buildObject "ConfigData" "config" $
364 b1e81520 Iustin Pop
--  timeStampFields ++
365 b1e81520 Iustin Pop
  [ simpleField "version"       [t| Int                |]
366 b1e81520 Iustin Pop
  , simpleField "cluster"       [t| Cluster            |]
367 b1e81520 Iustin Pop
  , containerField $ simpleField "nodes"      [t| Node     |]
368 b1e81520 Iustin Pop
  , containerField $ simpleField "nodegroups" [t| NodeGroup |]
369 b1e81520 Iustin Pop
  , containerField $ simpleField "instances"  [t| Instance |]
370 b1e81520 Iustin Pop
  ]
371 b1e81520 Iustin Pop
  ++ serialFields)