Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Text.hs @ f25e5aac

History | View | Annotate | Download (4 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 e2fa2baf Iustin Pop
Copyright (C) 2009 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 b2278348 Iustin Pop
    ) where
33 040afc35 Iustin Pop
34 040afc35 Iustin Pop
import Control.Monad
35 040afc35 Iustin Pop
36 040afc35 Iustin Pop
import Ganeti.HTools.Utils
37 040afc35 Iustin Pop
import Ganeti.HTools.Loader
38 e4c5beaf Iustin Pop
import Ganeti.HTools.Types
39 040afc35 Iustin Pop
import qualified Ganeti.HTools.Node as Node
40 040afc35 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
41 040afc35 Iustin Pop
42 78694255 Iustin Pop
-- | Parse results from readsPrec
43 78694255 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
44 78694255 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
45 78694255 Iustin Pop
parseChoices name s ((_, e):[]) =
46 78694255 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
47 78694255 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
48 78694255 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
49 78694255 Iustin Pop
50 9188aeef Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
51 040afc35 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
52 9f6dcdea Iustin Pop
tryRead name s = parseChoices name s $ reads s
53 040afc35 Iustin Pop
54 9188aeef Iustin Pop
-- | Load a node from a field list.
55 040afc35 Iustin Pop
loadNode :: (Monad m) => [String] -> m (String, Node.Node)
56 1a82215d Iustin Pop
loadNode (name:tm:nm:fm:td:fd:tc:fo:[]) = do
57 040afc35 Iustin Pop
  new_node <-
58 1a82215d Iustin Pop
      if any (== "?") [tm,nm,fm,td,fd,tc] || fo == "Y" then
59 1a82215d Iustin Pop
          return $ Node.create name 0 0 0 0 0 0 True
60 040afc35 Iustin Pop
      else do
61 040afc35 Iustin Pop
        vtm <- tryRead name tm
62 040afc35 Iustin Pop
        vnm <- tryRead name nm
63 040afc35 Iustin Pop
        vfm <- tryRead name fm
64 040afc35 Iustin Pop
        vtd <- tryRead name td
65 040afc35 Iustin Pop
        vfd <- tryRead name fd
66 1a82215d Iustin Pop
        vtc <- tryRead name tc
67 1a82215d Iustin Pop
        return $ Node.create name vtm vnm vfm vtd vfd vtc False
68 040afc35 Iustin Pop
  return (name, new_node)
69 9f6dcdea Iustin Pop
loadNode s = fail $ "Invalid/incomplete node data: '" ++ show s ++ "'"
70 040afc35 Iustin Pop
71 9188aeef Iustin Pop
-- | Load an instance from a field list.
72 040afc35 Iustin Pop
loadInst :: (Monad m) =>
73 608efcce Iustin Pop
            [(String, Ndx)] -> [String] -> m (String, Instance.Instance)
74 d752eb39 Iustin Pop
loadInst ktn (name:mem:dsk:vcpus:status:pnode:snode:[]) = do
75 040afc35 Iustin Pop
  pidx <- lookupNode ktn name pnode
76 040afc35 Iustin Pop
  sidx <- (if null snode then return Node.noSecondary
77 040afc35 Iustin Pop
           else lookupNode ktn name snode)
78 040afc35 Iustin Pop
  vmem <- tryRead name mem
79 040afc35 Iustin Pop
  vdsk <- tryRead name dsk
80 d752eb39 Iustin Pop
  vvcpus <- tryRead name vcpus
81 040afc35 Iustin Pop
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
82 040afc35 Iustin Pop
           " has same primary and secondary node - " ++ pnode
83 d752eb39 Iustin Pop
  let newinst = Instance.create name vmem vdsk vvcpus status pidx sidx
84 040afc35 Iustin Pop
  return (name, newinst)
85 9f6dcdea Iustin Pop
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ show s ++ "'"
86 040afc35 Iustin Pop
87 9188aeef Iustin Pop
-- | Convert newline and delimiter-separated text.
88 9188aeef Iustin Pop
--
89 9188aeef Iustin Pop
-- This function converts a text in tabular format as generated by
90 9188aeef Iustin Pop
-- @gnt-instance list@ and @gnt-node list@ to a list of objects using
91 9188aeef Iustin Pop
-- a supplied conversion function.
92 497e30a1 Iustin Pop
loadTabular :: (Monad m, Element a) =>
93 497e30a1 Iustin Pop
               String -> ([String] -> m (String, a))
94 497e30a1 Iustin Pop
            -> m ([(String, Int)], [(Int, a)])
95 497e30a1 Iustin Pop
loadTabular text_data convert_fn = do
96 040afc35 Iustin Pop
  let lines_data = lines text_data
97 040afc35 Iustin Pop
      rows = map (sepSplit '|') lines_data
98 040afc35 Iustin Pop
  kerows <- mapM convert_fn rows
99 497e30a1 Iustin Pop
  return $ assignIndices kerows
100 040afc35 Iustin Pop
101 9188aeef Iustin Pop
-- | Builds the cluster data from node\/instance files.
102 040afc35 Iustin Pop
loadData :: String -- ^ Node data in string format
103 040afc35 Iustin Pop
         -> String -- ^ Instance data in string format
104 e3a684c5 Iustin Pop
         -> IO (Result (Node.AssocList, Instance.AssocList))
105 040afc35 Iustin Pop
loadData nfile ifile = do -- IO monad
106 040afc35 Iustin Pop
  ndata <- readFile nfile
107 040afc35 Iustin Pop
  idata <- readFile ifile
108 040afc35 Iustin Pop
  return $ do
109 040afc35 Iustin Pop
    {- node file: name t_mem n_mem f_mem t_disk f_disk -}
110 497e30a1 Iustin Pop
    (ktn, nl) <- loadTabular ndata loadNode
111 040afc35 Iustin Pop
    {- instance file: name mem disk status pnode snode -}
112 e3a684c5 Iustin Pop
    (_, il) <- loadTabular idata (loadInst ktn)
113 e3a684c5 Iustin Pop
    return (nl, il)