Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 1ca6e10e

History | View | Annotate | Download (24.7 kB)

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