Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Backend / Simu.hs @ 96f9b0a6

History | View | Annotate | Download (4.3 kB)

1 525bfb36 Iustin Pop
{-| Parsing data from a simulated description of the cluster.
2 b2278348 Iustin Pop
3 b2278348 Iustin Pop
This module holds the code for parsing a cluster description.
4 b2278348 Iustin Pop
5 b2278348 Iustin Pop
-}
6 b2278348 Iustin Pop
7 b2278348 Iustin Pop
{-
8 b2278348 Iustin Pop
9 c324da14 Bernardo Dal Seno
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
10 b2278348 Iustin Pop
11 b2278348 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 b2278348 Iustin Pop
it under the terms of the GNU General Public License as published by
13 b2278348 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 b2278348 Iustin Pop
(at your option) any later version.
15 b2278348 Iustin Pop
16 b2278348 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 b2278348 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 b2278348 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 b2278348 Iustin Pop
General Public License for more details.
20 b2278348 Iustin Pop
21 b2278348 Iustin Pop
You should have received a copy of the GNU General Public License
22 b2278348 Iustin Pop
along with this program; if not, write to the Free Software
23 b2278348 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 b2278348 Iustin Pop
02110-1301, USA.
25 b2278348 Iustin Pop
26 b2278348 Iustin Pop
-}
27 b2278348 Iustin Pop
28 879d9290 Iustin Pop
module Ganeti.HTools.Backend.Simu
29 ebf38064 Iustin Pop
  ( loadData
30 ebf38064 Iustin Pop
  , parseData
31 ebf38064 Iustin Pop
  ) where
32 b2278348 Iustin Pop
33 2cdaf225 Iustin Pop
import Control.Monad (mplus, zipWithM)
34 b2278348 Iustin Pop
import Text.Printf (printf)
35 b2278348 Iustin Pop
36 01e52493 Iustin Pop
import Ganeti.BasicTypes
37 26d62e4c Iustin Pop
import Ganeti.Utils
38 b2278348 Iustin Pop
import Ganeti.HTools.Types
39 f4f6eb0b Iustin Pop
import Ganeti.HTools.Loader
40 99b63608 Iustin Pop
import qualified Ganeti.HTools.Container as Container
41 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
42 b2278348 Iustin Pop
import qualified Ganeti.HTools.Node as Node
43 b2278348 Iustin Pop
44 2ef8013f Iustin Pop
-- | Parse a shortened policy string (for command line usage).
45 2ef8013f Iustin Pop
apolAbbrev :: String -> Result AllocPolicy
46 2ef8013f Iustin Pop
apolAbbrev c | c == "p"  = return AllocPreferred
47 2ef8013f Iustin Pop
             | c == "a"  = return AllocLastResort
48 2ef8013f Iustin Pop
             | c == "u"  = return AllocUnallocable
49 2ef8013f Iustin Pop
             | otherwise = fail $ "Cannot parse AllocPolicy abbreviation '"
50 2ef8013f Iustin Pop
                           ++ c ++ "'"
51 2ef8013f Iustin Pop
52 9983063b Iustin Pop
-- | Parse the string description into nodes.
53 0c7d4422 Iustin Pop
parseDesc :: String -> [String]
54 c324da14 Bernardo Dal Seno
          -> Result (AllocPolicy, Int, Int, Int, Int, Int, Bool)
55 c324da14 Bernardo Dal Seno
parseDesc _ [a, n, d, m, c, s, exstor] = do
56 0c7d4422 Iustin Pop
  apol <- allocPolicyFromRaw a `mplus` apolAbbrev a
57 0c7d4422 Iustin Pop
  ncount <- tryRead "node count" n
58 0c7d4422 Iustin Pop
  disk <- annotateResult "disk size" (parseUnit d)
59 0c7d4422 Iustin Pop
  mem <- annotateResult "memory size" (parseUnit m)
60 0c7d4422 Iustin Pop
  cpu <- tryRead "cpu count" c
61 0c7d4422 Iustin Pop
  spindles <- tryRead "spindles" s
62 c324da14 Bernardo Dal Seno
  excl_stor <- tryRead "exclusive storage" exstor
63 c324da14 Bernardo Dal Seno
  return (apol, ncount, disk, mem, cpu, spindles, excl_stor)
64 0c7d4422 Iustin Pop
65 0c7d4422 Iustin Pop
parseDesc desc [a, n, d, m, c] = parseDesc desc [a, n, d, m, c, "1"]
66 0c7d4422 Iustin Pop
67 c324da14 Bernardo Dal Seno
parseDesc desc [a, n, d, m, c, s] = parseDesc desc [a, n, d, m, c, s, "False"]
68 c324da14 Bernardo Dal Seno
69 0c7d4422 Iustin Pop
parseDesc desc es =
70 0c7d4422 Iustin Pop
  fail $ printf
71 0c7d4422 Iustin Pop
         "Invalid cluster specification, expected 6 comma-separated\
72 0c7d4422 Iustin Pop
         \ sections (allocation policy, node count, disk size,\
73 0c7d4422 Iustin Pop
         \ memory size, number of CPUs, spindles) but got %d: '%s'"
74 0c7d4422 Iustin Pop
         (length es) desc
75 b2278348 Iustin Pop
76 9983063b Iustin Pop
-- | Creates a node group with the given specifications.
77 9983063b Iustin Pop
createGroup :: Int    -- ^ The group index
78 9983063b Iustin Pop
            -> String -- ^ The group specification
79 9983063b Iustin Pop
            -> Result (Group.Group, [Node.Node])
80 9983063b Iustin Pop
createGroup grpIndex spec = do
81 c324da14 Bernardo Dal Seno
  (apol, ncount, disk, mem, cpu, spindles, excl_stor) <- parseDesc spec $
82 c324da14 Bernardo Dal Seno
                                                         sepSplit ',' spec
83 9983063b Iustin Pop
  let nodes = map (\idx ->
84 30dd3377 Klaus Aehlig
                    flip Node.setMaster (grpIndex == 1 && idx == 1) $
85 30dd3377 Klaus Aehlig
                    Node.create (printf "node-%02d-%03d" grpIndex idx)
86 30dd3377 Klaus Aehlig
                      (fromIntegral mem) 0 mem
87 30dd3377 Klaus Aehlig
                      (fromIntegral disk) disk
88 96f9b0a6 Bernardo Dal Seno
                      (fromIntegral cpu) False spindles 0 grpIndex excl_stor
89 9983063b Iustin Pop
                  ) [1..ncount]
90 c8b199db Thomas Thrainer
      -- TODO: parse networks to which this group is connected
91 9983063b Iustin Pop
      grp = Group.create (printf "group-%02d" grpIndex)
92 c8b199db Thomas Thrainer
            (printf "fake-uuid-%02d" grpIndex) apol [] defIPolicy []
93 7af6975a Iustin Pop
  return (Group.setIdx grp grpIndex, nodes)
94 9983063b Iustin Pop
95 b2278348 Iustin Pop
-- | Builds the cluster data from node\/instance files.
96 9983063b Iustin Pop
parseData :: [String] -- ^ Cluster description in text format
97 f4f6eb0b Iustin Pop
          -> Result ClusterData
98 5e718042 Iustin Pop
parseData ndata = do
99 2cdaf225 Iustin Pop
  grpNodeData <- zipWithM createGroup [1..] ndata
100 9983063b Iustin Pop
  let (groups, nodes) = unzip grpNodeData
101 9983063b Iustin Pop
      nodes' = concat nodes
102 9983063b Iustin Pop
  let ktn = map (\(idx, n) -> (idx, Node.setIdx n idx))
103 9983063b Iustin Pop
            $ zip [1..] nodes'
104 9983063b Iustin Pop
      ktg = map (\g -> (Group.idx g, g)) groups
105 cb0c77ff Iustin Pop
  return (ClusterData (Container.fromList ktg)
106 71375ef7 Iustin Pop
                      (Container.fromList ktn) Container.empty [] defIPolicy)
107 5e718042 Iustin Pop
108 5e718042 Iustin Pop
-- | Builds the cluster data from node\/instance files.
109 9983063b Iustin Pop
loadData :: [String] -- ^ Cluster description in text format
110 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
111 5e718042 Iustin Pop
loadData = -- IO monad, just for consistency with the other loaders
112 5e718042 Iustin Pop
  return . parseData