Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 6d558717

History | View | Annotate | Download (19.5 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 persistent block driver type. Currently only one type is allowed.
206 2e12944a Iustin Pop
$(declareSADT "BlockDriver"
207 2e12944a Iustin Pop
  [ ("BlockDrvManual", 'C.blockdevDriverManual)
208 2e12944a Iustin Pop
  ])
209 2e12944a Iustin Pop
$(makeJSONInstance ''BlockDriver)
210 2e12944a Iustin Pop
211 2e12944a Iustin Pop
-- | Constant for the dev_type key entry in the disk config.
212 2e12944a Iustin Pop
devType :: String
213 2e12944a Iustin Pop
devType = "dev_type"
214 2e12944a Iustin Pop
215 2e12944a Iustin Pop
-- | The disk configuration type. This includes the disk type itself,
216 2e12944a Iustin Pop
-- for a more complete consistency. Note that since in the Python
217 2e12944a Iustin Pop
-- code-base there's no authoritative place where we document the
218 2e12944a Iustin Pop
-- logical id, this is probably a good reference point.
219 2e12944a Iustin Pop
data DiskLogicalId
220 2e12944a Iustin Pop
  = LIDPlain String String  -- ^ Volume group, logical volume
221 2e12944a Iustin Pop
  | LIDDrbd8 String String Int Int Int String
222 2e12944a Iustin Pop
  -- ^ NodeA, NodeB, Port, MinorA, MinorB, Secret
223 2e12944a Iustin Pop
  | LIDFile FileDriver String -- ^ Driver, path
224 2e12944a Iustin Pop
  | LIDBlockDev BlockDriver String -- ^ Driver, path (must be under /dev)
225 2e12944a Iustin Pop
  | LIDRados String String -- ^ Unused, path
226 2e12944a Iustin Pop
    deriving (Read, Show, Eq)
227 2e12944a Iustin Pop
228 2e12944a Iustin Pop
-- | Mapping from a logical id to a disk type.
229 2e12944a Iustin Pop
lidDiskType :: DiskLogicalId -> DiskType
230 2e12944a Iustin Pop
lidDiskType (LIDPlain {}) = LD_LV
231 2e12944a Iustin Pop
lidDiskType (LIDDrbd8 {}) = LD_DRBD8
232 2e12944a Iustin Pop
lidDiskType (LIDFile  {}) = LD_FILE
233 2e12944a Iustin Pop
lidDiskType (LIDBlockDev {}) = LD_BLOCKDEV
234 2e12944a Iustin Pop
lidDiskType (LIDRados {}) = LD_RADOS
235 2e12944a Iustin Pop
236 2e12944a Iustin Pop
-- | Builds the extra disk_type field for a given logical id.
237 2e12944a Iustin Pop
lidEncodeType :: DiskLogicalId -> [(String, JSValue)]
238 2e12944a Iustin Pop
lidEncodeType v = [(devType, showJSON . lidDiskType $ v)]
239 2e12944a Iustin Pop
240 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId (logical id only).
241 2e12944a Iustin Pop
encodeDLId :: DiskLogicalId -> JSValue
242 2e12944a Iustin Pop
encodeDLId (LIDPlain vg lv) = JSArray [showJSON vg, showJSON lv]
243 2e12944a Iustin Pop
encodeDLId (LIDDrbd8 nodeA nodeB port minorA minorB key) =
244 2e12944a Iustin Pop
  JSArray [ showJSON nodeA, showJSON nodeB, showJSON port
245 2e12944a Iustin Pop
          , showJSON minorA, showJSON minorB, showJSON key ]
246 2e12944a Iustin Pop
encodeDLId (LIDRados pool name) = JSArray [showJSON pool, showJSON name]
247 2e12944a Iustin Pop
encodeDLId (LIDFile driver name) = JSArray [showJSON driver, showJSON name]
248 2e12944a Iustin Pop
encodeDLId (LIDBlockDev driver name) = JSArray [showJSON driver, showJSON name]
249 2e12944a Iustin Pop
250 2e12944a Iustin Pop
-- | Custom encoder for DiskLogicalId, composing both the logical id
251 2e12944a Iustin Pop
-- and the extra disk_type field.
252 2e12944a Iustin Pop
encodeFullDLId :: DiskLogicalId -> (JSValue, [(String, JSValue)])
253 2e12944a Iustin Pop
encodeFullDLId v = (encodeDLId v, lidEncodeType v)
254 2e12944a Iustin Pop
255 2e12944a Iustin Pop
-- | Custom decoder for DiskLogicalId. This is manual for now, since
256 2e12944a Iustin Pop
-- we don't have yet automation for separate-key style fields.
257 2e12944a Iustin Pop
decodeDLId :: [(String, JSValue)] -> JSValue -> J.Result DiskLogicalId
258 2e12944a Iustin Pop
decodeDLId obj lid = do
259 2e12944a Iustin Pop
  dtype <- fromObj obj devType
260 2e12944a Iustin Pop
  case dtype of
261 2e12944a Iustin Pop
    LD_DRBD8 ->
262 2e12944a Iustin Pop
      case lid of
263 2e12944a Iustin Pop
        JSArray [nA, nB, p, mA, mB, k] -> do
264 2e12944a Iustin Pop
          nA' <- readJSON nA
265 2e12944a Iustin Pop
          nB' <- readJSON nB
266 2e12944a Iustin Pop
          p'  <- readJSON p
267 2e12944a Iustin Pop
          mA' <- readJSON mA
268 2e12944a Iustin Pop
          mB' <- readJSON mB
269 2e12944a Iustin Pop
          k'  <- readJSON k
270 2e12944a Iustin Pop
          return $ LIDDrbd8 nA' nB' p' mA' mB' k'
271 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for DRBD8 type"
272 2e12944a Iustin Pop
    LD_LV ->
273 2e12944a Iustin Pop
      case lid of
274 2e12944a Iustin Pop
        JSArray [vg, lv] -> do
275 2e12944a Iustin Pop
          vg' <- readJSON vg
276 2e12944a Iustin Pop
          lv' <- readJSON lv
277 2e12944a Iustin Pop
          return $ LIDPlain vg' lv'
278 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for plain type"
279 2e12944a Iustin Pop
    LD_FILE ->
280 2e12944a Iustin Pop
      case lid of
281 2e12944a Iustin Pop
        JSArray [driver, path] -> do
282 2e12944a Iustin Pop
          driver' <- readJSON driver
283 2e12944a Iustin Pop
          path'   <- readJSON path
284 2e12944a Iustin Pop
          return $ LIDFile driver' path'
285 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for file type"
286 2e12944a Iustin Pop
    LD_BLOCKDEV ->
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 $ LIDBlockDev driver' path'
292 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for blockdev type"
293 2e12944a Iustin Pop
    LD_RADOS ->
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 $ LIDRados driver' path'
299 5b11f8db Iustin Pop
        _ -> fail "Can't read logical_id for rdb type"
300 2e12944a Iustin Pop
301 b1e81520 Iustin Pop
-- | Disk data structure.
302 b1e81520 Iustin Pop
--
303 b1e81520 Iustin Pop
-- This is declared manually as it's a recursive structure, and our TH
304 b1e81520 Iustin Pop
-- code currently can't build it.
305 b1e81520 Iustin Pop
data Disk = Disk
306 2e12944a Iustin Pop
  { diskLogicalId  :: DiskLogicalId
307 b1e81520 Iustin Pop
--  , diskPhysicalId :: String
308 b1e81520 Iustin Pop
  , diskChildren   :: [Disk]
309 b1e81520 Iustin Pop
  , diskIvName     :: String
310 b1e81520 Iustin Pop
  , diskSize       :: Int
311 b1e81520 Iustin Pop
  , diskMode       :: DiskMode
312 b1e81520 Iustin Pop
  } deriving (Read, Show, Eq)
313 b1e81520 Iustin Pop
314 b1e81520 Iustin Pop
$(buildObjectSerialisation "Disk"
315 2e12944a Iustin Pop
  [ customField 'decodeDLId 'encodeFullDLId $
316 2e12944a Iustin Pop
      simpleField "logical_id"    [t| DiskLogicalId   |]
317 b1e81520 Iustin Pop
--  , simpleField "physical_id" [t| String   |]
318 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "children" [t| [Disk] |]
319 b1e81520 Iustin Pop
  , defaultField [| "" |] $ simpleField "iv_name" [t| String |]
320 b1e81520 Iustin Pop
  , simpleField "size" [t| Int |]
321 b1e81520 Iustin Pop
  , defaultField [| DiskRdWr |] $ simpleField "mode" [t| DiskMode |]
322 b1e81520 Iustin Pop
  ])
323 b1e81520 Iustin Pop
324 b1e81520 Iustin Pop
-- * Instance definitions
325 b1e81520 Iustin Pop
326 b1e81520 Iustin Pop
$(declareSADT "AdminState"
327 b1e81520 Iustin Pop
  [ ("AdminOffline", 'C.adminstOffline)
328 b1e81520 Iustin Pop
  , ("AdminDown",    'C.adminstDown)
329 b1e81520 Iustin Pop
  , ("AdminUp",      'C.adminstUp)
330 b1e81520 Iustin Pop
  ])
331 b1e81520 Iustin Pop
$(makeJSONInstance ''AdminState)
332 b1e81520 Iustin Pop
333 5b11f8db Iustin Pop
$(buildParam "Be" "bep"
334 b1e81520 Iustin Pop
  [ simpleField "minmem"       [t| Int  |]
335 b1e81520 Iustin Pop
  , simpleField "maxmem"       [t| Int  |]
336 b1e81520 Iustin Pop
  , simpleField "vcpus"        [t| Int  |]
337 b1e81520 Iustin Pop
  , simpleField "auto_balance" [t| Bool |]
338 b1e81520 Iustin Pop
  ])
339 b1e81520 Iustin Pop
340 b1e81520 Iustin Pop
$(buildObject "Instance" "inst" $
341 b1e81520 Iustin Pop
  [ simpleField "name"           [t| String             |]
342 b1e81520 Iustin Pop
  , simpleField "primary_node"   [t| String             |]
343 b1e81520 Iustin Pop
  , simpleField "os"             [t| String             |]
344 b09cce64 Iustin Pop
  , simpleField "hypervisor"     [t| Hypervisor         |]
345 b09cce64 Iustin Pop
  , simpleField "hvparams"       [t| HvParams           |]
346 b09cce64 Iustin Pop
  , simpleField "beparams"       [t| PartialBeParams    |]
347 b09cce64 Iustin Pop
  , simpleField "osparams"       [t| OsParams           |]
348 b1e81520 Iustin Pop
  , simpleField "admin_state"    [t| AdminState         |]
349 b09cce64 Iustin Pop
  , simpleField "nics"           [t| [PartialNic]       |]
350 b1e81520 Iustin Pop
  , simpleField "disks"          [t| [Disk]             |]
351 b1e81520 Iustin Pop
  , simpleField "disk_template"  [t| DiskTemplate       |]
352 b09cce64 Iustin Pop
  , optionalField $ simpleField "network_port" [t| Int  |]
353 b1e81520 Iustin Pop
  ]
354 b1e81520 Iustin Pop
  ++ timeStampFields
355 b1e81520 Iustin Pop
  ++ uuidFields
356 f2374060 Iustin Pop
  ++ serialFields
357 f2374060 Iustin Pop
  ++ tagsFields)
358 b1e81520 Iustin Pop
359 04dd53a3 Iustin Pop
instance TimeStampObject Instance where
360 04dd53a3 Iustin Pop
  cTimeOf = instCtime
361 04dd53a3 Iustin Pop
  mTimeOf = instMtime
362 04dd53a3 Iustin Pop
363 04dd53a3 Iustin Pop
instance UuidObject Instance where
364 04dd53a3 Iustin Pop
  uuidOf = instUuid
365 04dd53a3 Iustin Pop
366 04dd53a3 Iustin Pop
instance SerialNoObject Instance where
367 04dd53a3 Iustin Pop
  serialOf = instSerial
368 04dd53a3 Iustin Pop
369 04dd53a3 Iustin Pop
instance TagsObject Instance where
370 04dd53a3 Iustin Pop
  tagsOf = instTags
371 04dd53a3 Iustin Pop
372 7514fe92 Iustin Pop
-- * IPolicy definitions
373 7514fe92 Iustin Pop
374 5b11f8db Iustin Pop
$(buildParam "ISpec" "ispec"
375 7514fe92 Iustin Pop
  [ simpleField C.ispecMemSize     [t| Int |]
376 7514fe92 Iustin Pop
  , simpleField C.ispecDiskSize    [t| Int |]
377 7514fe92 Iustin Pop
  , simpleField C.ispecDiskCount   [t| Int |]
378 7514fe92 Iustin Pop
  , simpleField C.ispecCpuCount    [t| Int |]
379 db154319 Iustin Pop
  , simpleField C.ispecNicCount    [t| Int |]
380 7514fe92 Iustin Pop
  , simpleField C.ispecSpindleUse  [t| Int |]
381 7514fe92 Iustin Pop
  ])
382 7514fe92 Iustin Pop
383 7514fe92 Iustin Pop
-- | Custom partial ipolicy. This is not built via buildParam since it
384 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
385 5b11f8db Iustin Pop
$(buildObject "PartialIPolicy" "ipolicy"
386 7514fe92 Iustin Pop
  [ renameField "MinSpecP" $ simpleField "min" [t| PartialISpecParams |]
387 7514fe92 Iustin Pop
  , renameField "MaxSpecP" $ simpleField "max" [t| PartialISpecParams |]
388 7514fe92 Iustin Pop
  , renameField "StdSpecP" $ simpleField "std" [t| PartialISpecParams |]
389 7514fe92 Iustin Pop
  , optionalField . renameField "SpindleRatioP"
390 7514fe92 Iustin Pop
                    $ simpleField "spindle-ratio"  [t| Double |]
391 7514fe92 Iustin Pop
  , optionalField . renameField "VcpuRatioP"
392 7514fe92 Iustin Pop
                    $ simpleField "vcpu-ratio"     [t| Double |]
393 7514fe92 Iustin Pop
  , optionalField . renameField "DiskTemplatesP"
394 7514fe92 Iustin Pop
                    $ simpleField "disk-templates" [t| [DiskTemplate] |]
395 7514fe92 Iustin Pop
  ])
396 7514fe92 Iustin Pop
397 7514fe92 Iustin Pop
-- | Custom filled ipolicy. This is not built via buildParam since it
398 7514fe92 Iustin Pop
-- has a special 2-level inheritance mode.
399 5b11f8db Iustin Pop
$(buildObject "FilledIPolicy" "ipolicy"
400 7514fe92 Iustin Pop
  [ renameField "MinSpec" $ simpleField "min" [t| FilledISpecParams |]
401 7514fe92 Iustin Pop
  , renameField "MaxSpec" $ simpleField "max" [t| FilledISpecParams |]
402 7514fe92 Iustin Pop
  , renameField "StdSpec" $ simpleField "std" [t| FilledISpecParams |]
403 7514fe92 Iustin Pop
  , simpleField "spindle-ratio"  [t| Double |]
404 7514fe92 Iustin Pop
  , simpleField "vcpu-ratio"     [t| Double |]
405 7514fe92 Iustin Pop
  , simpleField "disk-templates" [t| [DiskTemplate] |]
406 7514fe92 Iustin Pop
  ])
407 7514fe92 Iustin Pop
408 7514fe92 Iustin Pop
-- | Custom filler for the ipolicy types.
409 7514fe92 Iustin Pop
fillIPolicy :: FilledIPolicy -> PartialIPolicy -> FilledIPolicy
410 7514fe92 Iustin Pop
fillIPolicy (FilledIPolicy { ipolicyMinSpec       = fmin
411 7514fe92 Iustin Pop
                           , ipolicyMaxSpec       = fmax
412 7514fe92 Iustin Pop
                           , ipolicyStdSpec       = fstd
413 7514fe92 Iustin Pop
                           , ipolicySpindleRatio  = fspindleRatio
414 7514fe92 Iustin Pop
                           , ipolicyVcpuRatio     = fvcpuRatio
415 7514fe92 Iustin Pop
                           , ipolicyDiskTemplates = fdiskTemplates})
416 7514fe92 Iustin Pop
            (PartialIPolicy { ipolicyMinSpecP       = pmin
417 7514fe92 Iustin Pop
                            , ipolicyMaxSpecP       = pmax
418 7514fe92 Iustin Pop
                            , ipolicyStdSpecP       = pstd
419 7514fe92 Iustin Pop
                            , ipolicySpindleRatioP  = pspindleRatio
420 7514fe92 Iustin Pop
                            , ipolicyVcpuRatioP     = pvcpuRatio
421 7514fe92 Iustin Pop
                            , ipolicyDiskTemplatesP = pdiskTemplates}) =
422 7514fe92 Iustin Pop
  FilledIPolicy { ipolicyMinSpec       = fillISpecParams fmin pmin
423 7514fe92 Iustin Pop
                , ipolicyMaxSpec       = fillISpecParams fmax pmax
424 7514fe92 Iustin Pop
                , ipolicyStdSpec       = fillISpecParams fstd pstd
425 7514fe92 Iustin Pop
                , ipolicySpindleRatio  = fromMaybe fspindleRatio pspindleRatio
426 7514fe92 Iustin Pop
                , ipolicyVcpuRatio     = fromMaybe fvcpuRatio pvcpuRatio
427 7514fe92 Iustin Pop
                , ipolicyDiskTemplates = fromMaybe fdiskTemplates
428 7514fe92 Iustin Pop
                                         pdiskTemplates
429 7514fe92 Iustin Pop
                }
430 b1e81520 Iustin Pop
-- * Node definitions
431 b1e81520 Iustin Pop
432 5b11f8db Iustin Pop
$(buildParam "ND" "ndp"
433 7514fe92 Iustin Pop
  [ simpleField "oob_program"   [t| String |]
434 7514fe92 Iustin Pop
  , simpleField "spindle_count" [t| Int    |]
435 b1e81520 Iustin Pop
  ])
436 b1e81520 Iustin Pop
437 b1e81520 Iustin Pop
$(buildObject "Node" "node" $
438 b1e81520 Iustin Pop
  [ simpleField "name"             [t| String |]
439 b1e81520 Iustin Pop
  , simpleField "primary_ip"       [t| String |]
440 b1e81520 Iustin Pop
  , simpleField "secondary_ip"     [t| String |]
441 b1e81520 Iustin Pop
  , simpleField "master_candidate" [t| Bool   |]
442 b1e81520 Iustin Pop
  , simpleField "offline"          [t| Bool   |]
443 b1e81520 Iustin Pop
  , simpleField "drained"          [t| Bool   |]
444 b1e81520 Iustin Pop
  , simpleField "group"            [t| String |]
445 b1e81520 Iustin Pop
  , simpleField "master_capable"   [t| Bool   |]
446 b1e81520 Iustin Pop
  , simpleField "vm_capable"       [t| Bool   |]
447 a957e150 Iustin Pop
  , simpleField "ndparams"         [t| PartialNDParams |]
448 b1e81520 Iustin Pop
  , simpleField "powered"          [t| Bool   |]
449 b1e81520 Iustin Pop
  ]
450 b1e81520 Iustin Pop
  ++ timeStampFields
451 b1e81520 Iustin Pop
  ++ uuidFields
452 f2374060 Iustin Pop
  ++ serialFields
453 f2374060 Iustin Pop
  ++ tagsFields)
454 b1e81520 Iustin Pop
455 04dd53a3 Iustin Pop
instance TimeStampObject Node where
456 04dd53a3 Iustin Pop
  cTimeOf = nodeCtime
457 04dd53a3 Iustin Pop
  mTimeOf = nodeMtime
458 04dd53a3 Iustin Pop
459 04dd53a3 Iustin Pop
instance UuidObject Node where
460 04dd53a3 Iustin Pop
  uuidOf = nodeUuid
461 04dd53a3 Iustin Pop
462 04dd53a3 Iustin Pop
instance SerialNoObject Node where
463 04dd53a3 Iustin Pop
  serialOf = nodeSerial
464 04dd53a3 Iustin Pop
465 04dd53a3 Iustin Pop
instance TagsObject Node where
466 04dd53a3 Iustin Pop
  tagsOf = nodeTags
467 04dd53a3 Iustin Pop
468 b1e81520 Iustin Pop
-- * NodeGroup definitions
469 b1e81520 Iustin Pop
470 b09cce64 Iustin Pop
-- | The disk parameters type.
471 b09cce64 Iustin Pop
type DiskParams = Container (Container JSValue)
472 b09cce64 Iustin Pop
473 b1e81520 Iustin Pop
$(buildObject "NodeGroup" "group" $
474 b1e81520 Iustin Pop
  [ simpleField "name"         [t| String |]
475 b1e81520 Iustin Pop
  , defaultField  [| [] |] $ simpleField "members" [t| [String] |]
476 a957e150 Iustin Pop
  , simpleField "ndparams"     [t| PartialNDParams |]
477 7514fe92 Iustin Pop
  , simpleField "alloc_policy" [t| AllocPolicy     |]
478 7514fe92 Iustin Pop
  , simpleField "ipolicy"      [t| PartialIPolicy  |]
479 b09cce64 Iustin Pop
  , simpleField "diskparams"   [t| DiskParams      |]
480 b1e81520 Iustin Pop
  ]
481 b1e81520 Iustin Pop
  ++ timeStampFields
482 b1e81520 Iustin Pop
  ++ uuidFields
483 f2374060 Iustin Pop
  ++ serialFields
484 f2374060 Iustin Pop
  ++ tagsFields)
485 b1e81520 Iustin Pop
486 04dd53a3 Iustin Pop
instance TimeStampObject NodeGroup where
487 04dd53a3 Iustin Pop
  cTimeOf = groupCtime
488 04dd53a3 Iustin Pop
  mTimeOf = groupMtime
489 04dd53a3 Iustin Pop
490 04dd53a3 Iustin Pop
instance UuidObject NodeGroup where
491 04dd53a3 Iustin Pop
  uuidOf = groupUuid
492 04dd53a3 Iustin Pop
493 04dd53a3 Iustin Pop
instance SerialNoObject NodeGroup where
494 04dd53a3 Iustin Pop
  serialOf = groupSerial
495 04dd53a3 Iustin Pop
496 04dd53a3 Iustin Pop
instance TagsObject NodeGroup where
497 04dd53a3 Iustin Pop
  tagsOf = groupTags
498 04dd53a3 Iustin Pop
499 a957e150 Iustin Pop
-- | IP family type
500 a957e150 Iustin Pop
$(declareIADT "IpFamily"
501 a957e150 Iustin Pop
  [ ("IpFamilyV4", 'C.ip4Family)
502 a957e150 Iustin Pop
  , ("IpFamilyV6", 'C.ip6Family)
503 a957e150 Iustin Pop
  ])
504 a957e150 Iustin Pop
$(makeJSONInstance ''IpFamily)
505 a957e150 Iustin Pop
506 a957e150 Iustin Pop
-- | Conversion from IP family to IP version. This is needed because
507 a957e150 Iustin Pop
-- Python uses both, depending on context.
508 a957e150 Iustin Pop
ipFamilyToVersion :: IpFamily -> Int
509 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV4 = C.ip4Version
510 a957e150 Iustin Pop
ipFamilyToVersion IpFamilyV6 = C.ip6Version
511 a957e150 Iustin Pop
512 b09cce64 Iustin Pop
-- | Cluster HvParams (hvtype to hvparams mapping).
513 b09cce64 Iustin Pop
type ClusterHvParams = Container HvParams
514 b09cce64 Iustin Pop
515 b09cce64 Iustin Pop
-- | Cluster Os-HvParams (os to hvparams mapping).
516 b09cce64 Iustin Pop
type OsHvParams = Container ClusterHvParams
517 b09cce64 Iustin Pop
518 b09cce64 Iustin Pop
-- | Cluser BeParams.
519 b09cce64 Iustin Pop
type ClusterBeParams = Container FilledBeParams
520 b09cce64 Iustin Pop
521 b09cce64 Iustin Pop
-- | Cluster OsParams.
522 b09cce64 Iustin Pop
type ClusterOsParams = Container OsParams
523 b09cce64 Iustin Pop
524 b09cce64 Iustin Pop
-- | Cluster NicParams.
525 b09cce64 Iustin Pop
type ClusterNicParams = Container FilledNicParams
526 b09cce64 Iustin Pop
527 b09cce64 Iustin Pop
-- | Cluster UID Pool, list (low, high) UID ranges.
528 b09cce64 Iustin Pop
type UidPool = [(Int, Int)]
529 b09cce64 Iustin Pop
530 b1e81520 Iustin Pop
-- * Cluster definitions
531 b1e81520 Iustin Pop
$(buildObject "Cluster" "cluster" $
532 b09cce64 Iustin Pop
  [ simpleField "rsahostkeypub"           [t| String           |]
533 b09cce64 Iustin Pop
  , simpleField "highest_used_port"       [t| Int              |]
534 b09cce64 Iustin Pop
  , simpleField "tcpudp_port_pool"        [t| [Int]            |]
535 b09cce64 Iustin Pop
  , simpleField "mac_prefix"              [t| String           |]
536 b09cce64 Iustin Pop
  , simpleField "volume_group_name"       [t| String           |]
537 b09cce64 Iustin Pop
  , simpleField "reserved_lvs"            [t| [String]         |]
538 b09cce64 Iustin Pop
  , optionalField $
539 b09cce64 Iustin Pop
    simpleField "drbd_usermode_helper"    [t| String           |]
540 b09cce64 Iustin Pop
  , simpleField "master_node"             [t| String           |]
541 b09cce64 Iustin Pop
  , simpleField "master_ip"               [t| String           |]
542 b09cce64 Iustin Pop
  , simpleField "master_netdev"           [t| String           |]
543 b09cce64 Iustin Pop
  , simpleField "master_netmask"          [t| Int              |]
544 b09cce64 Iustin Pop
  , simpleField "use_external_mip_script" [t| Bool             |]
545 b09cce64 Iustin Pop
  , simpleField "cluster_name"            [t| String           |]
546 b09cce64 Iustin Pop
  , simpleField "file_storage_dir"        [t| String           |]
547 b09cce64 Iustin Pop
  , simpleField "shared_file_storage_dir" [t| String           |]
548 f9b0084a Agata Murawska
  , simpleField "enabled_hypervisors"     [t| [Hypervisor]     |]
549 b09cce64 Iustin Pop
  , simpleField "hvparams"                [t| ClusterHvParams  |]
550 b09cce64 Iustin Pop
  , simpleField "os_hvp"                  [t| OsHvParams       |]
551 b09cce64 Iustin Pop
  , simpleField "beparams"                [t| ClusterBeParams  |]
552 b09cce64 Iustin Pop
  , simpleField "osparams"                [t| ClusterOsParams  |]
553 b09cce64 Iustin Pop
  , simpleField "nicparams"               [t| ClusterNicParams |]
554 b09cce64 Iustin Pop
  , simpleField "ndparams"                [t| FilledNDParams   |]
555 b09cce64 Iustin Pop
  , simpleField "diskparams"              [t| DiskParams       |]
556 b09cce64 Iustin Pop
  , simpleField "candidate_pool_size"     [t| Int              |]
557 b09cce64 Iustin Pop
  , simpleField "modify_etc_hosts"        [t| Bool             |]
558 b09cce64 Iustin Pop
  , simpleField "modify_ssh_setup"        [t| Bool             |]
559 b09cce64 Iustin Pop
  , simpleField "maintain_node_health"    [t| Bool             |]
560 b09cce64 Iustin Pop
  , simpleField "uid_pool"                [t| UidPool          |]
561 b09cce64 Iustin Pop
  , simpleField "default_iallocator"      [t| String           |]
562 b09cce64 Iustin Pop
  , simpleField "hidden_os"               [t| [String]         |]
563 b09cce64 Iustin Pop
  , simpleField "blacklisted_os"          [t| [String]         |]
564 b09cce64 Iustin Pop
  , simpleField "primary_ip_family"       [t| IpFamily         |]
565 b09cce64 Iustin Pop
  , simpleField "prealloc_wipe_disks"     [t| Bool             |]
566 b09cce64 Iustin Pop
  , simpleField "ipolicy"                 [t| FilledIPolicy    |]
567 b1e81520 Iustin Pop
 ]
568 02cccecd Iustin Pop
 ++ timeStampFields
569 02cccecd Iustin Pop
 ++ uuidFields
570 04dd53a3 Iustin Pop
 ++ serialFields
571 02cccecd Iustin Pop
 ++ tagsFields)
572 b1e81520 Iustin Pop
573 04dd53a3 Iustin Pop
instance TimeStampObject Cluster where
574 04dd53a3 Iustin Pop
  cTimeOf = clusterCtime
575 04dd53a3 Iustin Pop
  mTimeOf = clusterMtime
576 04dd53a3 Iustin Pop
577 04dd53a3 Iustin Pop
instance UuidObject Cluster where
578 04dd53a3 Iustin Pop
  uuidOf = clusterUuid
579 04dd53a3 Iustin Pop
580 04dd53a3 Iustin Pop
instance SerialNoObject Cluster where
581 04dd53a3 Iustin Pop
  serialOf = clusterSerial
582 04dd53a3 Iustin Pop
583 04dd53a3 Iustin Pop
instance TagsObject Cluster where
584 04dd53a3 Iustin Pop
  tagsOf = clusterTags
585 04dd53a3 Iustin Pop
586 b1e81520 Iustin Pop
-- * ConfigData definitions
587 b1e81520 Iustin Pop
588 b1e81520 Iustin Pop
$(buildObject "ConfigData" "config" $
589 b1e81520 Iustin Pop
--  timeStampFields ++
590 d5a93a80 Iustin Pop
  [ simpleField "version"    [t| Int                 |]
591 d5a93a80 Iustin Pop
  , simpleField "cluster"    [t| Cluster             |]
592 d5a93a80 Iustin Pop
  , simpleField "nodes"      [t| Container Node      |]
593 d5a93a80 Iustin Pop
  , simpleField "nodegroups" [t| Container NodeGroup |]
594 d5a93a80 Iustin Pop
  , simpleField "instances"  [t| Container Instance  |]
595 b1e81520 Iustin Pop
  ]
596 b1e81520 Iustin Pop
  ++ serialFields)
597 04dd53a3 Iustin Pop
598 04dd53a3 Iustin Pop
instance SerialNoObject ConfigData where
599 04dd53a3 Iustin Pop
  serialOf = configSerial