Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ bf028b21

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