Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Objects.hs @ 3e0c2a24

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