Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 22381768

History | View | Annotate | Download (19.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 b1e81520 Iustin Pop
Copyright (C) 2011, 2012 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
  , NICMode(..)
37 b09cce64 Iustin Pop
  , PartialNicParams(..)
38 b09cce64 Iustin Pop
  , FilledNicParams(..)
39 b09cce64 Iustin Pop
  , fillNicParams
40 2af78b97 Iustin Pop
  , allNicParamFields
41 b09cce64 Iustin Pop
  , PartialNic(..)
42 8d2b6a12 Iustin Pop
  , FileDriver(..)
43 8d2b6a12 Iustin Pop
  , BlockDriver(..)
44 b1e81520 Iustin Pop
  , DiskMode(..)
45 b1e81520 Iustin Pop
  , DiskType(..)
46 2e12944a Iustin Pop
  , DiskLogicalId(..)
47 b1e81520 Iustin Pop
  , Disk(..)
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 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 b1e81520 Iustin Pop
  ) where
92 b1e81520 Iustin Pop
93 adb77e3a Iustin Pop
import Data.List (foldl')
94 b1e81520 Iustin Pop
import Data.Maybe
95 adb77e3a Iustin Pop
import qualified Data.Map as Map
96 04dd53a3 Iustin Pop
import qualified Data.Set as Set
97 32a569fe Iustin Pop
import Text.JSON (showJSON, readJSON, JSON, JSValue(..))
98 2e12944a Iustin Pop
import qualified Text.JSON as J
99 b1e81520 Iustin Pop
100 b1e81520 Iustin Pop
import qualified Ganeti.Constants as C
101 f3baf5ef Iustin Pop
import Ganeti.JSON
102 5e9deac0 Iustin Pop
import Ganeti.Types
103 b1e81520 Iustin Pop
import Ganeti.THH
104 b1e81520 Iustin Pop
105 adb77e3a Iustin Pop
-- * Generic definitions
106 adb77e3a Iustin Pop
107 adb77e3a Iustin Pop
-- | Fills one map with keys from the other map, if not already
108 adb77e3a Iustin Pop
-- existing. Mirrors objects.py:FillDict.
109 adb77e3a Iustin Pop
fillDict :: (Ord k) => Map.Map k v -> Map.Map k v -> [k] -> Map.Map k v
110 adb77e3a Iustin Pop
fillDict defaults custom skip_keys =
111 adb77e3a Iustin Pop
  let updated = Map.union custom defaults
112 adb77e3a Iustin Pop
  in foldl' (flip Map.delete) updated skip_keys
113 adb77e3a Iustin Pop
114 9d4cc8ed Iustin Pop
-- | The VTYPES, a mini-type system in Python.
115 9d4cc8ed Iustin Pop
$(declareSADT "VType"
116 9d4cc8ed Iustin Pop
  [ ("VTypeString",      'C.vtypeString)
117 9d4cc8ed Iustin Pop
  , ("VTypeMaybeString", 'C.vtypeMaybeString)
118 9d4cc8ed Iustin Pop
  , ("VTypeBool",        'C.vtypeBool)
119 9d4cc8ed Iustin Pop
  , ("VTypeSize",        'C.vtypeSize)
120 9d4cc8ed Iustin Pop
  , ("VTypeInt",         'C.vtypeInt)
121 9d4cc8ed Iustin Pop
  ])
122 9d4cc8ed Iustin Pop
$(makeJSONInstance ''VType)
123 9d4cc8ed Iustin Pop
124 b09cce64 Iustin Pop
-- | The hypervisor parameter type. This is currently a simple map,
125 b09cce64 Iustin Pop
-- without type checking on key/value pairs.
126 b09cce64 Iustin Pop
type HvParams = Container JSValue
127 b09cce64 Iustin Pop
128 b09cce64 Iustin Pop
-- | The OS parameters type. This is, and will remain, a string
129 b09cce64 Iustin Pop
-- container, since the keys are dynamically declared by the OSes, and
130 b09cce64 Iustin Pop
-- the values are always strings.
131 b09cce64 Iustin Pop
type OsParams = Container String
132 b09cce64 Iustin Pop
133 04dd53a3 Iustin Pop
-- | Class of objects that have timestamps.
134 04dd53a3 Iustin Pop
class TimeStampObject a where
135 04dd53a3 Iustin Pop
  cTimeOf :: a -> Double
136 04dd53a3 Iustin Pop
  mTimeOf :: a -> Double
137 04dd53a3 Iustin Pop
138 04dd53a3 Iustin Pop
-- | Class of objects that have an UUID.
139 04dd53a3 Iustin Pop
class UuidObject a where
140 04dd53a3 Iustin Pop
  uuidOf :: a -> String
141 04dd53a3 Iustin Pop
142 04dd53a3 Iustin Pop
-- | Class of object that have a serial number.
143 04dd53a3 Iustin Pop
class SerialNoObject a where
144 04dd53a3 Iustin Pop
  serialOf :: a -> Int
145 04dd53a3 Iustin Pop
146 04dd53a3 Iustin Pop
-- | Class of objects that have tags.
147 04dd53a3 Iustin Pop
class TagsObject a where
148 04dd53a3 Iustin Pop
  tagsOf :: a -> Set.Set String
149 04dd53a3 Iustin Pop
150 da45c352 Iustin Pop
-- * Node role object
151 da45c352 Iustin Pop
152 da45c352 Iustin Pop
$(declareSADT "NodeRole"
153 da45c352 Iustin Pop
  [ ("NROffline",   'C.nrOffline)
154 da45c352 Iustin Pop
  , ("NRDrained",   'C.nrDrained)
155 da45c352 Iustin Pop
  , ("NRRegular",   'C.nrRegular)
156 da45c352 Iustin Pop
  , ("NRCandidate", 'C.nrMcandidate)
157 da45c352 Iustin Pop
  , ("NRMaster",    'C.nrMaster)
158 da45c352 Iustin Pop
  ])
159 da45c352 Iustin Pop
$(makeJSONInstance ''NodeRole)
160 da45c352 Iustin Pop
161 da45c352 Iustin Pop
-- | The description of the node role.
162 da45c352 Iustin Pop
roleDescription :: NodeRole -> String
163 da45c352 Iustin Pop
roleDescription NROffline   = "offline"
164 da45c352 Iustin Pop
roleDescription NRDrained   = "drained"
165 da45c352 Iustin Pop
roleDescription NRRegular   = "regular"
166 da45c352 Iustin Pop
roleDescription NRCandidate = "master candidate"
167 da45c352 Iustin Pop
roleDescription NRMaster    = "master"
168 da45c352 Iustin Pop
169 b1e81520 Iustin Pop
-- * NIC definitions
170 b1e81520 Iustin Pop
171 b1e81520 Iustin Pop
$(declareSADT "NICMode"
172 b1e81520 Iustin Pop
  [ ("NMBridged", 'C.nicModeBridged)
173 b1e81520 Iustin Pop
  , ("NMRouted",  'C.nicModeRouted)
174 b1e81520 Iustin Pop
  ])
175 b1e81520 Iustin Pop
$(makeJSONInstance ''NICMode)
176 b1e81520 Iustin Pop
177 b09cce64 Iustin Pop
$(buildParam "Nic" "nicp"
178 b1e81520 Iustin Pop
  [ simpleField "mode" [t| NICMode |]
179 b1e81520 Iustin Pop
  , simpleField "link" [t| String  |]
180 b1e81520 Iustin Pop
  ])
181 b1e81520 Iustin Pop
182 b09cce64 Iustin Pop
$(buildObject "PartialNic" "nic"
183 b1e81520 Iustin Pop
  [ simpleField "mac" [t| String |]
184 b1e81520 Iustin Pop
  , optionalField $ simpleField "ip" [t| String |]
185 b09cce64 Iustin Pop
  , simpleField "nicparams" [t| PartialNicParams |]
186 b1e81520 Iustin Pop
  ])
187 b1e81520 Iustin Pop
188 b1e81520 Iustin Pop
-- * Disk definitions
189 b1e81520 Iustin Pop
190 b1e81520 Iustin Pop
$(declareSADT "DiskMode"
191 b1e81520 Iustin Pop
  [ ("DiskRdOnly", 'C.diskRdonly)
192 b1e81520 Iustin Pop
  , ("DiskRdWr",   'C.diskRdwr)
193 b1e81520 Iustin Pop
  ])
194 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskMode)
195 b1e81520 Iustin Pop
196 b1e81520 Iustin Pop
$(declareSADT "DiskType"
197 b1e81520 Iustin Pop
  [ ("LD_LV",       'C.ldLv)
198 b1e81520 Iustin Pop
  , ("LD_DRBD8",    'C.ldDrbd8)
199 b1e81520 Iustin Pop
  , ("LD_FILE",     'C.ldFile)
200 b1e81520 Iustin Pop
  , ("LD_BLOCKDEV", 'C.ldBlockdev)
201 2e12944a Iustin Pop
  , ("LD_RADOS",    'C.ldRbd)
202 b1e81520 Iustin Pop
  ])
203 b1e81520 Iustin Pop
$(makeJSONInstance ''DiskType)
204 b1e81520 Iustin Pop
205 2e12944a Iustin Pop
-- | The file driver type.
206 2e12944a Iustin Pop
$(declareSADT "FileDriver"
207 2e12944a Iustin Pop
  [ ("FileLoop",   'C.fdLoop)
208 2e12944a Iustin Pop
  , ("FileBlktap", 'C.fdBlktap)
209 2e12944a Iustin Pop
  ])
210 2e12944a Iustin Pop
$(makeJSONInstance ''FileDriver)
211 2e12944a Iustin Pop
212 2e12944a Iustin Pop
-- | The persistent block driver type. Currently only one type is allowed.
213 2e12944a Iustin Pop
$(declareSADT "BlockDriver"
214 2e12944a Iustin Pop
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
215 2e12944a Iustin Pop
  ])
216 2e12944a Iustin Pop
$(makeJSONInstance ''BlockDriver)
217 2e12944a Iustin Pop
218 2e12944a Iustin Pop
-- | Constant for the dev_type key entry in the disk config.
219 2e12944a Iustin Pop
devType :: String
220 2e12944a Iustin Pop
devType = "dev_type"
221 2e12944a Iustin Pop
222 2e12944a Iustin Pop
-- | The disk configuration type. This includes the disk type itself,
223 2e12944a Iustin Pop
-- for a more complete consistency. Note that since in the Python
224 2e12944a Iustin Pop
-- code-base there's no authoritative place where we document the
225 2e12944a Iustin Pop
-- logical id, this is probably a good reference point.
226 2e12944a Iustin Pop
data DiskLogicalId
227 2e12944a Iustin Pop
  = LIDPlain String String  -- ^ Volume group, logical volume
228 2e12944a Iustin Pop
  | LIDDrbd8 String String Int Int Int String
229 2e12944a Iustin Pop
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
230 2e12944a Iustin Pop
  | LIDFile FileDriver String -- ^ Driver, path
231 2e12944a Iustin Pop
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
232 2e12944a Iustin Pop
  | LIDRados String String -- ^ Unused, path
233 2e12944a Iustin Pop
    deriving (Read, Show, Eq)
234 2e12944a Iustin Pop
235 2e12944a Iustin Pop
-- | Mapping from a logical id to a disk type.
236 2e12944a Iustin Pop
lidDiskType :: DiskLogicalId -> DiskType
237 2e12944a Iustin Pop
lidDiskType (LIDPlain {}) = LD_LV
238 2e12944a Iustin Pop
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
239 2e12944a Iustin Pop
lidDiskType (LIDFile  {}) = LD_FILE
240 2e12944a Iustin Pop
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
241 2e12944a Iustin Pop
lidDiskType (LIDRados {}) = LD_RADOS
242 2e12944a Iustin Pop
243 2e12944a Iustin Pop
-- | Builds the extra disk_type field for a given logical id.
244 2e12944a Iustin Pop
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
245 2e12944a Iustin Pop
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
246 2e12944a Iustin Pop
247 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId (logical id only).
248 2e12944a Iustin Pop
encodeDLId :: DiskLogicalId -> JSValue
249 2e12944a Iustin Pop
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
250 2e12944a Iustin Pop
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
251 2e12944a Iustin Pop
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
252 2e12944a Iustin Pop
          , showJSON minorA, showJSON minorB, showJSON key ]
253 2e12944a Iustin Pop
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
254 2e12944a Iustin Pop
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
255 2e12944a Iustin Pop
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
256 2e12944a Iustin Pop
257 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId, composing both the logical id
258 2e12944a Iustin Pop
-- and the extra disk_type field.
259 2e12944a Iustin Pop
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
260 2e12944a Iustin Pop
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
261 2e12944a Iustin Pop
262 2e12944a Iustin Pop
-- | Custom decoder for DiskLogicalId. This is manual for now, since
263 2e12944a Iustin Pop
-- we don't have yet automation for separate-key style fields.
264 2e12944a Iustin Pop
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
265 2e12944a Iustin Pop
decodeDLId obj lid = do
266 2e12944a Iustin Pop
  dtype <- fromObj obj devType
267 2e12944a Iustin Pop
  case dtype of
268 2e12944a Iustin Pop
    LD_DRBD8 ->
269 2e12944a Iustin Pop
      case lid of
270 2e12944a Iustin Pop
        JSArray [nA, nB, p, mA, mB, k] -> do
271 2e12944a Iustin Pop
          nA' <- readJSON nA
272 2e12944a Iustin Pop
          nB' <- readJSON nB
273 2e12944a Iustin Pop
          p'  <- readJSON p
274 2e12944a Iustin Pop
          mA' <- readJSON mA
275 2e12944a Iustin Pop
          mB' <- readJSON mB
276 2e12944a Iustin Pop
          k'  <- readJSON k
277 2e12944a Iustin Pop
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
278 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for DRBD8 type"
279 2e12944a Iustin Pop
    LD_LV ->
280 2e12944a Iustin Pop
      case lid of
281 2e12944a Iustin Pop
        JSArray [vg, lv] -> do
282 2e12944a Iustin Pop
          vg' <- readJSON vg
283 2e12944a Iustin Pop
          lv' <- readJSON lv
284 2e12944a Iustin Pop
          return $ LIDPlain vg' lv'
285 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for plain type"
286 2e12944a Iustin Pop
    LD_FILE ->
287 2e12944a Iustin Pop
      case lid of
288 2e12944a Iustin Pop
        JSArray [driver, path] -> do
289 2e12944a Iustin Pop
          driver' <- readJSON driver
290 2e12944a Iustin Pop
          path'   <- readJSON path
291 2e12944a Iustin Pop
          return $ LIDFile driver' path'
292 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for file type"
293 2e12944a Iustin Pop
    LD_BLOCKDEV ->
294 2e12944a Iustin Pop
      case lid of
295 2e12944a Iustin Pop
        JSArray [driver, path] -> do
296 2e12944a Iustin Pop
          driver' <- readJSON driver
297 2e12944a Iustin Pop
          path'   <- readJSON path
298 2e12944a Iustin Pop
          return $ LIDBlockDev driver' path'
299 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for blockdev type"
300 2e12944a Iustin Pop
    LD_RADOS ->
301 2e12944a Iustin Pop
      case lid of
302 2e12944a Iustin Pop
        JSArray [driver, path] -> do
303 2e12944a Iustin Pop
          driver' <- readJSON driver
304 2e12944a Iustin Pop
          path'   <- readJSON path
305 2e12944a Iustin Pop
          return $ LIDRados driver' path'
306 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for rdb type"
307 2e12944a Iustin Pop
308 b1e81520 Iustin Pop
-- | Disk data structure.
309 b1e81520 Iustin Pop
--
310 b1e81520 Iustin Pop
-- This is declared manually as it's a recursive structure, and our TH
311 b1e81520 Iustin Pop
-- code currently can't build it.
312 b1e81520 Iustin Pop
data Disk = Disk
313 2e12944a Iustin Pop
  { diskLogicalId  :: DiskLogicalId
314 b1e81520 Iustin Pop
--  , diskPhysicalId :: String
315 b1e81520 Iustin Pop
  , diskChildren   :: [Disk]
316 b1e81520 Iustin Pop
  , diskIvName     :: String
317 b1e81520 Iustin Pop
  , diskSize       :: Int
318 b1e81520 Iustin Pop
  , diskMode       :: DiskMode
319 b1e81520 Iustin Pop
  } deriving (Read, Show, Eq)
320 b1e81520 Iustin Pop
321 b1e81520 Iustin Pop
$(buildObjectSerialisation "Disk"
322 2e12944a Iustin Pop
  [ customField 'decodeDLId 'encodeFullDLId $
323 2e12944a Iustin Pop
      simpleField "logical_id"    [t| DiskLogicalId   |]
324 b1e81520 Iustin Pop
--  , simpleField "physical_id" [t| String   |]
325 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
326 b1e81520 Iustin Pop
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
327 b1e81520 Iustin Pop
  , simpleField "size" [t| Int |]
328 b1e81520 Iustin Pop
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
329 b1e81520 Iustin Pop
  ])
330 b1e81520 Iustin Pop
331 b1e81520 Iustin Pop
-- * Instance definitions
332 b1e81520 Iustin Pop
333 b1e81520 Iustin Pop
$(declareSADT "AdminState"
334 b1e81520 Iustin Pop
  [ ("AdminOffline", 'C.adminstOffline)
335 b1e81520 Iustin Pop
  , ("AdminDown",    'C.adminstDown)
336 b1e81520 Iustin Pop
  , ("AdminUp",      'C.adminstUp)
337 b1e81520 Iustin Pop
  ])
338 b1e81520 Iustin Pop
$(makeJSONInstance ''AdminState)
339 b1e81520 Iustin Pop
340 5b11f8db Iustin Pop
$(buildParam "Be" "bep"
341 b1e81520 Iustin Pop
  [ simpleField "minmem"       [t| Int  |]
342 b1e81520 Iustin Pop
  , simpleField "maxmem"       [t| Int  |]
343 b1e81520 Iustin Pop
  , simpleField "vcpus"        [t| Int  |]
344 b1e81520 Iustin Pop
  , simpleField "auto_balance" [t| Bool |]
345 b1e81520 Iustin Pop
  ])
346 b1e81520 Iustin Pop
347 b1e81520 Iustin Pop
$(buildObject "Instance" "inst" $
348 b1e81520 Iustin Pop
  [ simpleField "name"           [t| String             |]
349 b1e81520 Iustin Pop
  , simpleField "primary_node"   [t| String             |]
350 b1e81520 Iustin Pop
  , simpleField "os"             [t| String             |]
351 b09cce64 Iustin Pop
  , simpleField "hypervisor"     [t| Hypervisor         |]
352 b09cce64 Iustin Pop
  , simpleField "hvparams"       [t| HvParams           |]
353 b09cce64 Iustin Pop
  , simpleField "beparams"       [t| PartialBeParams    |]
354 b09cce64 Iustin Pop
  , simpleField "osparams"       [t| OsParams           |]
355 b1e81520 Iustin Pop
  , simpleField "admin_state"    [t| AdminState         |]
356 b09cce64 Iustin Pop
  , simpleField "nics"           [t| [PartialNic]       |]
357 b1e81520 Iustin Pop
  , simpleField "disks"          [t| [Disk]             |]
358 b1e81520 Iustin Pop
  , simpleField "disk_template"  [t| DiskTemplate       |]
359 b09cce64 Iustin Pop
  , optionalField $ simpleField "network_port" [t| Int  |]
360 b1e81520 Iustin Pop
  ]
361 b1e81520 Iustin Pop
  ++ timeStampFields
362 b1e81520 Iustin Pop
  ++ uuidFields
363 f2374060 Iustin Pop
  ++ serialFields
364 f2374060 Iustin Pop
  ++ tagsFields)
365 b1e81520 Iustin Pop
366 04dd53a3 Iustin Pop
instance TimeStampObject Instance where
367 04dd53a3 Iustin Pop
  cTimeOf = instCtime
368 04dd53a3 Iustin Pop
  mTimeOf = instMtime
369 04dd53a3 Iustin Pop
370 04dd53a3 Iustin Pop
instance UuidObject Instance where
371 04dd53a3 Iustin Pop
  uuidOf = instUuid
372 04dd53a3 Iustin Pop
373 04dd53a3 Iustin Pop
instance SerialNoObject Instance where
374 04dd53a3 Iustin Pop
  serialOf = instSerial
375 04dd53a3 Iustin Pop
376 04dd53a3 Iustin Pop
instance TagsObject Instance where
377 04dd53a3 Iustin Pop
  tagsOf = instTags
378 04dd53a3 Iustin Pop
379 7514fe92 Iustin Pop
-- * IPolicy definitions
380 7514fe92 Iustin Pop
381 5b11f8db Iustin Pop
$(buildParam "ISpec" "ispec"
382 7514fe92 Iustin Pop
  [ simpleField C.ispecMemSize     [t| Int |]
383 7514fe92 Iustin Pop
  , simpleField C.ispecDiskSize    [t| Int |]
384 7514fe92 Iustin Pop
  , simpleField C.ispecDiskCount   [t| Int |]
385 7514fe92 Iustin Pop
  , simpleField C.ispecCpuCount    [t| Int |]
386 db154319 Iustin Pop
  , simpleField C.ispecNicCount    [t| Int |]
387 7514fe92 Iustin Pop
  , simpleField C.ispecSpindleUse  [t| Int |]
388 7514fe92 Iustin Pop
  ])
389 7514fe92 Iustin Pop
390 7514fe92 Iustin Pop
-- | Custom partial ipolicy. This is not built via buildParam since it
391 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
392 5b11f8db Iustin Pop
$(buildObject "PartialIPolicy" "ipolicy"
393 7514fe92 Iustin Pop
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
394 7514fe92 Iustin Pop
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
395 7514fe92 Iustin Pop
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
396 7514fe92 Iustin Pop
  , optionalField . renameField "SpindleRatioP"
397 7514fe92 Iustin Pop
                    $ simpleField "spindle-ratio"  [t| Double |]
398 7514fe92 Iustin Pop
  , optionalField . renameField "VcpuRatioP"
399 7514fe92 Iustin Pop
                    $ simpleField "vcpu-ratio"     [t| Double |]
400 7514fe92 Iustin Pop
  , optionalField . renameField "DiskTemplatesP"
401 7514fe92 Iustin Pop
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
402 7514fe92 Iustin Pop
  ])
403 7514fe92 Iustin Pop
404 7514fe92 Iustin Pop
-- | Custom filled ipolicy. This is not built via buildParam since it
405 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
406 5b11f8db Iustin Pop
$(buildObject "FilledIPolicy" "ipolicy"
407 7514fe92 Iustin Pop
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
408 7514fe92 Iustin Pop
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
409 7514fe92 Iustin Pop
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
410 7514fe92 Iustin Pop
  , simpleField "spindle-ratio"  [t| Double |]
411 7514fe92 Iustin Pop
  , simpleField "vcpu-ratio"     [t| Double |]
412 7514fe92 Iustin Pop
  , simpleField "disk-templates" [t| [DiskTemplate] |]
413 7514fe92 Iustin Pop
  ])
414 7514fe92 Iustin Pop
415 7514fe92 Iustin Pop
-- | Custom filler for the ipolicy types.
416 7514fe92 Iustin Pop
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
417 7514fe92 Iustin Pop
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
418 7514fe92 Iustin Pop
                           , ipolicyMaxSpec       = fmax
419 7514fe92 Iustin Pop
                           , ipolicyStdSpec       = fstd
420 7514fe92 Iustin Pop
                           , ipolicySpindleRatio  = fspindleRatio
421 7514fe92 Iustin Pop
                           , ipolicyVcpuRatio     = fvcpuRatio
422 7514fe92 Iustin Pop
                           , ipolicyDiskTemplates = fdiskTemplates})
423 7514fe92 Iustin Pop
            (PartialIPolicy { ipolicyMinSpecP       = pmin
424 7514fe92 Iustin Pop
                            , ipolicyMaxSpecP       = pmax
425 7514fe92 Iustin Pop
                            , ipolicyStdSpecP       = pstd
426 7514fe92 Iustin Pop
                            , ipolicySpindleRatioP  = pspindleRatio
427 7514fe92 Iustin Pop
                            , ipolicyVcpuRatioP     = pvcpuRatio
428 7514fe92 Iustin Pop
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
429 7514fe92 Iustin Pop
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
430 7514fe92 Iustin Pop
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
431 7514fe92 Iustin Pop
                , ipolicyStdSpec       = fillISpecParams fstd pstd
432 7514fe92 Iustin Pop
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
433 7514fe92 Iustin Pop
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
434 7514fe92 Iustin Pop
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
435 7514fe92 Iustin Pop
                                         pdiskTemplates
436 7514fe92 Iustin Pop
                }
437 b1e81520 Iustin Pop
-- * Node definitions
438 b1e81520 Iustin Pop
439 5b11f8db Iustin Pop
$(buildParam "ND" "ndp"
440 7514fe92 Iustin Pop
  [ simpleField "oob_program"   [t| String |]
441 7514fe92 Iustin Pop
  , simpleField "spindle_count" [t| Int    |]
442 b1e81520 Iustin Pop
  ])
443 b1e81520 Iustin Pop
444 b1e81520 Iustin Pop
$(buildObject "Node" "node" $
445 b1e81520 Iustin Pop
  [ simpleField "name"             [t| String |]
446 b1e81520 Iustin Pop
  , simpleField "primary_ip"       [t| String |]
447 b1e81520 Iustin Pop
  , simpleField "secondary_ip"     [t| String |]
448 b1e81520 Iustin Pop
  , simpleField "master_candidate" [t| Bool   |]
449 b1e81520 Iustin Pop
  , simpleField "offline"          [t| Bool   |]
450 b1e81520 Iustin Pop
  , simpleField "drained"          [t| Bool   |]
451 b1e81520 Iustin Pop
  , simpleField "group"            [t| String |]
452 b1e81520 Iustin Pop
  , simpleField "master_capable"   [t| Bool   |]
453 b1e81520 Iustin Pop
  , simpleField "vm_capable"       [t| Bool   |]
454 a957e150 Iustin Pop
  , simpleField "ndparams"         [t| PartialNDParams |]
455 b1e81520 Iustin Pop
  , simpleField "powered"          [t| Bool   |]
456 b1e81520 Iustin Pop
  ]
457 b1e81520 Iustin Pop
  ++ timeStampFields
458 b1e81520 Iustin Pop
  ++ uuidFields
459 f2374060 Iustin Pop
  ++ serialFields
460 f2374060 Iustin Pop
  ++ tagsFields)
461 b1e81520 Iustin Pop
462 04dd53a3 Iustin Pop
instance TimeStampObject Node where
463 04dd53a3 Iustin Pop
  cTimeOf = nodeCtime
464 04dd53a3 Iustin Pop
  mTimeOf = nodeMtime
465 04dd53a3 Iustin Pop
466 04dd53a3 Iustin Pop
instance UuidObject Node where
467 04dd53a3 Iustin Pop
  uuidOf = nodeUuid
468 04dd53a3 Iustin Pop
469 04dd53a3 Iustin Pop
instance SerialNoObject Node where
470 04dd53a3 Iustin Pop
  serialOf = nodeSerial
471 04dd53a3 Iustin Pop
472 04dd53a3 Iustin Pop
instance TagsObject Node where
473 04dd53a3 Iustin Pop
  tagsOf = nodeTags
474 04dd53a3 Iustin Pop
475 b1e81520 Iustin Pop
-- * NodeGroup definitions
476 b1e81520 Iustin Pop
477 b09cce64 Iustin Pop
-- | The disk parameters type.
478 b09cce64 Iustin Pop
type DiskParams = Container (Container JSValue)
479 b09cce64 Iustin Pop
480 b1e81520 Iustin Pop
$(buildObject "NodeGroup" "group" $
481 b1e81520 Iustin Pop
  [ simpleField "name"         [t| String |]
482 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
483 a957e150 Iustin Pop
  , simpleField "ndparams"     [t| PartialNDParams |]
484 7514fe92 Iustin Pop
  , simpleField "alloc_policy" [t| AllocPolicy     |]
485 7514fe92 Iustin Pop
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
486 b09cce64 Iustin Pop
  , simpleField "diskparams"   [t| DiskParams      |]
487 b1e81520 Iustin Pop
  ]
488 b1e81520 Iustin Pop
  ++ timeStampFields
489 b1e81520 Iustin Pop
  ++ uuidFields
490 f2374060 Iustin Pop
  ++ serialFields
491 f2374060 Iustin Pop
  ++ tagsFields)
492 b1e81520 Iustin Pop
493 04dd53a3 Iustin Pop
instance TimeStampObject NodeGroup where
494 04dd53a3 Iustin Pop
  cTimeOf = groupCtime
495 04dd53a3 Iustin Pop
  mTimeOf = groupMtime
496 04dd53a3 Iustin Pop
497 04dd53a3 Iustin Pop
instance UuidObject NodeGroup where
498 04dd53a3 Iustin Pop
  uuidOf = groupUuid
499 04dd53a3 Iustin Pop
500 04dd53a3 Iustin Pop
instance SerialNoObject NodeGroup where
501 04dd53a3 Iustin Pop
  serialOf = groupSerial
502 04dd53a3 Iustin Pop
503 04dd53a3 Iustin Pop
instance TagsObject NodeGroup where
504 04dd53a3 Iustin Pop
  tagsOf = groupTags
505 04dd53a3 Iustin Pop
506 a957e150 Iustin Pop
-- | IP family type
507 a957e150 Iustin Pop
$(declareIADT "IpFamily"
508 a957e150 Iustin Pop
  [ ("IpFamilyV4", 'C.ip4Family)
509 a957e150 Iustin Pop
  , ("IpFamilyV6", 'C.ip6Family)
510 a957e150 Iustin Pop
  ])
511 a957e150 Iustin Pop
$(makeJSONInstance ''IpFamily)
512 a957e150 Iustin Pop
513 a957e150 Iustin Pop
-- | Conversion from IP family to IP version. This is needed because
514 a957e150 Iustin Pop
-- Python uses both, depending on context.
515 a957e150 Iustin Pop
ipFamilyToVersion :: IpFamily -> Int
516 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV4 = C.ip4Version
517 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV6 = C.ip6Version
518 a957e150 Iustin Pop
519 b09cce64 Iustin Pop
-- | Cluster HvParams (hvtype to hvparams mapping).
520 b09cce64 Iustin Pop
type ClusterHvParams = Container HvParams
521 b09cce64 Iustin Pop
522 b09cce64 Iustin Pop
-- | Cluster Os-HvParams (os to hvparams mapping).
523 b09cce64 Iustin Pop
type OsHvParams = Container ClusterHvParams
524 b09cce64 Iustin Pop
525 b09cce64 Iustin Pop
-- | Cluser BeParams.
526 b09cce64 Iustin Pop
type ClusterBeParams = Container FilledBeParams
527 b09cce64 Iustin Pop
528 b09cce64 Iustin Pop
-- | Cluster OsParams.
529 b09cce64 Iustin Pop
type ClusterOsParams = Container OsParams
530 b09cce64 Iustin Pop
531 b09cce64 Iustin Pop
-- | Cluster NicParams.
532 b09cce64 Iustin Pop
type ClusterNicParams = Container FilledNicParams
533 b09cce64 Iustin Pop
534 b09cce64 Iustin Pop
-- | Cluster UID Pool, list (low, high) UID ranges.
535 b09cce64 Iustin Pop
type UidPool = [(Int, Int)]
536 b09cce64 Iustin Pop
537 b1e81520 Iustin Pop
-- * Cluster definitions
538 b1e81520 Iustin Pop
$(buildObject "Cluster" "cluster" $
539 b09cce64 Iustin Pop
  [ simpleField "rsahostkeypub"           [t| String           |]
540 b09cce64 Iustin Pop
  , simpleField "highest_used_port"       [t| Int              |]
541 b09cce64 Iustin Pop
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
542 b09cce64 Iustin Pop
  , simpleField "mac_prefix"              [t| String           |]
543 b09cce64 Iustin Pop
  , simpleField "volume_group_name"       [t| String           |]
544 b09cce64 Iustin Pop
  , simpleField "reserved_lvs"            [t| [String]         |]
545 b09cce64 Iustin Pop
  , optionalField $
546 b09cce64 Iustin Pop
    simpleField "drbd_usermode_helper"    [t| String           |]
547 b09cce64 Iustin Pop
  , simpleField "master_node"             [t| String           |]
548 b09cce64 Iustin Pop
  , simpleField "master_ip"               [t| String           |]
549 b09cce64 Iustin Pop
  , simpleField "master_netdev"           [t| String           |]
550 b09cce64 Iustin Pop
  , simpleField "master_netmask"          [t| Int              |]
551 b09cce64 Iustin Pop
  , simpleField "use_external_mip_script" [t| Bool             |]
552 b09cce64 Iustin Pop
  , simpleField "cluster_name"            [t| String           |]
553 b09cce64 Iustin Pop
  , simpleField "file_storage_dir"        [t| String           |]
554 b09cce64 Iustin Pop
  , simpleField "shared_file_storage_dir" [t| String           |]
555 f9b0084a Agata Murawska
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
556 b09cce64 Iustin Pop
  , simpleField "hvparams"                [t| ClusterHvParams  |]
557 b09cce64 Iustin Pop
  , simpleField "os_hvp"                  [t| OsHvParams       |]
558 b09cce64 Iustin Pop
  , simpleField "beparams"                [t| ClusterBeParams  |]
559 b09cce64 Iustin Pop
  , simpleField "osparams"                [t| ClusterOsParams  |]
560 b09cce64 Iustin Pop
  , simpleField "nicparams"               [t| ClusterNicParams |]
561 b09cce64 Iustin Pop
  , simpleField "ndparams"                [t| FilledNDParams   |]
562 b09cce64 Iustin Pop
  , simpleField "diskparams"              [t| DiskParams       |]
563 b09cce64 Iustin Pop
  , simpleField "candidate_pool_size"     [t| Int              |]
564 b09cce64 Iustin Pop
  , simpleField "modify_etc_hosts"        [t| Bool             |]
565 b09cce64 Iustin Pop
  , simpleField "modify_ssh_setup"        [t| Bool             |]
566 b09cce64 Iustin Pop
  , simpleField "maintain_node_health"    [t| Bool             |]
567 b09cce64 Iustin Pop
  , simpleField "uid_pool"                [t| UidPool          |]
568 b09cce64 Iustin Pop
  , simpleField "default_iallocator"      [t| String           |]
569 b09cce64 Iustin Pop
  , simpleField "hidden_os"               [t| [String]         |]
570 b09cce64 Iustin Pop
  , simpleField "blacklisted_os"          [t| [String]         |]
571 b09cce64 Iustin Pop
  , simpleField "primary_ip_family"       [t| IpFamily         |]
572 b09cce64 Iustin Pop
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
573 b09cce64 Iustin Pop
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
574 b1e81520 Iustin Pop
 ]
575 02cccecd Iustin Pop
 ++ timeStampFields
576 02cccecd Iustin Pop
 ++ uuidFields
577 04dd53a3 Iustin Pop
 ++ serialFields
578 02cccecd Iustin Pop
 ++ tagsFields)
579 b1e81520 Iustin Pop
580 04dd53a3 Iustin Pop
instance TimeStampObject Cluster where
581 04dd53a3 Iustin Pop
  cTimeOf = clusterCtime
582 04dd53a3 Iustin Pop
  mTimeOf = clusterMtime
583 04dd53a3 Iustin Pop
584 04dd53a3 Iustin Pop
instance UuidObject Cluster where
585 04dd53a3 Iustin Pop
  uuidOf = clusterUuid
586 04dd53a3 Iustin Pop
587 04dd53a3 Iustin Pop
instance SerialNoObject Cluster where
588 04dd53a3 Iustin Pop
  serialOf = clusterSerial
589 04dd53a3 Iustin Pop
590 04dd53a3 Iustin Pop
instance TagsObject Cluster where
591 04dd53a3 Iustin Pop
  tagsOf = clusterTags
592 04dd53a3 Iustin Pop
593 b1e81520 Iustin Pop
-- * ConfigData definitions
594 b1e81520 Iustin Pop
595 b1e81520 Iustin Pop
$(buildObject "ConfigData" "config" $
596 b1e81520 Iustin Pop
--  timeStampFields ++
597 d5a93a80 Iustin Pop
  [ simpleField "version"    [t| Int                 |]
598 d5a93a80 Iustin Pop
  , simpleField "cluster"    [t| Cluster             |]
599 d5a93a80 Iustin Pop
  , simpleField "nodes"      [t| Container Node      |]
600 d5a93a80 Iustin Pop
  , simpleField "nodegroups" [t| Container NodeGroup |]
601 d5a93a80 Iustin Pop
  , simpleField "instances"  [t| Container Instance  |]
602 b1e81520 Iustin Pop
  ]
603 b1e81520 Iustin Pop
  ++ serialFields)
604 04dd53a3 Iustin Pop
605 04dd53a3 Iustin Pop
instance SerialNoObject ConfigData where
606 04dd53a3 Iustin Pop
  serialOf = configSerial