Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 0ea11dcb

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