Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Text.hs @ 4b542ebc

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