Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 96e3dfa7

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