Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Text.hs @ 306cccd5

History | View | Annotate | Download (5.4 kB)

1
{-| Parsing data from text-files
2

    
3
This module holds the code for loading the cluster state from text
4
files, as produced by gnt-node and gnt-instance list.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.HTools.Text
30
    (
31
      loadData
32
    , loadInst
33
    , loadNode
34
    , serializeInstances
35
    , serializeNode
36
    , serializeNodes
37
    , serializeCluster
38
    ) where
39

    
40
import Control.Monad
41
import Data.List
42

    
43
import Text.Printf (printf)
44

    
45
import Ganeti.HTools.Utils
46
import Ganeti.HTools.Loader
47
import Ganeti.HTools.Types
48
import qualified Ganeti.HTools.Container as Container
49
import qualified Ganeti.HTools.Node as Node
50
import qualified Ganeti.HTools.Instance as Instance
51

    
52
-- | Serialize a single node
53
serializeNode :: Node.Node -> String
54
serializeNode node =
55
    printf "%s|%.0f|%d|%d|%.0f|%d|%.0f|%c" (Node.name node)
56
               (Node.tMem node) (Node.nMem node) (Node.fMem node)
57
               (Node.tDsk node) (Node.fDsk node) (Node.tCpu node)
58
               (if Node.offline node then 'Y' else 'N')
59

    
60
-- | Generate node file data from node objects
61
serializeNodes :: Node.List -> String
62
serializeNodes = unlines . map serializeNode . Container.elems
63

    
64
-- | Serialize a single instance
65
serializeInstance :: Node.List -> Instance.Instance -> String
66
serializeInstance nl inst =
67
    let
68
        iname = Instance.name inst
69
        pnode = Container.nameOf nl (Instance.pNode inst)
70
        sidx = Instance.sNode inst
71
        snode = (if sidx == Node.noSecondary
72
                    then ""
73
                    else Container.nameOf nl sidx)
74
    in
75
      printf "%s|%d|%d|%d|%s|%s|%s|%s"
76
             iname (Instance.mem inst) (Instance.dsk inst)
77
             (Instance.vcpus inst) (Instance.runSt inst)
78
             pnode snode (intercalate "," (Instance.tags inst))
79

    
80
-- | Generate instance file data from instance objects
81
serializeInstances :: Node.List -> Instance.List -> String
82
serializeInstances nl =
83
    unlines . map (serializeInstance nl) . Container.elems
84

    
85
-- | Generate complete cluster data from node and instance lists
86
serializeCluster :: Node.List -> Instance.List -> String
87
serializeCluster nl il =
88
  let ndata = serializeNodes nl
89
      idata = serializeInstances nl il
90
  in ndata ++ ['\n'] ++ idata
91

    
92
-- | Load a node from a field list.
93
loadNode :: (Monad m) => [String] -> m (String, Node.Node)
94
loadNode [name, tm, nm, fm, td, fd, tc, fo] = do
95
  new_node <-
96
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
97
          return $ Node.create name 0 0 0 0 0 0 True
98
      else do
99
        vtm <- tryRead name tm
100
        vnm <- tryRead name nm
101
        vfm <- tryRead name fm
102
        vtd <- tryRead name td
103
        vfd <- tryRead name fd
104
        vtc <- tryRead name tc
105
        return $ Node.create name vtm vnm vfm vtd vfd vtc False
106
  return (name, new_node)
107
loadNode s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
108

    
109
-- | Load an instance from a field list.
110
loadInst :: (Monad m) =>
111
            [(String, Ndx)] -> [String] -> m (String, Instance.Instance)
112
loadInst ktn [name, mem, dsk, vcpus, status, pnode, snode, tags] = do
113
  pidx <- lookupNode ktn name pnode
114
  sidx <- (if null snode then return Node.noSecondary
115
           else lookupNode ktn name snode)
116
  vmem <- tryRead name mem
117
  vdsk <- tryRead name dsk
118
  vvcpus <- tryRead name vcpus
119
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
120
           " has same primary and secondary node - " ++ pnode
121
  let vtags = sepSplit ',' tags
122
      newinst = Instance.create name vmem vdsk vvcpus status vtags pidx sidx
123
  return (name, newinst)
124
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
125

    
126
-- | Convert newline and delimiter-separated text.
127
--
128
-- This function converts a text in tabular format as generated by
129
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
130
-- a supplied conversion function.
131
loadTabular :: (Monad m, Element a) =>
132
               [String] -> ([String] -> m (String, a))
133
            -> m ([(String, Int)], [(Int, a)])
134
loadTabular lines_data convert_fn = do
135
  let rows = map (sepSplit '|') lines_data
136
  kerows <- mapM convert_fn rows
137
  return $ assignIndices kerows
138

    
139
-- | Builds the cluster data from text input.
140
loadData :: String -- ^ Path to the text file
141
         -> IO (Result (Node.AssocList, Instance.AssocList, [String]))
142
loadData afile = do -- IO monad
143
  fdata <- readFile afile
144
  let flines = lines fdata
145
      (nlines, ilines) = break null flines
146
  return $ do
147
    ifixed <- case ilines of
148
                [] -> Bad "Invalid format of the input file (no instance data)"
149
                _:xs -> Ok xs
150
    {- node file: name t_mem n_mem f_mem t_disk f_disk -}
151
    (ktn, nl) <- loadTabular nlines loadNode
152
    {- instance file: name mem disk status pnode snode -}
153
    (_, il) <- loadTabular ifixed (loadInst ktn)
154
    return (nl, il, [])