Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ a6a6a1b5

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