Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 55416810

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