Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 36cb6837

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