Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ d5a93a80

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