Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Simu.hs @ f3f76ccc

History | View | Annotate | Download (3.7 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 7af6975a Iustin Pop
Copyright (C) 2009, 2010, 2011 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 b2278348 Iustin Pop
module Ganeti.HTools.Simu
29 ebf38064 Iustin Pop
  ( loadData
30 ebf38064 Iustin Pop
  , parseData
31 ebf38064 Iustin Pop
  ) where
32 b2278348 Iustin Pop
33 2ef8013f Iustin Pop
import Control.Monad (mplus)
34 b2278348 Iustin Pop
import Text.Printf (printf)
35 b2278348 Iustin Pop
36 b2278348 Iustin Pop
import Ganeti.HTools.Utils
37 b2278348 Iustin Pop
import Ganeti.HTools.Types
38 f4f6eb0b Iustin Pop
import Ganeti.HTools.Loader
39 99b63608 Iustin Pop
import qualified Ganeti.HTools.Container as Container
40 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
41 b2278348 Iustin Pop
import qualified Ganeti.HTools.Node as Node
42 b2278348 Iustin Pop
43 2ef8013f Iustin Pop
-- | Parse a shortened policy string (for command line usage).
44 2ef8013f Iustin Pop
apolAbbrev :: String -> Result AllocPolicy
45 2ef8013f Iustin Pop
apolAbbrev c | c == "p"  = return AllocPreferred
46 2ef8013f Iustin Pop
             | c == "a"  = return AllocLastResort
47 2ef8013f Iustin Pop
             | c == "u"  = return AllocUnallocable
48 2ef8013f Iustin Pop
             | otherwise = fail $ "Cannot parse AllocPolicy abbreviation '"
49 2ef8013f Iustin Pop
                           ++ c ++ "'"
50 2ef8013f Iustin Pop
51 9983063b Iustin Pop
-- | Parse the string description into nodes.
52 6c7448bb Iustin Pop
parseDesc :: String -> Result (AllocPolicy, Int, Int, Int, Int)
53 b2278348 Iustin Pop
parseDesc desc =
54 ebf38064 Iustin Pop
  case sepSplit ',' desc of
55 ebf38064 Iustin Pop
    [a, n, d, m, c] -> do
56 ebf38064 Iustin Pop
      apol <- allocPolicyFromRaw a `mplus` apolAbbrev a
57 ebf38064 Iustin Pop
      ncount <- tryRead "node count" n
58 ebf38064 Iustin Pop
      disk <- annotateResult "disk size" (parseUnit d)
59 ebf38064 Iustin Pop
      mem <- annotateResult "memory size" (parseUnit m)
60 ebf38064 Iustin Pop
      cpu <- tryRead "cpu count" c
61 ebf38064 Iustin Pop
      return (apol, ncount, disk, mem, cpu)
62 ebf38064 Iustin Pop
    es -> fail $ printf
63 ebf38064 Iustin Pop
          "Invalid cluster specification, expected 5 comma-separated\
64 ebf38064 Iustin Pop
          \ sections (allocation policy, node count, disk size,\
65 ebf38064 Iustin Pop
          \ memory size, number of CPUs) but got %d: '%s'" (length es) desc
66 b2278348 Iustin Pop
67 9983063b Iustin Pop
-- | Creates a node group with the given specifications.
68 9983063b Iustin Pop
createGroup :: Int    -- ^ The group index
69 9983063b Iustin Pop
            -> String -- ^ The group specification
70 9983063b Iustin Pop
            -> Result (Group.Group, [Node.Node])
71 9983063b Iustin Pop
createGroup grpIndex spec = do
72 6c7448bb Iustin Pop
  (apol, ncount, disk, mem, cpu) <- parseDesc spec
73 9983063b Iustin Pop
  let nodes = map (\idx ->
74 ebf38064 Iustin Pop
                     Node.create (printf "node-%02d-%03d" grpIndex idx)
75 ebf38064 Iustin Pop
                           (fromIntegral mem) 0 mem
76 ebf38064 Iustin Pop
                           (fromIntegral disk) disk
77 ebf38064 Iustin Pop
                           (fromIntegral cpu) False grpIndex
78 9983063b Iustin Pop
                  ) [1..ncount]
79 9983063b Iustin Pop
      grp = Group.create (printf "group-%02d" grpIndex)
80 6c7448bb Iustin Pop
            (printf "fake-uuid-%02d" grpIndex) apol
81 7af6975a Iustin Pop
  return (Group.setIdx grp grpIndex, nodes)
82 9983063b Iustin Pop
83 b2278348 Iustin Pop
-- | Builds the cluster data from node\/instance files.
84 9983063b Iustin Pop
parseData :: [String] -- ^ Cluster description in text format
85 f4f6eb0b Iustin Pop
          -> Result ClusterData
86 5e718042 Iustin Pop
parseData ndata = do
87 9983063b Iustin Pop
  grpNodeData <- mapM (uncurry createGroup) $ zip [1..] ndata
88 9983063b Iustin Pop
  let (groups, nodes) = unzip grpNodeData
89 9983063b Iustin Pop
      nodes' = concat nodes
90 9983063b Iustin Pop
  let ktn = map (\(idx, n) -> (idx, Node.setIdx n idx))
91 9983063b Iustin Pop
            $ zip [1..] nodes'
92 9983063b Iustin Pop
      ktg = map (\g -> (Group.idx g, g)) groups
93 cb0c77ff Iustin Pop
  return (ClusterData (Container.fromList ktg)
94 cb0c77ff Iustin Pop
                      (Container.fromList ktn) Container.empty [])
95 5e718042 Iustin Pop
96 5e718042 Iustin Pop
-- | Builds the cluster data from node\/instance files.
97 9983063b Iustin Pop
loadData :: [String] -- ^ Cluster description in text format
98 f4f6eb0b Iustin Pop
         -> IO (Result ClusterData)
99 5e718042 Iustin Pop
loadData = -- IO monad, just for consistency with the other loaders
100 5e718042 Iustin Pop
  return . parseData