Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 04dd53a3

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