Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ cb44e3db

History | View | Annotate | Download (23.5 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 3a991f2d Iustin Pop
Copyright (C) 2011, 2012, 2013 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 9d4cc8ed Iustin Pop
  ( VType(..)
33 9d4cc8ed Iustin Pop
  , vTypeFromRaw
34 9d4cc8ed Iustin Pop
  , HvParams
35 b09cce64 Iustin Pop
  , OsParams
36 b09cce64 Iustin Pop
  , PartialNicParams(..)
37 b09cce64 Iustin Pop
  , FilledNicParams(..)
38 b09cce64 Iustin Pop
  , fillNicParams
39 2af78b97 Iustin Pop
  , allNicParamFields
40 b09cce64 Iustin Pop
  , PartialNic(..)
41 8d2b6a12 Iustin Pop
  , FileDriver(..)
42 8d2b6a12 Iustin Pop
  , BlockDriver(..)
43 b1e81520 Iustin Pop
  , DiskMode(..)
44 b1e81520 Iustin Pop
  , DiskType(..)
45 2e12944a Iustin Pop
  , DiskLogicalId(..)
46 b1e81520 Iustin Pop
  , Disk(..)
47 b1e81520 Iustin Pop
  , DiskTemplate(..)
48 b09cce64 Iustin Pop
  , PartialBeParams(..)
49 b09cce64 Iustin Pop
  , FilledBeParams(..)
50 b09cce64 Iustin Pop
  , fillBeParams
51 2af78b97 Iustin Pop
  , allBeParamFields
52 c4f65a0e Agata Murawska
  , AdminState(..)
53 c4f65a0e Agata Murawska
  , adminStateFromRaw
54 b1e81520 Iustin Pop
  , Instance(..)
55 b1e81520 Iustin Pop
  , toDictInstance
56 b1e81520 Iustin Pop
  , PartialNDParams(..)
57 b1e81520 Iustin Pop
  , FilledNDParams(..)
58 b1e81520 Iustin Pop
  , fillNDParams
59 2af78b97 Iustin Pop
  , allNDParamFields
60 b1e81520 Iustin Pop
  , Node(..)
61 da45c352 Iustin Pop
  , NodeRole(..)
62 da45c352 Iustin Pop
  , nodeRoleToRaw
63 da45c352 Iustin Pop
  , roleDescription
64 b1e81520 Iustin Pop
  , AllocPolicy(..)
65 7514fe92 Iustin Pop
  , FilledISpecParams(..)
66 7514fe92 Iustin Pop
  , PartialISpecParams(..)
67 7514fe92 Iustin Pop
  , fillISpecParams
68 2af78b97 Iustin Pop
  , allISpecParamFields
69 7514fe92 Iustin Pop
  , FilledIPolicy(..)
70 7514fe92 Iustin Pop
  , PartialIPolicy(..)
71 7514fe92 Iustin Pop
  , fillIPolicy
72 b09cce64 Iustin Pop
  , DiskParams
73 b1e81520 Iustin Pop
  , NodeGroup(..)
74 a957e150 Iustin Pop
  , IpFamily(..)
75 a957e150 Iustin Pop
  , ipFamilyToVersion
76 adb77e3a Iustin Pop
  , fillDict
77 b09cce64 Iustin Pop
  , ClusterHvParams
78 b09cce64 Iustin Pop
  , OsHvParams
79 b09cce64 Iustin Pop
  , ClusterBeParams
80 b09cce64 Iustin Pop
  , ClusterOsParams
81 b09cce64 Iustin Pop
  , ClusterNicParams
82 b1e81520 Iustin Pop
  , Cluster(..)
83 b1e81520 Iustin Pop
  , ConfigData(..)
84 04dd53a3 Iustin Pop
  , TimeStampObject(..)
85 04dd53a3 Iustin Pop
  , UuidObject(..)
86 04dd53a3 Iustin Pop
  , SerialNoObject(..)
87 04dd53a3 Iustin Pop
  , TagsObject(..)
88 2af78b97 Iustin Pop
  , DictObject(..) -- re-exported from THH
89 9924d61e Iustin Pop
  , TagSet -- re-exported from THH
90 76a0266e Helga Velroyen
  , Network(..)
91 3a991f2d Iustin Pop
  , Ip4Address(..)
92 3a991f2d Iustin Pop
  , Ip4Network(..)
93 3a991f2d Iustin Pop
  , readIp4Address
94 3a991f2d Iustin Pop
  , nextIp4Address
95 b1e81520 Iustin Pop
  ) where
96 b1e81520 Iustin Pop
97 3a991f2d Iustin Pop
import Control.Applicative
98 adb77e3a Iustin Pop
import Data.List (foldl')
99 b1e81520 Iustin Pop
import Data.Maybe
100 adb77e3a Iustin Pop
import qualified Data.Map as Map
101 04dd53a3 Iustin Pop
import qualified Data.Set as Set
102 3a991f2d Iustin Pop
import Data.Word
103 3a991f2d Iustin Pop
import Text.JSON (showJSON, readJSON, JSON, JSValue(..), fromJSString)
104 2e12944a Iustin Pop
import qualified Text.JSON as J
105 b1e81520 Iustin Pop
106 b1e81520 Iustin Pop
import qualified Ganeti.Constants as C
107 f3baf5ef Iustin Pop
import Ganeti.JSON
108 5e9deac0 Iustin Pop
import Ganeti.Types
109 b1e81520 Iustin Pop
import Ganeti.THH
110 3a991f2d Iustin Pop
import Ganeti.Utils (sepSplit, tryRead)
111 b1e81520 Iustin Pop
112 adb77e3a Iustin Pop
-- * Generic definitions
113 adb77e3a Iustin Pop
114 adb77e3a Iustin Pop
-- | Fills one map with keys from the other map, if not already
115 adb77e3a Iustin Pop
-- existing. Mirrors objects.py:FillDict.
116 adb77e3a Iustin Pop
fillDict :: (Ord k) => Map.Map k v -> Map.Map k v -> [k] -> Map.Map k v
117 adb77e3a Iustin Pop
fillDict defaults custom skip_keys =
118 adb77e3a Iustin Pop
  let updated = Map.union custom defaults
119 adb77e3a Iustin Pop
  in foldl' (flip Map.delete) updated skip_keys
120 adb77e3a Iustin Pop
121 9d4cc8ed Iustin Pop
-- | The VTYPES, a mini-type system in Python.
122 9d4cc8ed Iustin Pop
$(declareSADT "VType"
123 9d4cc8ed Iustin Pop
  [ ("VTypeString",      'C.vtypeString)
124 9d4cc8ed Iustin Pop
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
125 9d4cc8ed Iustin Pop
  , ("VTypeBool",        'C.vtypeBool)
126 9d4cc8ed Iustin Pop
  , ("VTypeSize",        'C.vtypeSize)
127 9d4cc8ed Iustin Pop
  , ("VTypeInt",         'C.vtypeInt)
128 9d4cc8ed Iustin Pop
  ])
129 9d4cc8ed Iustin Pop
$(makeJSONInstance ''VType)
130 9d4cc8ed Iustin Pop
131 b09cce64 Iustin Pop
-- | The hypervisor parameter type. This is currently a simple map,
132 b09cce64 Iustin Pop
-- without type checking on key/value pairs.
133 b09cce64 Iustin Pop
type HvParams = Container JSValue
134 b09cce64 Iustin Pop
135 b09cce64 Iustin Pop
-- | The OS parameters type. This is, and will remain, a string
136 b09cce64 Iustin Pop
-- container, since the keys are dynamically declared by the OSes, and
137 b09cce64 Iustin Pop
-- the values are always strings.
138 b09cce64 Iustin Pop
type OsParams = Container String
139 b09cce64 Iustin Pop
140 04dd53a3 Iustin Pop
-- | Class of objects that have timestamps.
141 04dd53a3 Iustin Pop
class TimeStampObject a where
142 04dd53a3 Iustin Pop
  cTimeOf :: a -> Double
143 04dd53a3 Iustin Pop
  mTimeOf :: a -> Double
144 04dd53a3 Iustin Pop
145 04dd53a3 Iustin Pop
-- | Class of objects that have an UUID.
146 04dd53a3 Iustin Pop
class UuidObject a where
147 04dd53a3 Iustin Pop
  uuidOf :: a -> String
148 04dd53a3 Iustin Pop
149 04dd53a3 Iustin Pop
-- | Class of object that have a serial number.
150 04dd53a3 Iustin Pop
class SerialNoObject a where
151 04dd53a3 Iustin Pop
  serialOf :: a -> Int
152 04dd53a3 Iustin Pop
153 04dd53a3 Iustin Pop
-- | Class of objects that have tags.
154 04dd53a3 Iustin Pop
class TagsObject a where
155 04dd53a3 Iustin Pop
  tagsOf :: a -> Set.Set String
156 04dd53a3 Iustin Pop
157 da45c352 Iustin Pop
-- * Node role object
158 da45c352 Iustin Pop
159 da45c352 Iustin Pop
$(declareSADT "NodeRole"
160 da45c352 Iustin Pop
  [ ("NROffline",   'C.nrOffline)
161 da45c352 Iustin Pop
  , ("NRDrained",   'C.nrDrained)
162 da45c352 Iustin Pop
  , ("NRRegular",   'C.nrRegular)
163 da45c352 Iustin Pop
  , ("NRCandidate", 'C.nrMcandidate)
164 da45c352 Iustin Pop
  , ("NRMaster",    'C.nrMaster)
165 da45c352 Iustin Pop
  ])
166 da45c352 Iustin Pop
$(makeJSONInstance ''NodeRole)
167 da45c352 Iustin Pop
168 da45c352 Iustin Pop
-- | The description of the node role.
169 da45c352 Iustin Pop
roleDescription :: NodeRole -> String
170 da45c352 Iustin Pop
roleDescription NROffline   = "offline"
171 da45c352 Iustin Pop
roleDescription NRDrained   = "drained"
172 da45c352 Iustin Pop
roleDescription NRRegular   = "regular"
173 da45c352 Iustin Pop
roleDescription NRCandidate = "master candidate"
174 da45c352 Iustin Pop
roleDescription NRMaster    = "master"
175 da45c352 Iustin Pop
176 6f732ae0 Helga Velroyen
-- * Network definitions
177 6f732ae0 Helga Velroyen
178 3a991f2d Iustin Pop
-- ** Ipv4 types
179 3a991f2d Iustin Pop
180 3a991f2d Iustin Pop
-- | Custom type for a simple IPv4 address.
181 3a991f2d Iustin Pop
data Ip4Address = Ip4Address Word8 Word8 Word8 Word8
182 3a991f2d Iustin Pop
                  deriving Eq
183 3a991f2d Iustin Pop
184 3a991f2d Iustin Pop
instance Show Ip4Address where
185 3a991f2d Iustin Pop
  show (Ip4Address a b c d) = show a ++ "." ++ show b ++ "." ++
186 3a991f2d Iustin Pop
                              show c ++ "." ++ show d
187 3a991f2d Iustin Pop
188 3a991f2d Iustin Pop
-- | Parses an IPv4 address from a string.
189 3a991f2d Iustin Pop
readIp4Address :: (Applicative m, Monad m) => String -> m Ip4Address
190 3a991f2d Iustin Pop
readIp4Address s =
191 3a991f2d Iustin Pop
  case sepSplit '.' s of
192 3a991f2d Iustin Pop
    [a, b, c, d] -> Ip4Address <$>
193 3a991f2d Iustin Pop
                      tryRead "first octect" a <*>
194 3a991f2d Iustin Pop
                      tryRead "second octet" b <*>
195 3a991f2d Iustin Pop
                      tryRead "third octet"  c <*>
196 3a991f2d Iustin Pop
                      tryRead "fourth octet" d
197 3a991f2d Iustin Pop
    _ -> fail $ "Can't parse IPv4 address from string " ++ s
198 3a991f2d Iustin Pop
199 3a991f2d Iustin Pop
-- | JSON instance for 'Ip4Address'.
200 3a991f2d Iustin Pop
instance JSON Ip4Address where
201 3a991f2d Iustin Pop
  showJSON = showJSON . show
202 3a991f2d Iustin Pop
  readJSON (JSString s) = readIp4Address (fromJSString s)
203 3a991f2d Iustin Pop
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 address"
204 3a991f2d Iustin Pop
205 3a991f2d Iustin Pop
-- | \"Next\" address implementation for IPv4 addresses.
206 3a991f2d Iustin Pop
--
207 3a991f2d Iustin Pop
-- Note that this loops! Note also that this is a very dumb
208 3a991f2d Iustin Pop
-- implementation.
209 3a991f2d Iustin Pop
nextIp4Address :: Ip4Address -> Ip4Address
210 3a991f2d Iustin Pop
nextIp4Address (Ip4Address a b c d) =
211 3a991f2d Iustin Pop
  let inc xs y = if all (==0) xs then y + 1 else y
212 3a991f2d Iustin Pop
      d' = d + 1
213 3a991f2d Iustin Pop
      c' = inc [d'] c
214 3a991f2d Iustin Pop
      b' = inc [c', d'] b
215 3a991f2d Iustin Pop
      a' = inc [b', c', d'] a
216 3a991f2d Iustin Pop
  in Ip4Address a' b' c' d'
217 3a991f2d Iustin Pop
218 3a991f2d Iustin Pop
-- | Custom type for an IPv4 network.
219 3a991f2d Iustin Pop
data Ip4Network = Ip4Network Ip4Address Word8
220 3a991f2d Iustin Pop
                  deriving Eq
221 3a991f2d Iustin Pop
222 3a991f2d Iustin Pop
instance Show Ip4Network where
223 3a991f2d Iustin Pop
  show (Ip4Network ip netmask) = show ip ++ "/" ++ show netmask
224 3a991f2d Iustin Pop
225 3a991f2d Iustin Pop
-- | JSON instance for 'Ip4Network'.
226 3a991f2d Iustin Pop
instance JSON Ip4Network where
227 3a991f2d Iustin Pop
  showJSON = showJSON . show
228 3a991f2d Iustin Pop
  readJSON (JSString s) =
229 3a991f2d Iustin Pop
    case sepSplit '/' (fromJSString s) of
230 3a991f2d Iustin Pop
      [ip, nm] -> do
231 3a991f2d Iustin Pop
        ip' <- readIp4Address ip
232 3a991f2d Iustin Pop
        nm' <- tryRead "parsing netmask" nm
233 3a991f2d Iustin Pop
        if nm' >= 0 && nm' <= 32
234 3a991f2d Iustin Pop
          then return $ Ip4Network ip' nm'
235 3a991f2d Iustin Pop
          else fail $ "Invalid netmask " ++ show nm' ++ " from string " ++
236 3a991f2d Iustin Pop
                      fromJSString s
237 3a991f2d Iustin Pop
      _ -> fail $ "Can't parse IPv4 network from string " ++ fromJSString s
238 3a991f2d Iustin Pop
  readJSON v = fail $ "Invalid JSON value " ++ show v ++ " for an IPv4 network"
239 3a991f2d Iustin Pop
240 3a991f2d Iustin Pop
-- ** Ganeti \"network\" config object.
241 3a991f2d Iustin Pop
242 6f732ae0 Helga Velroyen
-- FIXME: Not all types might be correct here, since they
243 6f732ae0 Helga Velroyen
-- haven't been exhaustively deduced from the python code yet.
244 6f732ae0 Helga Velroyen
$(buildObject "Network" "network" $
245 6f732ae0 Helga Velroyen
  [ simpleField "name"             [t| NonEmptyString |]
246 6f732ae0 Helga Velroyen
  , optionalField $
247 6f732ae0 Helga Velroyen
    simpleField "mac_prefix"       [t| String |]
248 3a991f2d Iustin Pop
  , simpleField "network"          [t| Ip4Network |]
249 6f732ae0 Helga Velroyen
  , optionalField $
250 6f732ae0 Helga Velroyen
    simpleField "network6"         [t| String |]
251 6f732ae0 Helga Velroyen
  , optionalField $
252 3a991f2d Iustin Pop
    simpleField "gateway"          [t| Ip4Address |]
253 6f732ae0 Helga Velroyen
  , optionalField $
254 6f732ae0 Helga Velroyen
    simpleField "gateway6"         [t| String |]
255 6f732ae0 Helga Velroyen
  , optionalField $
256 6f732ae0 Helga Velroyen
    simpleField "reservations"     [t| String |]
257 6f732ae0 Helga Velroyen
  , optionalField $
258 6f732ae0 Helga Velroyen
    simpleField "ext_reservations" [t| String |]
259 6f732ae0 Helga Velroyen
  ]
260 b43064d0 Helga Velroyen
  ++ uuidFields
261 6f732ae0 Helga Velroyen
  ++ serialFields
262 6f732ae0 Helga Velroyen
  ++ tagsFields)
263 6f732ae0 Helga Velroyen
264 6f732ae0 Helga Velroyen
instance SerialNoObject Network where
265 6f732ae0 Helga Velroyen
  serialOf = networkSerial
266 6f732ae0 Helga Velroyen
267 6f732ae0 Helga Velroyen
instance TagsObject Network where
268 6f732ae0 Helga Velroyen
  tagsOf = networkTags
269 6f732ae0 Helga Velroyen
270 b43064d0 Helga Velroyen
instance UuidObject Network where
271 b43064d0 Helga Velroyen
  uuidOf = networkUuid
272 b43064d0 Helga Velroyen
273 b1e81520 Iustin Pop
-- * NIC definitions
274 b1e81520 Iustin Pop
275 b09cce64 Iustin Pop
$(buildParam "Nic" "nicp"
276 b1e81520 Iustin Pop
  [ simpleField "mode" [t| NICMode |]
277 b1e81520 Iustin Pop
  , simpleField "link" [t| String  |]
278 b1e81520 Iustin Pop
  ])
279 b1e81520 Iustin Pop
280 b09cce64 Iustin Pop
$(buildObject "PartialNic" "nic"
281 b1e81520 Iustin Pop
  [ simpleField "mac" [t| String |]
282 b1e81520 Iustin Pop
  , optionalField $ simpleField "ip" [t| String |]
283 b09cce64 Iustin Pop
  , simpleField "nicparams" [t| PartialNicParams |]
284 0c6d6a52 Helga Velroyen
  , optionalField $ simpleField "network" [t| String |]
285 b1e81520 Iustin Pop
  ])
286 b1e81520 Iustin Pop
287 b1e81520 Iustin Pop
-- * Disk definitions
288 b1e81520 Iustin Pop
289 b1e81520 Iustin Pop
$(declareSADT "DiskMode"
290 b1e81520 Iustin Pop
  [ ("DiskRdOnly", 'C.diskRdonly)
291 b1e81520 Iustin Pop
  , ("DiskRdWr",   'C.diskRdwr)
292 b1e81520 Iustin Pop
  ])
293 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskMode)
294 b1e81520 Iustin Pop
295 b1e81520 Iustin Pop
$(declareSADT "DiskType"
296 b1e81520 Iustin Pop
  [ ("LD_LV",       'C.ldLv)
297 b1e81520 Iustin Pop
  , ("LD_DRBD8",    'C.ldDrbd8)
298 b1e81520 Iustin Pop
  , ("LD_FILE",     'C.ldFile)
299 b1e81520 Iustin Pop
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
300 2e12944a Iustin Pop
  , ("LD_RADOS",    'C.ldRbd)
301 277a2ec9 Constantinos Venetsanopoulos
  , ("LD_EXT",      'C.ldExt)
302 b1e81520 Iustin Pop
  ])
303 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskType)
304 b1e81520 Iustin Pop
305 2e12944a Iustin Pop
-- | The persistent block driver type. Currently only one type is allowed.
306 2e12944a Iustin Pop
$(declareSADT "BlockDriver"
307 2e12944a Iustin Pop
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
308 2e12944a Iustin Pop
  ])
309 2e12944a Iustin Pop
$(makeJSONInstance ''BlockDriver)
310 2e12944a Iustin Pop
311 2e12944a Iustin Pop
-- | Constant for the dev_type key entry in the disk config.
312 2e12944a Iustin Pop
devType :: String
313 2e12944a Iustin Pop
devType = "dev_type"
314 2e12944a Iustin Pop
315 2e12944a Iustin Pop
-- | The disk configuration type. This includes the disk type itself,
316 2e12944a Iustin Pop
-- for a more complete consistency. Note that since in the Python
317 2e12944a Iustin Pop
-- code-base there's no authoritative place where we document the
318 2e12944a Iustin Pop
-- logical id, this is probably a good reference point.
319 2e12944a Iustin Pop
data DiskLogicalId
320 2e12944a Iustin Pop
  = LIDPlain String String  -- ^ Volume group, logical volume
321 2e12944a Iustin Pop
  | LIDDrbd8 String String Int Int Int String
322 2e12944a Iustin Pop
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
323 2e12944a Iustin Pop
  | LIDFile FileDriver String -- ^ Driver, path
324 2e12944a Iustin Pop
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
325 2e12944a Iustin Pop
  | LIDRados String String -- ^ Unused, path
326 277a2ec9 Constantinos Venetsanopoulos
  | LIDExt String String -- ^ ExtProvider, unique name
327 139c0683 Iustin Pop
    deriving (Show, Eq)
328 2e12944a Iustin Pop
329 2e12944a Iustin Pop
-- | Mapping from a logical id to a disk type.
330 2e12944a Iustin Pop
lidDiskType :: DiskLogicalId -> DiskType
331 2e12944a Iustin Pop
lidDiskType (LIDPlain {}) = LD_LV
332 2e12944a Iustin Pop
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
333 2e12944a Iustin Pop
lidDiskType (LIDFile  {}) = LD_FILE
334 2e12944a Iustin Pop
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
335 2e12944a Iustin Pop
lidDiskType (LIDRados {}) = LD_RADOS
336 277a2ec9 Constantinos Venetsanopoulos
lidDiskType (LIDExt {}) = LD_EXT
337 2e12944a Iustin Pop
338 2e12944a Iustin Pop
-- | Builds the extra disk_type field for a given logical id.
339 2e12944a Iustin Pop
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
340 2e12944a Iustin Pop
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
341 2e12944a Iustin Pop
342 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId (logical id only).
343 2e12944a Iustin Pop
encodeDLId :: DiskLogicalId -> JSValue
344 2e12944a Iustin Pop
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
345 2e12944a Iustin Pop
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
346 2e12944a Iustin Pop
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
347 2e12944a Iustin Pop
          , showJSON minorA, showJSON minorB, showJSON key ]
348 2e12944a Iustin Pop
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
349 2e12944a Iustin Pop
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
350 2e12944a Iustin Pop
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
351 9f6f74b4 Iustin Pop
encodeDLId (LIDExt extprovider name) =
352 9f6f74b4 Iustin Pop
  JSArray [showJSON extprovider, showJSON name]
353 2e12944a Iustin Pop
354 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId, composing both the logical id
355 2e12944a Iustin Pop
-- and the extra disk_type field.
356 2e12944a Iustin Pop
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
357 2e12944a Iustin Pop
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
358 2e12944a Iustin Pop
359 2e12944a Iustin Pop
-- | Custom decoder for DiskLogicalId. This is manual for now, since
360 2e12944a Iustin Pop
-- we don't have yet automation for separate-key style fields.
361 2e12944a Iustin Pop
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
362 2e12944a Iustin Pop
decodeDLId obj lid = do
363 2e12944a Iustin Pop
  dtype <- fromObj obj devType
364 2e12944a Iustin Pop
  case dtype of
365 2e12944a Iustin Pop
    LD_DRBD8 ->
366 2e12944a Iustin Pop
      case lid of
367 2e12944a Iustin Pop
        JSArray [nA, nB, p, mA, mB, k] -> do
368 2e12944a Iustin Pop
          nA' <- readJSON nA
369 2e12944a Iustin Pop
          nB' <- readJSON nB
370 2e12944a Iustin Pop
          p'  <- readJSON p
371 2e12944a Iustin Pop
          mA' <- readJSON mA
372 2e12944a Iustin Pop
          mB' <- readJSON mB
373 2e12944a Iustin Pop
          k'  <- readJSON k
374 2e12944a Iustin Pop
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
375 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for DRBD8 type"
376 2e12944a Iustin Pop
    LD_LV ->
377 2e12944a Iustin Pop
      case lid of
378 2e12944a Iustin Pop
        JSArray [vg, lv] -> do
379 2e12944a Iustin Pop
          vg' <- readJSON vg
380 2e12944a Iustin Pop
          lv' <- readJSON lv
381 2e12944a Iustin Pop
          return $ LIDPlain vg' lv'
382 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for plain type"
383 2e12944a Iustin Pop
    LD_FILE ->
384 2e12944a Iustin Pop
      case lid of
385 2e12944a Iustin Pop
        JSArray [driver, path] -> do
386 2e12944a Iustin Pop
          driver' <- readJSON driver
387 2e12944a Iustin Pop
          path'   <- readJSON path
388 2e12944a Iustin Pop
          return $ LIDFile driver' path'
389 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for file type"
390 2e12944a Iustin Pop
    LD_BLOCKDEV ->
391 2e12944a Iustin Pop
      case lid of
392 2e12944a Iustin Pop
        JSArray [driver, path] -> do
393 2e12944a Iustin Pop
          driver' <- readJSON driver
394 2e12944a Iustin Pop
          path'   <- readJSON path
395 2e12944a Iustin Pop
          return $ LIDBlockDev driver' path'
396 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for blockdev type"
397 2e12944a Iustin Pop
    LD_RADOS ->
398 2e12944a Iustin Pop
      case lid of
399 2e12944a Iustin Pop
        JSArray [driver, path] -> do
400 2e12944a Iustin Pop
          driver' <- readJSON driver
401 2e12944a Iustin Pop
          path'   <- readJSON path
402 2e12944a Iustin Pop
          return $ LIDRados driver' path'
403 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for rdb type"
404 277a2ec9 Constantinos Venetsanopoulos
    LD_EXT ->
405 277a2ec9 Constantinos Venetsanopoulos
      case lid of
406 277a2ec9 Constantinos Venetsanopoulos
        JSArray [extprovider, name] -> do
407 277a2ec9 Constantinos Venetsanopoulos
          extprovider' <- readJSON extprovider
408 277a2ec9 Constantinos Venetsanopoulos
          name'   <- readJSON name
409 277a2ec9 Constantinos Venetsanopoulos
          return $ LIDExt extprovider' name'
410 277a2ec9 Constantinos Venetsanopoulos
        _ -> fail "Can't read logical_id for extstorage type"
411 2e12944a Iustin Pop
412 b1e81520 Iustin Pop
-- | Disk data structure.
413 b1e81520 Iustin Pop
--
414 b1e81520 Iustin Pop
-- This is declared manually as it's a recursive structure, and our TH
415 b1e81520 Iustin Pop
-- code currently can't build it.
416 b1e81520 Iustin Pop
data Disk = Disk
417 2e12944a Iustin Pop
  { diskLogicalId  :: DiskLogicalId
418 b1e81520 Iustin Pop
--  , diskPhysicalId :: String
419 b1e81520 Iustin Pop
  , diskChildren   :: [Disk]
420 b1e81520 Iustin Pop
  , diskIvName     :: String
421 b1e81520 Iustin Pop
  , diskSize       :: Int
422 b1e81520 Iustin Pop
  , diskMode       :: DiskMode
423 139c0683 Iustin Pop
  } deriving (Show, Eq)
424 b1e81520 Iustin Pop
425 b1e81520 Iustin Pop
$(buildObjectSerialisation "Disk"
426 fa10983e Iustin Pop
  [ customField 'decodeDLId 'encodeFullDLId ["dev_type"] $
427 2e12944a Iustin Pop
      simpleField "logical_id"    [t| DiskLogicalId   |]
428 b1e81520 Iustin Pop
--  , simpleField "physical_id" [t| String   |]
429 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
430 b1e81520 Iustin Pop
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
431 b1e81520 Iustin Pop
  , simpleField "size" [t| Int |]
432 b1e81520 Iustin Pop
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
433 b1e81520 Iustin Pop
  ])
434 b1e81520 Iustin Pop
435 b1e81520 Iustin Pop
-- * Instance definitions
436 b1e81520 Iustin Pop
437 b1e81520 Iustin Pop
$(declareSADT "AdminState"
438 b1e81520 Iustin Pop
  [ ("AdminOffline", 'C.adminstOffline)
439 b1e81520 Iustin Pop
  , ("AdminDown",    'C.adminstDown)
440 b1e81520 Iustin Pop
  , ("AdminUp",      'C.adminstUp)
441 b1e81520 Iustin Pop
  ])
442 b1e81520 Iustin Pop
$(makeJSONInstance ''AdminState)
443 b1e81520 Iustin Pop
444 5b11f8db Iustin Pop
$(buildParam "Be" "bep"
445 b1e81520 Iustin Pop
  [ simpleField "minmem"       [t| Int  |]
446 b1e81520 Iustin Pop
  , simpleField "maxmem"       [t| Int  |]
447 b1e81520 Iustin Pop
  , simpleField "vcpus"        [t| Int  |]
448 b1e81520 Iustin Pop
  , simpleField "auto_balance" [t| Bool |]
449 b1e81520 Iustin Pop
  ])
450 b1e81520 Iustin Pop
451 b1e81520 Iustin Pop
$(buildObject "Instance" "inst" $
452 b1e81520 Iustin Pop
  [ simpleField "name"           [t| String             |]
453 b1e81520 Iustin Pop
  , simpleField "primary_node"   [t| String             |]
454 b1e81520 Iustin Pop
  , simpleField "os"             [t| String             |]
455 b09cce64 Iustin Pop
  , simpleField "hypervisor"     [t| Hypervisor         |]
456 b09cce64 Iustin Pop
  , simpleField "hvparams"       [t| HvParams           |]
457 b09cce64 Iustin Pop
  , simpleField "beparams"       [t| PartialBeParams    |]
458 b09cce64 Iustin Pop
  , simpleField "osparams"       [t| OsParams           |]
459 b1e81520 Iustin Pop
  , simpleField "admin_state"    [t| AdminState         |]
460 b09cce64 Iustin Pop
  , simpleField "nics"           [t| [PartialNic]       |]
461 b1e81520 Iustin Pop
  , simpleField "disks"          [t| [Disk]             |]
462 b1e81520 Iustin Pop
  , simpleField "disk_template"  [t| DiskTemplate       |]
463 b09cce64 Iustin Pop
  , optionalField $ simpleField "network_port" [t| Int  |]
464 b1e81520 Iustin Pop
  ]
465 b1e81520 Iustin Pop
  ++ timeStampFields
466 b1e81520 Iustin Pop
  ++ uuidFields
467 f2374060 Iustin Pop
  ++ serialFields
468 f2374060 Iustin Pop
  ++ tagsFields)
469 b1e81520 Iustin Pop
470 04dd53a3 Iustin Pop
instance TimeStampObject Instance where
471 04dd53a3 Iustin Pop
  cTimeOf = instCtime
472 04dd53a3 Iustin Pop
  mTimeOf = instMtime
473 04dd53a3 Iustin Pop
474 04dd53a3 Iustin Pop
instance UuidObject Instance where
475 04dd53a3 Iustin Pop
  uuidOf = instUuid
476 04dd53a3 Iustin Pop
477 04dd53a3 Iustin Pop
instance SerialNoObject Instance where
478 04dd53a3 Iustin Pop
  serialOf = instSerial
479 04dd53a3 Iustin Pop
480 04dd53a3 Iustin Pop
instance TagsObject Instance where
481 04dd53a3 Iustin Pop
  tagsOf = instTags
482 04dd53a3 Iustin Pop
483 7514fe92 Iustin Pop
-- * IPolicy definitions
484 7514fe92 Iustin Pop
485 5b11f8db Iustin Pop
$(buildParam "ISpec" "ispec"
486 7514fe92 Iustin Pop
  [ simpleField C.ispecMemSize     [t| Int |]
487 7514fe92 Iustin Pop
  , simpleField C.ispecDiskSize    [t| Int |]
488 7514fe92 Iustin Pop
  , simpleField C.ispecDiskCount   [t| Int |]
489 7514fe92 Iustin Pop
  , simpleField C.ispecCpuCount    [t| Int |]
490 db154319 Iustin Pop
  , simpleField C.ispecNicCount    [t| Int |]
491 7514fe92 Iustin Pop
  , simpleField C.ispecSpindleUse  [t| Int |]
492 7514fe92 Iustin Pop
  ])
493 7514fe92 Iustin Pop
494 7514fe92 Iustin Pop
-- | Custom partial ipolicy. This is not built via buildParam since it
495 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
496 5b11f8db Iustin Pop
$(buildObject "PartialIPolicy" "ipolicy"
497 7514fe92 Iustin Pop
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
498 7514fe92 Iustin Pop
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
499 7514fe92 Iustin Pop
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
500 7514fe92 Iustin Pop
  , optionalField . renameField "SpindleRatioP"
501 7514fe92 Iustin Pop
                    $ simpleField "spindle-ratio"  [t| Double |]
502 7514fe92 Iustin Pop
  , optionalField . renameField "VcpuRatioP"
503 7514fe92 Iustin Pop
                    $ simpleField "vcpu-ratio"     [t| Double |]
504 7514fe92 Iustin Pop
  , optionalField . renameField "DiskTemplatesP"
505 7514fe92 Iustin Pop
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
506 7514fe92 Iustin Pop
  ])
507 7514fe92 Iustin Pop
508 7514fe92 Iustin Pop
-- | Custom filled ipolicy. This is not built via buildParam since it
509 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
510 5b11f8db Iustin Pop
$(buildObject "FilledIPolicy" "ipolicy"
511 7514fe92 Iustin Pop
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
512 7514fe92 Iustin Pop
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
513 7514fe92 Iustin Pop
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
514 7514fe92 Iustin Pop
  , simpleField "spindle-ratio"  [t| Double |]
515 7514fe92 Iustin Pop
  , simpleField "vcpu-ratio"     [t| Double |]
516 7514fe92 Iustin Pop
  , simpleField "disk-templates" [t| [DiskTemplate] |]
517 7514fe92 Iustin Pop
  ])
518 7514fe92 Iustin Pop
519 7514fe92 Iustin Pop
-- | Custom filler for the ipolicy types.
520 7514fe92 Iustin Pop
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
521 7514fe92 Iustin Pop
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
522 7514fe92 Iustin Pop
                           , ipolicyMaxSpec       = fmax
523 7514fe92 Iustin Pop
                           , ipolicyStdSpec       = fstd
524 7514fe92 Iustin Pop
                           , ipolicySpindleRatio  = fspindleRatio
525 7514fe92 Iustin Pop
                           , ipolicyVcpuRatio     = fvcpuRatio
526 7514fe92 Iustin Pop
                           , ipolicyDiskTemplates = fdiskTemplates})
527 7514fe92 Iustin Pop
            (PartialIPolicy { ipolicyMinSpecP       = pmin
528 7514fe92 Iustin Pop
                            , ipolicyMaxSpecP       = pmax
529 7514fe92 Iustin Pop
                            , ipolicyStdSpecP       = pstd
530 7514fe92 Iustin Pop
                            , ipolicySpindleRatioP  = pspindleRatio
531 7514fe92 Iustin Pop
                            , ipolicyVcpuRatioP     = pvcpuRatio
532 7514fe92 Iustin Pop
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
533 7514fe92 Iustin Pop
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
534 7514fe92 Iustin Pop
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
535 7514fe92 Iustin Pop
                , ipolicyStdSpec       = fillISpecParams fstd pstd
536 7514fe92 Iustin Pop
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
537 7514fe92 Iustin Pop
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
538 7514fe92 Iustin Pop
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
539 7514fe92 Iustin Pop
                                         pdiskTemplates
540 7514fe92 Iustin Pop
                }
541 b1e81520 Iustin Pop
-- * Node definitions
542 b1e81520 Iustin Pop
543 5b11f8db Iustin Pop
$(buildParam "ND" "ndp"
544 7514fe92 Iustin Pop
  [ simpleField "oob_program"   [t| String |]
545 7514fe92 Iustin Pop
  , simpleField "spindle_count" [t| Int    |]
546 0ea11dcb Bernardo Dal Seno
  , simpleField "exclusive_storage" [t| Bool |]
547 b1e81520 Iustin Pop
  ])
548 b1e81520 Iustin Pop
549 b1e81520 Iustin Pop
$(buildObject "Node" "node" $
550 b1e81520 Iustin Pop
  [ simpleField "name"             [t| String |]
551 b1e81520 Iustin Pop
  , simpleField "primary_ip"       [t| String |]
552 b1e81520 Iustin Pop
  , simpleField "secondary_ip"     [t| String |]
553 b1e81520 Iustin Pop
  , simpleField "master_candidate" [t| Bool   |]
554 b1e81520 Iustin Pop
  , simpleField "offline"          [t| Bool   |]
555 b1e81520 Iustin Pop
  , simpleField "drained"          [t| Bool   |]
556 b1e81520 Iustin Pop
  , simpleField "group"            [t| String |]
557 b1e81520 Iustin Pop
  , simpleField "master_capable"   [t| Bool   |]
558 b1e81520 Iustin Pop
  , simpleField "vm_capable"       [t| Bool   |]
559 a957e150 Iustin Pop
  , simpleField "ndparams"         [t| PartialNDParams |]
560 b1e81520 Iustin Pop
  , simpleField "powered"          [t| Bool   |]
561 b1e81520 Iustin Pop
  ]
562 b1e81520 Iustin Pop
  ++ timeStampFields
563 b1e81520 Iustin Pop
  ++ uuidFields
564 f2374060 Iustin Pop
  ++ serialFields
565 f2374060 Iustin Pop
  ++ tagsFields)
566 b1e81520 Iustin Pop
567 04dd53a3 Iustin Pop
instance TimeStampObject Node where
568 04dd53a3 Iustin Pop
  cTimeOf = nodeCtime
569 04dd53a3 Iustin Pop
  mTimeOf = nodeMtime
570 04dd53a3 Iustin Pop
571 04dd53a3 Iustin Pop
instance UuidObject Node where
572 04dd53a3 Iustin Pop
  uuidOf = nodeUuid
573 04dd53a3 Iustin Pop
574 04dd53a3 Iustin Pop
instance SerialNoObject Node where
575 04dd53a3 Iustin Pop
  serialOf = nodeSerial
576 04dd53a3 Iustin Pop
577 04dd53a3 Iustin Pop
instance TagsObject Node where
578 04dd53a3 Iustin Pop
  tagsOf = nodeTags
579 04dd53a3 Iustin Pop
580 b1e81520 Iustin Pop
-- * NodeGroup definitions
581 b1e81520 Iustin Pop
582 b09cce64 Iustin Pop
-- | The disk parameters type.
583 b09cce64 Iustin Pop
type DiskParams = Container (Container JSValue)
584 b09cce64 Iustin Pop
585 da1dcce1 Helga Velroyen
-- | A mapping from network UUIDs to nic params of the networks.
586 2f3a3365 Helga Velroyen
type Networks = Container PartialNicParams
587 da1dcce1 Helga Velroyen
588 b1e81520 Iustin Pop
$(buildObject "NodeGroup" "group" $
589 b1e81520 Iustin Pop
  [ simpleField "name"         [t| String |]
590 0f0d7aba Helga Velroyen
  , defaultField [| [] |] $ simpleField "members" [t| [String] |]
591 a957e150 Iustin Pop
  , simpleField "ndparams"     [t| PartialNDParams |]
592 7514fe92 Iustin Pop
  , simpleField "alloc_policy" [t| AllocPolicy     |]
593 7514fe92 Iustin Pop
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
594 b09cce64 Iustin Pop
  , simpleField "diskparams"   [t| DiskParams      |]
595 da1dcce1 Helga Velroyen
  , simpleField "networks"     [t| Networks        |]
596 b1e81520 Iustin Pop
  ]
597 b1e81520 Iustin Pop
  ++ timeStampFields
598 b1e81520 Iustin Pop
  ++ uuidFields
599 f2374060 Iustin Pop
  ++ serialFields
600 f2374060 Iustin Pop
  ++ tagsFields)
601 b1e81520 Iustin Pop
602 04dd53a3 Iustin Pop
instance TimeStampObject NodeGroup where
603 04dd53a3 Iustin Pop
  cTimeOf = groupCtime
604 04dd53a3 Iustin Pop
  mTimeOf = groupMtime
605 04dd53a3 Iustin Pop
606 04dd53a3 Iustin Pop
instance UuidObject NodeGroup where
607 04dd53a3 Iustin Pop
  uuidOf = groupUuid
608 04dd53a3 Iustin Pop
609 04dd53a3 Iustin Pop
instance SerialNoObject NodeGroup where
610 04dd53a3 Iustin Pop
  serialOf = groupSerial
611 04dd53a3 Iustin Pop
612 04dd53a3 Iustin Pop
instance TagsObject NodeGroup where
613 04dd53a3 Iustin Pop
  tagsOf = groupTags
614 04dd53a3 Iustin Pop
615 a957e150 Iustin Pop
-- | IP family type
616 a957e150 Iustin Pop
$(declareIADT "IpFamily"
617 a957e150 Iustin Pop
  [ ("IpFamilyV4", 'C.ip4Family)
618 a957e150 Iustin Pop
  , ("IpFamilyV6", 'C.ip6Family)
619 a957e150 Iustin Pop
  ])
620 a957e150 Iustin Pop
$(makeJSONInstance ''IpFamily)
621 a957e150 Iustin Pop
622 a957e150 Iustin Pop
-- | Conversion from IP family to IP version. This is needed because
623 a957e150 Iustin Pop
-- Python uses both, depending on context.
624 a957e150 Iustin Pop
ipFamilyToVersion :: IpFamily -> Int
625 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV4 = C.ip4Version
626 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV6 = C.ip6Version
627 a957e150 Iustin Pop
628 b09cce64 Iustin Pop
-- | Cluster HvParams (hvtype to hvparams mapping).
629 b09cce64 Iustin Pop
type ClusterHvParams = Container HvParams
630 b09cce64 Iustin Pop
631 b09cce64 Iustin Pop
-- | Cluster Os-HvParams (os to hvparams mapping).
632 b09cce64 Iustin Pop
type OsHvParams = Container ClusterHvParams
633 b09cce64 Iustin Pop
634 b09cce64 Iustin Pop
-- | Cluser BeParams.
635 b09cce64 Iustin Pop
type ClusterBeParams = Container FilledBeParams
636 b09cce64 Iustin Pop
637 b09cce64 Iustin Pop
-- | Cluster OsParams.
638 b09cce64 Iustin Pop
type ClusterOsParams = Container OsParams
639 b09cce64 Iustin Pop
640 b09cce64 Iustin Pop
-- | Cluster NicParams.
641 b09cce64 Iustin Pop
type ClusterNicParams = Container FilledNicParams
642 b09cce64 Iustin Pop
643 b09cce64 Iustin Pop
-- | Cluster UID Pool, list (low, high) UID ranges.
644 b09cce64 Iustin Pop
type UidPool = [(Int, Int)]
645 b09cce64 Iustin Pop
646 b1e81520 Iustin Pop
-- * Cluster definitions
647 b1e81520 Iustin Pop
$(buildObject "Cluster" "cluster" $
648 b09cce64 Iustin Pop
  [ simpleField "rsahostkeypub"           [t| String           |]
649 b09cce64 Iustin Pop
  , simpleField "highest_used_port"       [t| Int              |]
650 b09cce64 Iustin Pop
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
651 b09cce64 Iustin Pop
  , simpleField "mac_prefix"              [t| String           |]
652 64b0309a Dimitris Aragiorgis
  , optionalField $
653 64b0309a Dimitris Aragiorgis
    simpleField "volume_group_name"       [t| String           |]
654 b09cce64 Iustin Pop
  , simpleField "reserved_lvs"            [t| [String]         |]
655 b09cce64 Iustin Pop
  , optionalField $
656 b09cce64 Iustin Pop
    simpleField "drbd_usermode_helper"    [t| String           |]
657 b09cce64 Iustin Pop
  , simpleField "master_node"             [t| String           |]
658 b09cce64 Iustin Pop
  , simpleField "master_ip"               [t| String           |]
659 b09cce64 Iustin Pop
  , simpleField "master_netdev"           [t| String           |]
660 b09cce64 Iustin Pop
  , simpleField "master_netmask"          [t| Int              |]
661 b09cce64 Iustin Pop
  , simpleField "use_external_mip_script" [t| Bool             |]
662 b09cce64 Iustin Pop
  , simpleField "cluster_name"            [t| String           |]
663 b09cce64 Iustin Pop
  , simpleField "file_storage_dir"        [t| String           |]
664 b09cce64 Iustin Pop
  , simpleField "shared_file_storage_dir" [t| String           |]
665 f9b0084a Agata Murawska
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
666 b09cce64 Iustin Pop
  , simpleField "hvparams"                [t| ClusterHvParams  |]
667 b09cce64 Iustin Pop
  , simpleField "os_hvp"                  [t| OsHvParams       |]
668 b09cce64 Iustin Pop
  , simpleField "beparams"                [t| ClusterBeParams  |]
669 b09cce64 Iustin Pop
  , simpleField "osparams"                [t| ClusterOsParams  |]
670 b09cce64 Iustin Pop
  , simpleField "nicparams"               [t| ClusterNicParams |]
671 b09cce64 Iustin Pop
  , simpleField "ndparams"                [t| FilledNDParams   |]
672 b09cce64 Iustin Pop
  , simpleField "diskparams"              [t| DiskParams       |]
673 b09cce64 Iustin Pop
  , simpleField "candidate_pool_size"     [t| Int              |]
674 b09cce64 Iustin Pop
  , simpleField "modify_etc_hosts"        [t| Bool             |]
675 b09cce64 Iustin Pop
  , simpleField "modify_ssh_setup"        [t| Bool             |]
676 b09cce64 Iustin Pop
  , simpleField "maintain_node_health"    [t| Bool             |]
677 b09cce64 Iustin Pop
  , simpleField "uid_pool"                [t| UidPool          |]
678 b09cce64 Iustin Pop
  , simpleField "default_iallocator"      [t| String           |]
679 b09cce64 Iustin Pop
  , simpleField "hidden_os"               [t| [String]         |]
680 b09cce64 Iustin Pop
  , simpleField "blacklisted_os"          [t| [String]         |]
681 b09cce64 Iustin Pop
  , simpleField "primary_ip_family"       [t| IpFamily         |]
682 b09cce64 Iustin Pop
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
683 b09cce64 Iustin Pop
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
684 b1e81520 Iustin Pop
 ]
685 02cccecd Iustin Pop
 ++ timeStampFields
686 02cccecd Iustin Pop
 ++ uuidFields
687 04dd53a3 Iustin Pop
 ++ serialFields
688 02cccecd Iustin Pop
 ++ tagsFields)
689 b1e81520 Iustin Pop
690 04dd53a3 Iustin Pop
instance TimeStampObject Cluster where
691 04dd53a3 Iustin Pop
  cTimeOf = clusterCtime
692 04dd53a3 Iustin Pop
  mTimeOf = clusterMtime
693 04dd53a3 Iustin Pop
694 04dd53a3 Iustin Pop
instance UuidObject Cluster where
695 04dd53a3 Iustin Pop
  uuidOf = clusterUuid
696 04dd53a3 Iustin Pop
697 04dd53a3 Iustin Pop
instance SerialNoObject Cluster where
698 04dd53a3 Iustin Pop
  serialOf = clusterSerial
699 04dd53a3 Iustin Pop
700 04dd53a3 Iustin Pop
instance TagsObject Cluster where
701 04dd53a3 Iustin Pop
  tagsOf = clusterTags
702 04dd53a3 Iustin Pop
703 b1e81520 Iustin Pop
-- * ConfigData definitions
704 b1e81520 Iustin Pop
705 b1e81520 Iustin Pop
$(buildObject "ConfigData" "config" $
706 b1e81520 Iustin Pop
--  timeStampFields ++
707 d5a93a80 Iustin Pop
  [ simpleField "version"    [t| Int                 |]
708 d5a93a80 Iustin Pop
  , simpleField "cluster"    [t| Cluster             |]
709 d5a93a80 Iustin Pop
  , simpleField "nodes"      [t| Container Node      |]
710 d5a93a80 Iustin Pop
  , simpleField "nodegroups" [t| Container NodeGroup |]
711 d5a93a80 Iustin Pop
  , simpleField "instances"  [t| Container Instance  |]
712 b43064d0 Helga Velroyen
  , simpleField "networks"   [t| Container Network   |]
713 b1e81520 Iustin Pop
  ]
714 b1e81520 Iustin Pop
  ++ serialFields)
715 04dd53a3 Iustin Pop
716 04dd53a3 Iustin Pop
instance SerialNoObject ConfigData where
717 04dd53a3 Iustin Pop
  serialOf = configSerial