Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ ae8e7986

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