Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Text.hs @ c8c071cb

History | View | Annotate | Download (16.7 kB)

1 525bfb36 Iustin Pop
{-| Parsing data from text-files.
2 040afc35 Iustin Pop
3 040afc35 Iustin Pop
This module holds the code for loading the cluster state from text
4 525bfb36 Iustin Pop
files, as produced by @gnt-node@ and @gnt-instance@ @list@ command.
5 040afc35 Iustin Pop
6 040afc35 Iustin Pop
-}
7 040afc35 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 da5f09ef Bernardo Dal Seno
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
14 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e2fa2baf Iustin Pop
(at your option) any later version.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e2fa2baf Iustin Pop
General Public License for more details.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
23 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
24 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e2fa2baf Iustin Pop
02110-1301, USA.
26 e2fa2baf Iustin Pop
27 e2fa2baf Iustin Pop
-}
28 e2fa2baf Iustin Pop
29 879d9290 Iustin Pop
module Ganeti.HTools.Backend.Text
30 ebf38064 Iustin Pop
  ( loadData
31 ebf38064 Iustin Pop
  , parseData
32 ebf38064 Iustin Pop
  , loadInst
33 ebf38064 Iustin Pop
  , loadNode
34 bcd17bf0 Iustin Pop
  , loadISpec
35 41044e04 Bernardo Dal Seno
  , loadMultipleMinMaxISpecs
36 bcd17bf0 Iustin Pop
  , loadIPolicy
37 c09359ee Bernardo Dal Seno
  , serializeInstance
38 ebf38064 Iustin Pop
  , serializeInstances
39 ebf38064 Iustin Pop
  , serializeNode
40 ebf38064 Iustin Pop
  , serializeNodes
41 bcd17bf0 Iustin Pop
  , serializeGroup
42 bcd17bf0 Iustin Pop
  , serializeISpec
43 41044e04 Bernardo Dal Seno
  , serializeMultipleMinMaxISpecs
44 bcd17bf0 Iustin Pop
  , serializeIPolicy
45 ebf38064 Iustin Pop
  , serializeCluster
46 ebf38064 Iustin Pop
  ) where
47 040afc35 Iustin Pop
48 040afc35 Iustin Pop
import Control.Monad
49 3bf75b7d Iustin Pop
import Data.List
50 3bf75b7d Iustin Pop
51 3bf75b7d Iustin Pop
import Text.Printf (printf)
52 040afc35 Iustin Pop
53 01e52493 Iustin Pop
import Ganeti.BasicTypes
54 26d62e4c Iustin Pop
import Ganeti.Utils
55 040afc35 Iustin Pop
import Ganeti.HTools.Loader
56 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
57 3bf75b7d Iustin Pop
import qualified Ganeti.HTools.Container as Container
58 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
59 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
60 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
61 040afc35 Iustin Pop
62 b37f4a76 Iustin Pop
-- * Helper functions
63 b37f4a76 Iustin Pop
64 b37f4a76 Iustin Pop
-- | Simple wrapper over sepSplit
65 b37f4a76 Iustin Pop
commaSplit :: String -> [String]
66 b37f4a76 Iustin Pop
commaSplit = sepSplit ','
67 b37f4a76 Iustin Pop
68 525bfb36 Iustin Pop
-- * Serialisation functions
69 525bfb36 Iustin Pop
70 525bfb36 Iustin Pop
-- | Serialize a single group.
71 e4d8071d Iustin Pop
serializeGroup :: Group.Group -> String
72 e4d8071d Iustin Pop
serializeGroup grp =
73 a0be8f1a Thomas Thrainer
  printf "%s|%s|%s|%s|%s" (Group.name grp) (Group.uuid grp)
74 ebf38064 Iustin Pop
           (allocPolicyToRaw (Group.allocPolicy grp))
75 6b6e335b Dato Simó
           (intercalate "," (Group.allTags grp))
76 a0be8f1a Thomas Thrainer
           (intercalate "," (Group.networks grp))
77 e4d8071d Iustin Pop
78 525bfb36 Iustin Pop
-- | Generate group file data from a group list.
79 e4d8071d Iustin Pop
serializeGroups :: Group.List -> String
80 e4d8071d Iustin Pop
serializeGroups = unlines . map serializeGroup . Container.elems
81 e4d8071d Iustin Pop
82 525bfb36 Iustin Pop
-- | Serialize a single node.
83 525bfb36 Iustin Pop
serializeNode :: Group.List -- ^ The list of groups (needed for group uuid)
84 525bfb36 Iustin Pop
              -> Node.Node  -- ^ The node to be serialised
85 525bfb36 Iustin Pop
              -> String
86 10ef6b4e Iustin Pop
serializeNode gl node =
87 c8c071cb Bernardo Dal Seno
  printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s|%d|%s|%s|%d|%d" (Node.name node)
88 ebf38064 Iustin Pop
           (Node.tMem node) (Node.nMem node) (Node.fMem node)
89 ebf38064 Iustin Pop
           (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
90 000ca91a Klaus Aehlig
           (if Node.offline node then 'Y' else
91 000ca91a Klaus Aehlig
              if Node.isMaster node then 'M' else 'N')
92 ebf38064 Iustin Pop
           (Group.uuid grp)
93 96f9b0a6 Bernardo Dal Seno
           (Node.tSpindles node)
94 4b542ebc Klaus Aehlig
           (intercalate "," (Node.nTags node))
95 c324da14 Bernardo Dal Seno
           (if Node.exclStorage node then "Y" else "N")
96 96f9b0a6 Bernardo Dal Seno
           (Node.fSpindles node)
97 c8c071cb Bernardo Dal Seno
           (Node.nCpu node)
98 10ef6b4e Iustin Pop
    where grp = Container.find (Node.group node) gl
99 3bf75b7d Iustin Pop
100 525bfb36 Iustin Pop
-- | Generate node file data from node objects.
101 10ef6b4e Iustin Pop
serializeNodes :: Group.List -> Node.List -> String
102 10ef6b4e Iustin Pop
serializeNodes gl = unlines . map (serializeNode gl) . Container.elems
103 3bf75b7d Iustin Pop
104 525bfb36 Iustin Pop
-- | Serialize a single instance.
105 525bfb36 Iustin Pop
serializeInstance :: Node.List         -- ^ The node list (needed for
106 525bfb36 Iustin Pop
                                       -- node names)
107 525bfb36 Iustin Pop
                  -> Instance.Instance -- ^ The instance to be serialised
108 525bfb36 Iustin Pop
                  -> String
109 3bf75b7d Iustin Pop
serializeInstance nl inst =
110 ebf38064 Iustin Pop
  let iname = Instance.name inst
111 ebf38064 Iustin Pop
      pnode = Container.nameOf nl (Instance.pNode inst)
112 ebf38064 Iustin Pop
      sidx = Instance.sNode inst
113 ebf38064 Iustin Pop
      snode = (if sidx == Node.noSecondary
114 ebf38064 Iustin Pop
                 then ""
115 ebf38064 Iustin Pop
                 else Container.nameOf nl sidx)
116 2724417c Bernardo Dal Seno
  in printf "%s|%d|%d|%d|%s|%s|%s|%s|%s|%s|%d|%s"
117 ebf38064 Iustin Pop
       iname (Instance.mem inst) (Instance.dsk inst)
118 ebf38064 Iustin Pop
       (Instance.vcpus inst) (instanceStatusToRaw (Instance.runSt inst))
119 ebf38064 Iustin Pop
       (if Instance.autoBalance inst then "Y" else "N")
120 ebf38064 Iustin Pop
       pnode snode (diskTemplateToRaw (Instance.diskTemplate inst))
121 2f907bad Dato Simó
       (intercalate "," (Instance.allTags inst)) (Instance.spindleUse inst)
122 2724417c Bernardo Dal Seno
       -- disk spindles are summed together, as it's done for disk size
123 2724417c Bernardo Dal Seno
       (case Instance.getTotalSpindles inst of
124 2724417c Bernardo Dal Seno
          Nothing -> "-"
125 2724417c Bernardo Dal Seno
          Just x -> show x)
126 3bf75b7d Iustin Pop
127 525bfb36 Iustin Pop
-- | Generate instance file data from instance objects.
128 3bf75b7d Iustin Pop
serializeInstances :: Node.List -> Instance.List -> String
129 3bf75b7d Iustin Pop
serializeInstances nl =
130 ebf38064 Iustin Pop
  unlines . map (serializeInstance nl) . Container.elems
131 3bf75b7d Iustin Pop
132 41044e04 Bernardo Dal Seno
-- | Separator between ISpecs (in MinMaxISpecs).
133 41044e04 Bernardo Dal Seno
iSpecsSeparator :: Char
134 41044e04 Bernardo Dal Seno
iSpecsSeparator = ';'
135 41044e04 Bernardo Dal Seno
136 b37f4a76 Iustin Pop
-- | Generate a spec data from a given ISpec object.
137 b37f4a76 Iustin Pop
serializeISpec :: ISpec -> String
138 b37f4a76 Iustin Pop
serializeISpec ispec =
139 b37f4a76 Iustin Pop
  -- this needs to be kept in sync with the object definition
140 d953a965 René Nussbaumer
  let ISpec mem_s cpu_c disk_s disk_c nic_c su = ispec
141 d953a965 René Nussbaumer
      strings = [show mem_s, show cpu_c, show disk_s, show disk_c, show nic_c,
142 d953a965 René Nussbaumer
                 show su]
143 b37f4a76 Iustin Pop
  in intercalate "," strings
144 b37f4a76 Iustin Pop
145 b37f4a76 Iustin Pop
-- | Generate disk template data.
146 b37f4a76 Iustin Pop
serializeDiskTemplates :: [DiskTemplate] -> String
147 b37f4a76 Iustin Pop
serializeDiskTemplates = intercalate "," . map diskTemplateToRaw
148 b37f4a76 Iustin Pop
149 41044e04 Bernardo Dal Seno
-- | Generate min/max instance specs data.
150 41044e04 Bernardo Dal Seno
serializeMultipleMinMaxISpecs :: [MinMaxISpecs] -> String
151 41044e04 Bernardo Dal Seno
serializeMultipleMinMaxISpecs minmaxes =
152 41044e04 Bernardo Dal Seno
  intercalate [iSpecsSeparator] $ foldr serialpair [] minmaxes
153 41044e04 Bernardo Dal Seno
  where serialpair (MinMaxISpecs minspec maxspec) acc =
154 41044e04 Bernardo Dal Seno
          serializeISpec minspec : serializeISpec maxspec : acc
155 41044e04 Bernardo Dal Seno
156 b37f4a76 Iustin Pop
-- | Generate policy data from a given policy object.
157 b37f4a76 Iustin Pop
serializeIPolicy :: String -> IPolicy -> String
158 b37f4a76 Iustin Pop
serializeIPolicy owner ipol =
159 da5f09ef Bernardo Dal Seno
  let IPolicy minmax stdspec dts vcpu_ratio spindle_ratio = ipol
160 b37f4a76 Iustin Pop
      strings = [ owner
161 b37f4a76 Iustin Pop
                , serializeISpec stdspec
162 41044e04 Bernardo Dal Seno
                , serializeMultipleMinMaxISpecs minmax
163 b37f4a76 Iustin Pop
                , serializeDiskTemplates dts
164 e8fa4ff6 Iustin Pop
                , show vcpu_ratio
165 c22d4dd4 Iustin Pop
                , show spindle_ratio
166 b37f4a76 Iustin Pop
                ]
167 b37f4a76 Iustin Pop
  in intercalate "|" strings
168 b37f4a76 Iustin Pop
169 b37f4a76 Iustin Pop
-- | Generates the entire ipolicy section from the cluster and group
170 b37f4a76 Iustin Pop
-- objects.
171 b37f4a76 Iustin Pop
serializeAllIPolicies :: IPolicy -> Group.List -> String
172 b37f4a76 Iustin Pop
serializeAllIPolicies cpol gl =
173 b37f4a76 Iustin Pop
  let groups = Container.elems gl
174 5b11f8db Iustin Pop
      allpolicies = ("", cpol) :
175 b37f4a76 Iustin Pop
                    map (\g -> (Group.name g, Group.iPolicy g)) groups
176 b37f4a76 Iustin Pop
      strings = map (uncurry serializeIPolicy) allpolicies
177 b37f4a76 Iustin Pop
  in unlines strings
178 b37f4a76 Iustin Pop
179 525bfb36 Iustin Pop
-- | Generate complete cluster data from node and instance lists.
180 c0e31451 Iustin Pop
serializeCluster :: ClusterData -> String
181 b37f4a76 Iustin Pop
serializeCluster (ClusterData gl nl il ctags cpol) =
182 e4d8071d Iustin Pop
  let gdata = serializeGroups gl
183 e4d8071d Iustin Pop
      ndata = serializeNodes gl nl
184 4a273e97 Iustin Pop
      idata = serializeInstances nl il
185 b37f4a76 Iustin Pop
      pdata = serializeAllIPolicies cpol gl
186 716c6be5 Iustin Pop
  -- note: not using 'unlines' as that adds too many newlines
187 b37f4a76 Iustin Pop
  in intercalate "\n" [gdata, ndata, idata, unlines ctags, pdata]
188 4a273e97 Iustin Pop
189 525bfb36 Iustin Pop
-- * Parsing functions
190 525bfb36 Iustin Pop
191 a679e9dc Iustin Pop
-- | Load a group from a field list.
192 525bfb36 Iustin Pop
loadGroup :: (Monad m) => [String]
193 525bfb36 Iustin Pop
          -> m (String, Group.Group) -- ^ The result, a tuple of group
194 525bfb36 Iustin Pop
                                     -- UUID and group object
195 a0be8f1a Thomas Thrainer
loadGroup [name, gid, apol, tags, nets] = do
196 5f828ce4 Agata Murawska
  xapol <- allocPolicyFromRaw apol
197 6b6e335b Dato Simó
  let xtags = commaSplit tags
198 a0be8f1a Thomas Thrainer
  let xnets = commaSplit nets
199 a0be8f1a Thomas Thrainer
  return (gid, Group.create name gid xapol xnets defIPolicy xtags)
200 a0be8f1a Thomas Thrainer
loadGroup [name, gid, apol, tags] = loadGroup [name, gid, apol, tags, ""]
201 a679e9dc Iustin Pop
loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
202 a679e9dc Iustin Pop
203 9188aeef Iustin Pop
-- | Load a node from a field list.
204 525bfb36 Iustin Pop
loadNode :: (Monad m) =>
205 525bfb36 Iustin Pop
            NameAssoc             -- ^ Association list with current groups
206 525bfb36 Iustin Pop
         -> [String]              -- ^ Input data as a list of fields
207 525bfb36 Iustin Pop
         -> m (String, Node.Node) -- ^ The result, a tuple o node name
208 525bfb36 Iustin Pop
                                  -- and node object
209 c324da14 Bernardo Dal Seno
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
210 c8c071cb Bernardo Dal Seno
              excl_stor, free_spindles, nos_cpu] = do
211 10ef6b4e Iustin Pop
  gdx <- lookupGroup ktg name gu
212 040afc35 Iustin Pop
  new_node <-
213 2cdaf225 Iustin Pop
      if "?" `elem` [tm,nm,fm,td,fd,tc] || fo == "Y" then
214 c8c071cb Bernardo Dal Seno
          return $ Node.create name 0 0 0 0 0 0 0 True 0 0 gdx False
215 040afc35 Iustin Pop
      else do
216 4b542ebc Klaus Aehlig
        let vtags = commaSplit tags
217 040afc35 Iustin Pop
        vtm <- tryRead name tm
218 040afc35 Iustin Pop
        vnm <- tryRead name nm
219 040afc35 Iustin Pop
        vfm <- tryRead name fm
220 040afc35 Iustin Pop
        vtd <- tryRead name td
221 040afc35 Iustin Pop
        vfd <- tryRead name fd
222 1a82215d Iustin Pop
        vtc <- tryRead name tc
223 c8c071cb Bernardo Dal Seno
        vnc <- tryRead name nos_cpu
224 f951bd09 Iustin Pop
        vspindles <- tryRead name spindles
225 96f9b0a6 Bernardo Dal Seno
        vfree_spindles <- tryRead name free_spindles
226 c324da14 Bernardo Dal Seno
        vexcl_stor <- case excl_stor of
227 c324da14 Bernardo Dal Seno
                        "Y" -> return True
228 c324da14 Bernardo Dal Seno
                        "N" -> return False
229 c324da14 Bernardo Dal Seno
                        _ -> fail $
230 c324da14 Bernardo Dal Seno
                             "Invalid exclusive_storage value for node '" ++
231 c324da14 Bernardo Dal Seno
                             name ++ "': " ++ excl_stor
232 4b542ebc Klaus Aehlig
        return . flip Node.setMaster (fo == "M") . flip Node.setNodeTags vtags $
233 c8c071cb Bernardo Dal Seno
          Node.create name vtm vnm vfm vtd vfd vtc vnc False vspindles
234 96f9b0a6 Bernardo Dal Seno
          vfree_spindles gdx vexcl_stor
235 040afc35 Iustin Pop
  return (name, new_node)
236 f951bd09 Iustin Pop
237 f951bd09 Iustin Pop
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu] =
238 f951bd09 Iustin Pop
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, "1"]
239 f951bd09 Iustin Pop
240 4b542ebc Klaus Aehlig
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles] =
241 4b542ebc Klaus Aehlig
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, ""]
242 4b542ebc Klaus Aehlig
243 c324da14 Bernardo Dal Seno
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags] =
244 c324da14 Bernardo Dal Seno
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags, "N"]
245 c324da14 Bernardo Dal Seno
246 96f9b0a6 Bernardo Dal Seno
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
247 96f9b0a6 Bernardo Dal Seno
              excl_stor] =
248 96f9b0a6 Bernardo Dal Seno
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
249 96f9b0a6 Bernardo Dal Seno
                excl_stor, "0"]
250 96f9b0a6 Bernardo Dal Seno
251 c8c071cb Bernardo Dal Seno
loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
252 c8c071cb Bernardo Dal Seno
              excl_stor, free_spindles] =
253 c8c071cb Bernardo Dal Seno
  loadNode ktg [name, tm, nm, fm, td, fd, tc, fo, gu, spindles, tags,
254 c8c071cb Bernardo Dal Seno
                excl_stor, free_spindles, "1"]
255 c8c071cb Bernardo Dal Seno
256 10ef6b4e Iustin Pop
loadNode _ s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
257 040afc35 Iustin Pop
258 9188aeef Iustin Pop
-- | Load an instance from a field list.
259 6429e8d8 Iustin Pop
loadInst :: NameAssoc -- ^ Association list with the current nodes
260 6429e8d8 Iustin Pop
         -> [String]  -- ^ Input data as a list of fields
261 6429e8d8 Iustin Pop
         -> Result (String, Instance.Instance) -- ^ A tuple of
262 6429e8d8 Iustin Pop
                                               -- instance name and
263 6429e8d8 Iustin Pop
                                               -- the instance object
264 6429e8d8 Iustin Pop
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
265 2724417c Bernardo Dal Seno
             , dt, tags, su, spindles ] = do
266 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
267 3603605a Iustin Pop
  sidx <- if null snode
268 3603605a Iustin Pop
            then return Node.noSecondary
269 3603605a Iustin Pop
            else lookupNode ktn name snode
270 040afc35 Iustin Pop
  vmem <- tryRead name mem
271 2724417c Bernardo Dal Seno
  dsize <- tryRead name dsk
272 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
273 7dd14211 Agata Murawska
  vstatus <- instanceStatusFromRaw status
274 bc782180 Iustin Pop
  auto_balance <- case auto_bal of
275 bc782180 Iustin Pop
                    "Y" -> return True
276 bc782180 Iustin Pop
                    "N" -> return False
277 bc782180 Iustin Pop
                    _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
278 bc782180 Iustin Pop
                         "' for instance " ++ name
279 2c9336a4 Iustin Pop
  disk_template <- annotateResult ("Instance " ++ name)
280 5f828ce4 Agata Murawska
                   (diskTemplateFromRaw dt)
281 ec629280 René Nussbaumer
  spindle_use <- tryRead name su
282 2724417c Bernardo Dal Seno
  vspindles <- case spindles of
283 2724417c Bernardo Dal Seno
                 "-" -> return Nothing
284 2724417c Bernardo Dal Seno
                 _ -> liftM Just (tryRead name spindles)
285 2724417c Bernardo Dal Seno
  let disk = Instance.Disk dsize vspindles
286 b37f4a76 Iustin Pop
  let vtags = commaSplit tags
287 2724417c Bernardo Dal Seno
      newinst = Instance.create name vmem dsize [disk] vvcpus vstatus vtags
288 908c2f67 Thomas Thrainer
                auto_balance pidx sidx disk_template spindle_use []
289 c09359ee Bernardo Dal Seno
  when (Instance.hasSecondary newinst && sidx == pidx) . fail $
290 c09359ee Bernardo Dal Seno
    "Instance " ++ name ++ " has same primary and secondary node - " ++ pnode
291 040afc35 Iustin Pop
  return (name, newinst)
292 52cc1370 René Nussbaumer
293 52cc1370 René Nussbaumer
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
294 52cc1370 René Nussbaumer
             , dt, tags ] = loadInst ktn [ name, mem, dsk, vcpus, status,
295 52cc1370 René Nussbaumer
                                           auto_bal, pnode, snode, dt, tags,
296 52cc1370 René Nussbaumer
                                           "1" ]
297 2724417c Bernardo Dal Seno
298 2724417c Bernardo Dal Seno
loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
299 2724417c Bernardo Dal Seno
             , dt, tags, su ] =
300 2724417c Bernardo Dal Seno
  loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode, dt
301 2724417c Bernardo Dal Seno
               , tags, su, "-" ]
302 2724417c Bernardo Dal Seno
303 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
304 040afc35 Iustin Pop
305 b37f4a76 Iustin Pop
-- | Loads a spec from a field list.
306 b37f4a76 Iustin Pop
loadISpec :: String -> [String] -> Result ISpec
307 d953a965 René Nussbaumer
loadISpec owner [mem_s, cpu_c, dsk_s, dsk_c, nic_c, su] = do
308 b37f4a76 Iustin Pop
  xmem_s <- tryRead (owner ++ "/memsize") mem_s
309 b37f4a76 Iustin Pop
  xcpu_c <- tryRead (owner ++ "/cpucount") cpu_c
310 b37f4a76 Iustin Pop
  xdsk_s <- tryRead (owner ++ "/disksize") dsk_s
311 b37f4a76 Iustin Pop
  xdsk_c <- tryRead (owner ++ "/diskcount") dsk_c
312 b37f4a76 Iustin Pop
  xnic_c <- tryRead (owner ++ "/niccount") nic_c
313 d953a965 René Nussbaumer
  xsu    <- tryRead (owner ++ "/spindleuse") su
314 d953a965 René Nussbaumer
  return $ ISpec xmem_s xcpu_c xdsk_s xdsk_c xnic_c xsu
315 b37f4a76 Iustin Pop
loadISpec owner s = fail $ "Invalid ispec data for " ++ owner ++ ": " ++ show s
316 b37f4a76 Iustin Pop
317 41044e04 Bernardo Dal Seno
-- | Load a single min/max ISpec pair
318 41044e04 Bernardo Dal Seno
loadMinMaxISpecs :: String -> String -> String -> Result MinMaxISpecs
319 41044e04 Bernardo Dal Seno
loadMinMaxISpecs owner minspec maxspec = do
320 41044e04 Bernardo Dal Seno
  xminspec <- loadISpec (owner ++ "/minspec") (commaSplit minspec)
321 41044e04 Bernardo Dal Seno
  xmaxspec <- loadISpec (owner ++ "/maxspec") (commaSplit maxspec)
322 41044e04 Bernardo Dal Seno
  return $ MinMaxISpecs xminspec xmaxspec
323 41044e04 Bernardo Dal Seno
324 41044e04 Bernardo Dal Seno
-- | Break a list of ispecs strings into a list of (min/max) ispecs pairs
325 41044e04 Bernardo Dal Seno
breakISpecsPairs :: String -> [String] -> Result [(String, String)]
326 41044e04 Bernardo Dal Seno
breakISpecsPairs _ [] =
327 41044e04 Bernardo Dal Seno
  return []
328 41044e04 Bernardo Dal Seno
breakISpecsPairs owner (x:y:xs) = do
329 41044e04 Bernardo Dal Seno
  rest <- breakISpecsPairs owner xs
330 41044e04 Bernardo Dal Seno
  return $ (x, y) : rest
331 41044e04 Bernardo Dal Seno
breakISpecsPairs owner _ =
332 41044e04 Bernardo Dal Seno
  fail $ "Odd number of min/max specs for " ++ owner
333 41044e04 Bernardo Dal Seno
334 41044e04 Bernardo Dal Seno
-- | Load a list of min/max ispecs pairs
335 41044e04 Bernardo Dal Seno
loadMultipleMinMaxISpecs :: String -> [String] -> Result [MinMaxISpecs]
336 41044e04 Bernardo Dal Seno
loadMultipleMinMaxISpecs owner ispecs = do
337 41044e04 Bernardo Dal Seno
  pairs <- breakISpecsPairs owner ispecs
338 41044e04 Bernardo Dal Seno
  mapM (uncurry $ loadMinMaxISpecs owner) pairs
339 41044e04 Bernardo Dal Seno
340 b37f4a76 Iustin Pop
-- | Loads an ipolicy from a field list.
341 b37f4a76 Iustin Pop
loadIPolicy :: [String] -> Result (String, IPolicy)
342 41044e04 Bernardo Dal Seno
loadIPolicy [owner, stdspec, minmaxspecs, dtemplates,
343 c22d4dd4 Iustin Pop
             vcpu_ratio, spindle_ratio] = do
344 b37f4a76 Iustin Pop
  xstdspec <- loadISpec (owner ++ "/stdspec") (commaSplit stdspec)
345 41044e04 Bernardo Dal Seno
  xminmaxspecs <- loadMultipleMinMaxISpecs owner $
346 41044e04 Bernardo Dal Seno
                  sepSplit iSpecsSeparator minmaxspecs
347 b37f4a76 Iustin Pop
  xdts <- mapM diskTemplateFromRaw $ commaSplit dtemplates
348 e8fa4ff6 Iustin Pop
  xvcpu_ratio <- tryRead (owner ++ "/vcpu_ratio") vcpu_ratio
349 c22d4dd4 Iustin Pop
  xspindle_ratio <- tryRead (owner ++ "/spindle_ratio") spindle_ratio
350 5b11f8db Iustin Pop
  return (owner,
351 41044e04 Bernardo Dal Seno
          IPolicy xminmaxspecs xstdspec
352 da5f09ef Bernardo Dal Seno
                xdts xvcpu_ratio xspindle_ratio)
353 b37f4a76 Iustin Pop
loadIPolicy s = fail $ "Invalid ipolicy data: '" ++ show s ++ "'"
354 b37f4a76 Iustin Pop
355 b37f4a76 Iustin Pop
loadOnePolicy :: (IPolicy, Group.List) -> String
356 b37f4a76 Iustin Pop
              -> Result (IPolicy, Group.List)
357 b37f4a76 Iustin Pop
loadOnePolicy (cpol, gl) line = do
358 b37f4a76 Iustin Pop
  (owner, ipol) <- loadIPolicy (sepSplit '|' line)
359 b37f4a76 Iustin Pop
  case owner of
360 b37f4a76 Iustin Pop
    "" -> return (ipol, gl) -- this is a cluster policy (no owner)
361 b37f4a76 Iustin Pop
    _ -> do
362 b37f4a76 Iustin Pop
      grp <- Container.findByName gl owner
363 b37f4a76 Iustin Pop
      let grp' = grp { Group.iPolicy = ipol }
364 b37f4a76 Iustin Pop
          gl' = Container.add (Group.idx grp') grp' gl
365 b37f4a76 Iustin Pop
      return (cpol, gl')
366 b37f4a76 Iustin Pop
367 b37f4a76 Iustin Pop
-- | Loads all policies from the policy section
368 b37f4a76 Iustin Pop
loadAllIPolicies :: Group.List -> [String] -> Result (IPolicy, Group.List)
369 b37f4a76 Iustin Pop
loadAllIPolicies gl =
370 b37f4a76 Iustin Pop
  foldM loadOnePolicy (defIPolicy, gl)
371 b37f4a76 Iustin Pop
372 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
373 9188aeef Iustin Pop
--
374 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
375 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
376 9188aeef Iustin Pop
-- a supplied conversion function.
377 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
378 525bfb36 Iustin Pop
               [String] -- ^ Input data, as a list of lines
379 525bfb36 Iustin Pop
            -> ([String] -> m (String, a)) -- ^ Conversion function
380 525bfb36 Iustin Pop
            -> m ( NameAssoc
381 525bfb36 Iustin Pop
                 , Container.Container a ) -- ^ A tuple of an
382 525bfb36 Iustin Pop
                                           -- association list (name
383 525bfb36 Iustin Pop
                                           -- to object) and a set as
384 525bfb36 Iustin Pop
                                           -- used in
385 525bfb36 Iustin Pop
                                           -- "Ganeti.HTools.Container"
386 525bfb36 Iustin Pop
387 f5197d89 Iustin Pop
loadTabular lines_data convert_fn = do
388 f5197d89 Iustin Pop
  let rows = map (sepSplit '|') lines_data
389 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
390 497e30a1 Iustin Pop
  return $ assignIndices kerows
391 040afc35 Iustin Pop
392 dadfc261 Iustin Pop
-- | Load the cluser data from disk.
393 525bfb36 Iustin Pop
--
394 525bfb36 Iustin Pop
-- This is an alias to 'readFile' just for consistency with the other
395 525bfb36 Iustin Pop
-- modules.
396 525bfb36 Iustin Pop
readData :: String    -- ^ Path to the text file
397 525bfb36 Iustin Pop
         -> IO String -- ^ Contents of the file
398 dadfc261 Iustin Pop
readData = readFile
399 dadfc261 Iustin Pop
400 16c2369c Iustin Pop
-- | Builds the cluster data from text input.
401 dadfc261 Iustin Pop
parseData :: String -- ^ Text data
402 f4f6eb0b Iustin Pop
          -> Result ClusterData
403 dadfc261 Iustin Pop
parseData fdata = do
404 16c2369c Iustin Pop
  let flines = lines fdata
405 b37f4a76 Iustin Pop
  (glines, nlines, ilines, ctags, pollines) <-
406 a604456d Iustin Pop
      case sepSplit "" flines of
407 b37f4a76 Iustin Pop
        [a, b, c, d, e] -> Ok (a, b, c, d, e)
408 b37f4a76 Iustin Pop
        [a, b, c, d] -> Ok (a, b, c, d, [])
409 a604456d Iustin Pop
        xs -> Bad $ printf "Invalid format of the input file: %d sections\
410 b37f4a76 Iustin Pop
                           \ instead of 4 or 5" (length xs)
411 b0b8337a Dato Simó
  {- group file: name uuid alloc_policy -}
412 10ef6b4e Iustin Pop
  (ktg, gl) <- loadTabular glines loadGroup
413 b0b8337a Dato Simó
  {- node file: name t_mem n_mem f_mem t_disk f_disk t_cpu offline grp_uuid
414 4b542ebc Klaus Aehlig
                spindles tags -}
415 a604456d Iustin Pop
  (ktn, nl) <- loadTabular nlines (loadNode ktg)
416 b0b8337a Dato Simó
  {- instance file: name mem disk vcpus status auto_bal pnode snode
417 b0b8337a Dato Simó
                    disk_template tags spindle_use -}
418 a604456d Iustin Pop
  (_, il) <- loadTabular ilines (loadInst ktn)
419 afcd5a0b Iustin Pop
  {- the tags are simply line-based, no processing needed -}
420 b37f4a76 Iustin Pop
  {- process policies -}
421 b37f4a76 Iustin Pop
  (cpol, gl') <- loadAllIPolicies gl pollines
422 b37f4a76 Iustin Pop
  return (ClusterData gl' nl il ctags cpol)
423 dadfc261 Iustin Pop
424 525bfb36 Iustin Pop
-- | Top level function for data loading.
425 dadfc261 Iustin Pop
loadData :: String -- ^ Path to the text file
426 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
427 2a8e2dc9 Iustin Pop
loadData = fmap parseData . readData