Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Luxi.hs @ 7b6e99b3

History | View | Annotate | Download (7.1 kB)

1 6583e677 Iustin Pop
{-| Implementation of the LUXI loader.
2 53ec9022 Iustin Pop
3 53ec9022 Iustin Pop
-}
4 53ec9022 Iustin Pop
5 53ec9022 Iustin Pop
{-
6 53ec9022 Iustin Pop
7 9d775204 Iustin Pop
Copyright (C) 2009, 2010 Google Inc.
8 53ec9022 Iustin Pop
9 53ec9022 Iustin Pop
This program is free software; you can redistribute it and/or modify
10 53ec9022 Iustin Pop
it under the terms of the GNU General Public License as published by
11 53ec9022 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 53ec9022 Iustin Pop
(at your option) any later version.
13 53ec9022 Iustin Pop
14 53ec9022 Iustin Pop
This program is distributed in the hope that it will be useful, but
15 53ec9022 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 53ec9022 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 53ec9022 Iustin Pop
General Public License for more details.
18 53ec9022 Iustin Pop
19 53ec9022 Iustin Pop
You should have received a copy of the GNU General Public License
20 53ec9022 Iustin Pop
along with this program; if not, write to the Free Software
21 53ec9022 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 53ec9022 Iustin Pop
02110-1301, USA.
23 53ec9022 Iustin Pop
24 53ec9022 Iustin Pop
-}
25 53ec9022 Iustin Pop
26 53ec9022 Iustin Pop
module Ganeti.HTools.Luxi
27 53ec9022 Iustin Pop
    (
28 53ec9022 Iustin Pop
      loadData
29 b3f0710c Iustin Pop
    , parseData
30 53ec9022 Iustin Pop
    ) where
31 53ec9022 Iustin Pop
32 53ec9022 Iustin Pop
import qualified Control.Exception as E
33 53ec9022 Iustin Pop
import Text.JSON.Types
34 53ec9022 Iustin Pop
35 6583e677 Iustin Pop
import qualified Ganeti.Luxi as L
36 53ec9022 Iustin Pop
import Ganeti.HTools.Loader
37 53ec9022 Iustin Pop
import Ganeti.HTools.Types
38 a679e9dc Iustin Pop
import qualified Ganeti.HTools.Group as Group
39 53ec9022 Iustin Pop
import qualified Ganeti.HTools.Node as Node
40 53ec9022 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
41 f5ed8632 Iustin Pop
import Ganeti.HTools.Utils (fromJVal, annotateResult, tryFromObj, asJSObject)
42 53ec9022 Iustin Pop
43 53ec9022 Iustin Pop
-- * Utility functions
44 53ec9022 Iustin Pop
45 53ec9022 Iustin Pop
-- | Ensure a given JSValue is actually a JSArray.
46 53ec9022 Iustin Pop
toArray :: (Monad m) => JSValue -> m [JSValue]
47 53ec9022 Iustin Pop
toArray v =
48 53ec9022 Iustin Pop
    case v of
49 53ec9022 Iustin Pop
      JSArray arr -> return arr
50 53ec9022 Iustin Pop
      o -> fail ("Invalid input, expected array but got " ++ show o)
51 53ec9022 Iustin Pop
52 53ec9022 Iustin Pop
-- * Data querying functionality
53 53ec9022 Iustin Pop
54 53ec9022 Iustin Pop
-- | The input data for node query.
55 683b1ca7 Iustin Pop
queryNodesMsg :: L.LuxiOp
56 53ec9022 Iustin Pop
queryNodesMsg =
57 683b1ca7 Iustin Pop
  L.QueryNodes [] ["name", "mtotal", "mnode", "mfree", "dtotal", "dfree",
58 f5ed8632 Iustin Pop
                   "ctotal", "offline", "drained", "vm_capable",
59 f5ed8632 Iustin Pop
                   "group.uuid"] False
60 53ec9022 Iustin Pop
61 53ec9022 Iustin Pop
-- | The input data for instance query.
62 683b1ca7 Iustin Pop
queryInstancesMsg :: L.LuxiOp
63 53ec9022 Iustin Pop
queryInstancesMsg =
64 683b1ca7 Iustin Pop
  L.QueryInstances [] ["name", "disk_usage", "be/memory", "be/vcpus",
65 683b1ca7 Iustin Pop
                       "status", "pnode", "snodes", "tags", "oper_ram"] False
66 53ec9022 Iustin Pop
67 a679e9dc Iustin Pop
-- | The input data for cluster query.
68 683b1ca7 Iustin Pop
queryClusterInfoMsg :: L.LuxiOp
69 683b1ca7 Iustin Pop
queryClusterInfoMsg = L.QueryClusterInfo
70 f89235f1 Iustin Pop
71 a679e9dc Iustin Pop
-- | The input data for node group query.
72 a679e9dc Iustin Pop
queryGroupsMsg :: L.LuxiOp
73 a679e9dc Iustin Pop
queryGroupsMsg =
74 c4c37257 Iustin Pop
  L.QueryGroups [] ["uuid", "name", "alloc_policy"] False
75 a679e9dc Iustin Pop
76 53ec9022 Iustin Pop
-- | Wraper over callMethod doing node query.
77 6583e677 Iustin Pop
queryNodes :: L.Client -> IO (Result JSValue)
78 683b1ca7 Iustin Pop
queryNodes = L.callMethod queryNodesMsg
79 53ec9022 Iustin Pop
80 53ec9022 Iustin Pop
-- | Wraper over callMethod doing instance query.
81 6583e677 Iustin Pop
queryInstances :: L.Client -> IO (Result JSValue)
82 683b1ca7 Iustin Pop
queryInstances = L.callMethod queryInstancesMsg
83 53ec9022 Iustin Pop
84 f89235f1 Iustin Pop
queryClusterInfo :: L.Client -> IO (Result JSValue)
85 683b1ca7 Iustin Pop
queryClusterInfo = L.callMethod queryClusterInfoMsg
86 f89235f1 Iustin Pop
87 a679e9dc Iustin Pop
-- | Wrapper over callMethod doing group query.
88 a679e9dc Iustin Pop
queryGroups :: L.Client -> IO (Result JSValue)
89 a679e9dc Iustin Pop
queryGroups = L.callMethod queryGroupsMsg
90 a679e9dc Iustin Pop
91 53ec9022 Iustin Pop
-- | Parse a instance list in JSON format.
92 53ec9022 Iustin Pop
getInstances :: NameAssoc
93 53ec9022 Iustin Pop
             -> JSValue
94 53ec9022 Iustin Pop
             -> Result [(String, Instance.Instance)]
95 53ec9022 Iustin Pop
getInstances ktn arr = toArray arr >>= mapM (parseInstance ktn)
96 53ec9022 Iustin Pop
97 53ec9022 Iustin Pop
-- | Construct an instance from a JSON object.
98 6ff78049 Iustin Pop
parseInstance :: NameAssoc
99 53ec9022 Iustin Pop
              -> JSValue
100 53ec9022 Iustin Pop
              -> Result (String, Instance.Instance)
101 27671a61 Iustin Pop
parseInstance ktn (JSArray [ name, disk, mem, vcpus
102 6402a260 Iustin Pop
                           , status, pnode, snodes, tags, oram ]) = do
103 117dc2d8 Iustin Pop
  xname <- annotateResult "Parsing new instance" (fromJVal name)
104 117dc2d8 Iustin Pop
  let convert v = annotateResult ("Instance '" ++ xname ++ "'") (fromJVal v)
105 117dc2d8 Iustin Pop
  xdisk <- convert disk
106 6402a260 Iustin Pop
  xmem <- (case oram of
107 6402a260 Iustin Pop
             JSRational _ _ -> convert oram
108 6402a260 Iustin Pop
             _ -> convert mem)
109 117dc2d8 Iustin Pop
  xvcpus <- convert vcpus
110 117dc2d8 Iustin Pop
  xpnode <- convert pnode >>= lookupNode ktn xname
111 117dc2d8 Iustin Pop
  xsnodes <- convert snodes::Result [JSString]
112 53ec9022 Iustin Pop
  snode <- (if null xsnodes then return Node.noSecondary
113 53ec9022 Iustin Pop
            else lookupNode ktn xname (fromJSString $ head xsnodes))
114 117dc2d8 Iustin Pop
  xrunning <- convert status
115 17e7af2b Iustin Pop
  xtags <- convert tags
116 17e7af2b Iustin Pop
  let inst = Instance.create xname xmem xdisk xvcpus
117 17e7af2b Iustin Pop
             xrunning xtags xpnode snode
118 53ec9022 Iustin Pop
  return (xname, inst)
119 53ec9022 Iustin Pop
120 53ec9022 Iustin Pop
parseInstance _ v = fail ("Invalid instance query result: " ++ show v)
121 53ec9022 Iustin Pop
122 53ec9022 Iustin Pop
-- | Parse a node list in JSON format.
123 10ef6b4e Iustin Pop
getNodes :: NameAssoc -> JSValue -> Result [(String, Node.Node)]
124 10ef6b4e Iustin Pop
getNodes ktg arr = toArray arr >>= mapM (parseNode ktg)
125 53ec9022 Iustin Pop
126 53ec9022 Iustin Pop
-- | Construct a node from a JSON object.
127 10ef6b4e Iustin Pop
parseNode :: NameAssoc -> JSValue -> Result (String, Node.Node)
128 10ef6b4e Iustin Pop
parseNode ktg (JSArray [ name, mtotal, mnode, mfree, dtotal, dfree
129 10ef6b4e Iustin Pop
                       , ctotal, offline, drained, vm_capable, g_uuid ])
130 53ec9022 Iustin Pop
    = do
131 117dc2d8 Iustin Pop
  xname <- annotateResult "Parsing new node" (fromJVal name)
132 117dc2d8 Iustin Pop
  let convert v = annotateResult ("Node '" ++ xname ++ "'") (fromJVal v)
133 117dc2d8 Iustin Pop
  xoffline <- convert offline
134 b45222ce Iustin Pop
  xdrained <- convert drained
135 9d775204 Iustin Pop
  xvm_capable <- convert vm_capable
136 10ef6b4e Iustin Pop
  xgdx   <- convert g_uuid >>= lookupGroup ktg xname
137 9d775204 Iustin Pop
  node <- (if xoffline || xdrained || not xvm_capable
138 10ef6b4e Iustin Pop
           then return $ Node.create xname 0 0 0 0 0 0 True xgdx
139 53ec9022 Iustin Pop
           else do
140 117dc2d8 Iustin Pop
             xmtotal  <- convert mtotal
141 117dc2d8 Iustin Pop
             xmnode   <- convert mnode
142 117dc2d8 Iustin Pop
             xmfree   <- convert mfree
143 117dc2d8 Iustin Pop
             xdtotal  <- convert dtotal
144 117dc2d8 Iustin Pop
             xdfree   <- convert dfree
145 117dc2d8 Iustin Pop
             xctotal  <- convert ctotal
146 53ec9022 Iustin Pop
             return $ Node.create xname xmtotal xmnode xmfree
147 10ef6b4e Iustin Pop
                    xdtotal xdfree xctotal False xgdx)
148 53ec9022 Iustin Pop
  return (xname, node)
149 53ec9022 Iustin Pop
150 10ef6b4e Iustin Pop
parseNode _ v = fail ("Invalid node query result: " ++ show v)
151 53ec9022 Iustin Pop
152 f89235f1 Iustin Pop
getClusterTags :: JSValue -> Result [String]
153 f89235f1 Iustin Pop
getClusterTags v = do
154 f89235f1 Iustin Pop
  let errmsg = "Parsing cluster info"
155 f89235f1 Iustin Pop
  obj <- annotateResult errmsg $ asJSObject v
156 5182e970 Iustin Pop
  tryFromObj errmsg (fromJSObject obj) "tags"
157 f89235f1 Iustin Pop
158 a679e9dc Iustin Pop
getGroups :: JSValue -> Result [(String, Group.Group)]
159 a679e9dc Iustin Pop
getGroups arr = toArray arr >>= mapM parseGroup
160 a679e9dc Iustin Pop
161 a679e9dc Iustin Pop
parseGroup :: JSValue -> Result (String, Group.Group)
162 c4c37257 Iustin Pop
parseGroup (JSArray [ uuid, name, apol ]) = do
163 a679e9dc Iustin Pop
  xname <- annotateResult "Parsing new group" (fromJVal name)
164 a679e9dc Iustin Pop
  let convert v = annotateResult ("Node '" ++ xname ++ "'") (fromJVal v)
165 a679e9dc Iustin Pop
  xuuid <- convert uuid
166 c4c37257 Iustin Pop
  xapol <- convert apol
167 c4c37257 Iustin Pop
  return $ (xuuid, Group.create xname xuuid xapol)
168 a679e9dc Iustin Pop
169 a679e9dc Iustin Pop
parseGroup v = fail ("Invalid group query result: " ++ show v)
170 a679e9dc Iustin Pop
171 53ec9022 Iustin Pop
-- * Main loader functionality
172 53ec9022 Iustin Pop
173 53ec9022 Iustin Pop
-- | Builds the cluster data from an URL.
174 b3f0710c Iustin Pop
readData :: String -- ^ Unix socket to use as source
175 a679e9dc Iustin Pop
         -> IO (Result JSValue, Result JSValue, Result JSValue, Result JSValue)
176 b3f0710c Iustin Pop
readData master =
177 53ec9022 Iustin Pop
  E.bracket
178 6583e677 Iustin Pop
       (L.getClient master)
179 6583e677 Iustin Pop
       L.closeClient
180 53ec9022 Iustin Pop
       (\s -> do
181 53ec9022 Iustin Pop
          nodes <- queryNodes s
182 53ec9022 Iustin Pop
          instances <- queryInstances s
183 f89235f1 Iustin Pop
          cinfo <- queryClusterInfo s
184 a679e9dc Iustin Pop
          groups <- queryGroups s
185 a679e9dc Iustin Pop
          return (groups, nodes, instances, cinfo)
186 53ec9022 Iustin Pop
       )
187 b3f0710c Iustin Pop
188 a679e9dc Iustin Pop
parseData :: (Result JSValue, Result JSValue, Result JSValue, Result JSValue)
189 a679e9dc Iustin Pop
          -> Result (Group.List, Node.List, Instance.List, [String])
190 a679e9dc Iustin Pop
parseData (groups, nodes, instances, cinfo) = do
191 a679e9dc Iustin Pop
  group_data <- groups >>= getGroups
192 10ef6b4e Iustin Pop
  let (group_names, group_idx) = assignIndices group_data
193 10ef6b4e Iustin Pop
  node_data <- nodes >>= getNodes group_names
194 b3f0710c Iustin Pop
  let (node_names, node_idx) = assignIndices node_data
195 b3f0710c Iustin Pop
  inst_data <- instances >>= getInstances node_names
196 b3f0710c Iustin Pop
  let (_, inst_idx) = assignIndices inst_data
197 b3f0710c Iustin Pop
  ctags <- cinfo >>= getClusterTags
198 a679e9dc Iustin Pop
  return (group_idx, node_idx, inst_idx, ctags)
199 b3f0710c Iustin Pop
200 b3f0710c Iustin Pop
-- | Top level function for data loading
201 b3f0710c Iustin Pop
loadData :: String -- ^ Unix socket to use as source
202 a679e9dc Iustin Pop
            -> IO (Result (Group.List, Node.List, Instance.List, [String]))
203 b3f0710c Iustin Pop
loadData master = readData master >>= return . parseData