Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Text.hs @ a334d536

History | View | Annotate | Download (5.8 kB)

1 040afc35 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 a8946537 Iustin Pop
files, as produced by gnt-node and gnt-instance list.
5 040afc35 Iustin Pop
6 040afc35 Iustin Pop
-}
7 040afc35 Iustin Pop
8 e2fa2baf Iustin Pop
{-
9 e2fa2baf Iustin Pop
10 3bf75b7d Iustin Pop
Copyright (C) 2009, 2010 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 040afc35 Iustin Pop
module Ganeti.HTools.Text
30 b2278348 Iustin Pop
    (
31 b2278348 Iustin Pop
      loadData
32 dadfc261 Iustin Pop
    , parseData
33 1ae7a904 Iustin Pop
    , loadInst
34 39d11971 Iustin Pop
    , loadNode
35 3bf75b7d Iustin Pop
    , serializeInstances
36 50811e2c Iustin Pop
    , serializeNode
37 3bf75b7d Iustin Pop
    , serializeNodes
38 4a273e97 Iustin Pop
    , serializeCluster
39 b2278348 Iustin Pop
    ) where
40 040afc35 Iustin Pop
41 040afc35 Iustin Pop
import Control.Monad
42 3bf75b7d Iustin Pop
import Data.List
43 3bf75b7d Iustin Pop
44 3bf75b7d Iustin Pop
import Text.Printf (printf)
45 040afc35 Iustin Pop
46 040afc35 Iustin Pop
import Ganeti.HTools.Utils
47 040afc35 Iustin Pop
import Ganeti.HTools.Loader
48 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
49 3bf75b7d Iustin Pop
import qualified Ganeti.HTools.Container as Container
50 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
51 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
52 040afc35 Iustin Pop
53 3bf75b7d Iustin Pop
-- | Serialize a single node
54 3bf75b7d Iustin Pop
serializeNode :: Node.Node -> String
55 3bf75b7d Iustin Pop
serializeNode node =
56 b3707354 Iustin Pop
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c|%s" (Node.name node)
57 3bf75b7d Iustin Pop
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
58 3bf75b7d Iustin Pop
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
59 3bf75b7d Iustin Pop
               (if Node.offline node then 'Y' else 'N')
60 b3707354 Iustin Pop
               (Node.group node)
61 3bf75b7d Iustin Pop
62 3bf75b7d Iustin Pop
-- | Generate node file data from node objects
63 3bf75b7d Iustin Pop
serializeNodes :: Node.List -> String
64 3bf75b7d Iustin Pop
serializeNodes = unlines . map serializeNode . Container.elems
65 3bf75b7d Iustin Pop
66 3bf75b7d Iustin Pop
-- | Serialize a single instance
67 3bf75b7d Iustin Pop
serializeInstance :: Node.List -> Instance.Instance -> String
68 3bf75b7d Iustin Pop
serializeInstance nl inst =
69 3bf75b7d Iustin Pop
    let
70 3bf75b7d Iustin Pop
        iname = Instance.name inst
71 3bf75b7d Iustin Pop
        pnode = Container.nameOf nl (Instance.pNode inst)
72 3bf75b7d Iustin Pop
        sidx = Instance.sNode inst
73 3bf75b7d Iustin Pop
        snode = (if sidx == Node.noSecondary
74 3bf75b7d Iustin Pop
                    then ""
75 3bf75b7d Iustin Pop
                    else Container.nameOf nl sidx)
76 3bf75b7d Iustin Pop
    in
77 3bf75b7d Iustin Pop
      printf "%s|%d|%d|%d|%s|%s|%s|%s"
78 3bf75b7d Iustin Pop
             iname (Instance.mem inst) (Instance.dsk inst)
79 3bf75b7d Iustin Pop
             (Instance.vcpus inst) (Instance.runSt inst)
80 3bf75b7d Iustin Pop
             pnode snode (intercalate "," (Instance.tags inst))
81 3bf75b7d Iustin Pop
82 3bf75b7d Iustin Pop
-- | Generate instance file data from instance objects
83 3bf75b7d Iustin Pop
serializeInstances :: Node.List -> Instance.List -> String
84 3bf75b7d Iustin Pop
serializeInstances nl =
85 3bf75b7d Iustin Pop
    unlines . map (serializeInstance nl) . Container.elems
86 3bf75b7d Iustin Pop
87 4a273e97 Iustin Pop
-- | Generate complete cluster data from node and instance lists
88 4a273e97 Iustin Pop
serializeCluster :: Node.List -> Instance.List -> String
89 4a273e97 Iustin Pop
serializeCluster nl il =
90 4a273e97 Iustin Pop
  let ndata = serializeNodes nl
91 4a273e97 Iustin Pop
      idata = serializeInstances nl il
92 4a273e97 Iustin Pop
  in ndata ++ ['\n'] ++ idata
93 4a273e97 Iustin Pop
94 9188aeef Iustin Pop
-- | Load a node from a field list.
95 040afc35 Iustin Pop
loadNode :: (Monad m) => [String] -> m (String, Node.Node)
96 b3707354 Iustin Pop
-- compatibility wrapper for old text files
97 b3707354 Iustin Pop
loadNode [name, tm, nm, fm, td, fd, tc, fo] =
98 c4d98278 Iustin Pop
  loadNode [name, tm, nm, fm, td, fd, tc, fo, defaultGroupID]
99 b3707354 Iustin Pop
loadNode [name, tm, nm, fm, td, fd, tc, fo, gu] = do
100 040afc35 Iustin Pop
  new_node <-
101 1a82215d Iustin Pop
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
102 b3707354 Iustin Pop
          return $ Node.create name 0 0 0 0 0 0 True gu
103 040afc35 Iustin Pop
      else do
104 040afc35 Iustin Pop
        vtm <- tryRead name tm
105 040afc35 Iustin Pop
        vnm <- tryRead name nm
106 040afc35 Iustin Pop
        vfm <- tryRead name fm
107 040afc35 Iustin Pop
        vtd <- tryRead name td
108 040afc35 Iustin Pop
        vfd <- tryRead name fd
109 1a82215d Iustin Pop
        vtc <- tryRead name tc
110 b3707354 Iustin Pop
        return $ Node.create name vtm vnm vfm vtd vfd vtc False gu
111 040afc35 Iustin Pop
  return (name, new_node)
112 9f6dcdea Iustin Pop
loadNode s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
113 040afc35 Iustin Pop
114 9188aeef Iustin Pop
-- | Load an instance from a field list.
115 040afc35 Iustin Pop
loadInst :: (Monad m) =>
116 6ff78049 Iustin Pop
            NameAssoc -> [String] -> m (String, Instance.Instance)
117 17e7af2b Iustin Pop
loadInst ktn [name, mem, dsk, vcpus, status, pnode, snode, tags] = do
118 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
119 040afc35 Iustin Pop
  sidx <- (if null snode then return Node.noSecondary
120 040afc35 Iustin Pop
           else lookupNode ktn name snode)
121 040afc35 Iustin Pop
  vmem <- tryRead name mem
122 040afc35 Iustin Pop
  vdsk <- tryRead name dsk
123 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
124 040afc35 Iustin Pop
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
125 040afc35 Iustin Pop
           " has same primary and secondary node - " ++ pnode
126 17e7af2b Iustin Pop
  let vtags = sepSplit ',' tags
127 17e7af2b Iustin Pop
      newinst = Instance.create name vmem vdsk vvcpus status vtags pidx sidx
128 040afc35 Iustin Pop
  return (name, newinst)
129 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
130 040afc35 Iustin Pop
131 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
132 9188aeef Iustin Pop
--
133 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
134 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
135 9188aeef Iustin Pop
-- a supplied conversion function.
136 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
137 f5197d89 Iustin Pop
               [String] -> ([String] -> m (String, a))
138 99b63608 Iustin Pop
            -> m (NameAssoc, Container.Container a)
139 f5197d89 Iustin Pop
loadTabular lines_data convert_fn = do
140 f5197d89 Iustin Pop
  let rows = map (sepSplit '|') lines_data
141 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
142 497e30a1 Iustin Pop
  return $ assignIndices kerows
143 040afc35 Iustin Pop
144 dadfc261 Iustin Pop
-- | Load the cluser data from disk.
145 dadfc261 Iustin Pop
readData :: String -- ^ Path to the text file
146 dadfc261 Iustin Pop
         -> IO String
147 dadfc261 Iustin Pop
readData = readFile
148 dadfc261 Iustin Pop
149 16c2369c Iustin Pop
-- | Builds the cluster data from text input.
150 dadfc261 Iustin Pop
parseData :: String -- ^ Text data
151 99b63608 Iustin Pop
          -> Result (Node.List, Instance.List, [String])
152 dadfc261 Iustin Pop
parseData fdata = do
153 16c2369c Iustin Pop
  let flines = lines fdata
154 16c2369c Iustin Pop
      (nlines, ilines) = break null flines
155 dadfc261 Iustin Pop
  ifixed <- case ilines of
156 dadfc261 Iustin Pop
    [] -> Bad "Invalid format of the input file (no instance data)"
157 dadfc261 Iustin Pop
    _:xs -> Ok xs
158 dadfc261 Iustin Pop
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
159 dadfc261 Iustin Pop
  (ktn, nl) <- loadTabular nlines loadNode
160 dadfc261 Iustin Pop
  {- instance file: name mem disk status pnode snode -}
161 dadfc261 Iustin Pop
  (_, il) <- loadTabular ifixed (loadInst ktn)
162 dadfc261 Iustin Pop
  return (nl, il, [])
163 dadfc261 Iustin Pop
164 dadfc261 Iustin Pop
-- | Top level function for data loading
165 dadfc261 Iustin Pop
loadData :: String -- ^ Path to the text file
166 99b63608 Iustin Pop
         -> IO (Result (Node.List, Instance.List, [String]))
167 dadfc261 Iustin Pop
loadData afile = readData afile >>= return . parseData