Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Objects.hs @ 2af78b97

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