Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 74b25887

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