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