Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ e19ee6e4

History | View | Annotate | Download (8.3 kB)

1 a0090487 Agata Murawska
{-# LANGUAGE TemplateHaskell #-}
2 a0090487 Agata Murawska
3 6583e677 Iustin Pop
{-| Implementation of the Ganeti LUXI interface.
4 6583e677 Iustin Pop
5 6583e677 Iustin Pop
-}
6 6583e677 Iustin Pop
7 6583e677 Iustin Pop
{-
8 6583e677 Iustin Pop
9 e8230242 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
10 6583e677 Iustin Pop
11 6583e677 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 6583e677 Iustin Pop
it under the terms of the GNU General Public License as published by
13 6583e677 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 6583e677 Iustin Pop
(at your option) any later version.
15 6583e677 Iustin Pop
16 6583e677 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 6583e677 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 6583e677 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 6583e677 Iustin Pop
General Public License for more details.
20 6583e677 Iustin Pop
21 6583e677 Iustin Pop
You should have received a copy of the GNU General Public License
22 6583e677 Iustin Pop
along with this program; if not, write to the Free Software
23 6583e677 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 6583e677 Iustin Pop
02110-1301, USA.
25 6583e677 Iustin Pop
26 6583e677 Iustin Pop
-}
27 6583e677 Iustin Pop
28 6583e677 Iustin Pop
module Ganeti.Luxi
29 6583e677 Iustin Pop
    ( LuxiOp(..)
30 6583e677 Iustin Pop
    , Client
31 6583e677 Iustin Pop
    , getClient
32 6583e677 Iustin Pop
    , closeClient
33 6583e677 Iustin Pop
    , callMethod
34 9a2ff880 Iustin Pop
    , submitManyJobs
35 9a2ff880 Iustin Pop
    , queryJobsStatus
36 6583e677 Iustin Pop
    ) where
37 6583e677 Iustin Pop
38 6583e677 Iustin Pop
import Data.IORef
39 6583e677 Iustin Pop
import Control.Monad
40 0903280b Iustin Pop
import Text.JSON (encodeStrict, decodeStrict)
41 6583e677 Iustin Pop
import qualified Text.JSON as J
42 6583e677 Iustin Pop
import Text.JSON.Types
43 6583e677 Iustin Pop
import System.Timeout
44 6583e677 Iustin Pop
import qualified Network.Socket as S
45 6583e677 Iustin Pop
46 6583e677 Iustin Pop
import Ganeti.HTools.Utils
47 6583e677 Iustin Pop
import Ganeti.HTools.Types
48 6583e677 Iustin Pop
49 9a2ff880 Iustin Pop
import Ganeti.Jobs (JobStatus)
50 683b1ca7 Iustin Pop
import Ganeti.OpCodes (OpCode)
51 a0090487 Agata Murawska
import Ganeti.THH
52 9a2ff880 Iustin Pop
53 6583e677 Iustin Pop
-- * Utility functions
54 6583e677 Iustin Pop
55 6583e677 Iustin Pop
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
56 6583e677 Iustin Pop
withTimeout :: Int -> String -> IO a -> IO a
57 6583e677 Iustin Pop
withTimeout secs descr action = do
58 6583e677 Iustin Pop
    result <- timeout (secs * 1000000) action
59 6583e677 Iustin Pop
    (case result of
60 6583e677 Iustin Pop
       Nothing -> fail $ "Timeout in " ++ descr
61 6583e677 Iustin Pop
       Just v -> return v)
62 6583e677 Iustin Pop
63 6583e677 Iustin Pop
-- * Generic protocol functionality
64 6583e677 Iustin Pop
65 a0090487 Agata Murawska
-- | Currently supported Luxi operations and JSON serialization.
66 a0090487 Agata Murawska
$(genLuxiOp "LuxiOp"
67 a0090487 Agata Murawska
    [ ("QueryNodes",
68 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
69 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
70 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
71 a0090487 Agata Murawska
       ],
72 a0090487 Agata Murawska
       [| J.showJSON |])
73 a0090487 Agata Murawska
    , ("QueryGroups",
74 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
75 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
76 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
77 a0090487 Agata Murawska
       ],
78 a0090487 Agata Murawska
       [| J.showJSON |])
79 a0090487 Agata Murawska
    , ("QueryInstances",
80 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
81 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
82 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
83 a0090487 Agata Murawska
       ],
84 a0090487 Agata Murawska
       [| J.showJSON |])
85 a0090487 Agata Murawska
    , ("QueryJobs",
86 a0090487 Agata Murawska
       [ ("ids",    [t| [Int]    |], [| map show |])
87 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
88 a0090487 Agata Murawska
       ],
89 a0090487 Agata Murawska
       [| J.showJSON |])
90 a0090487 Agata Murawska
    , ("QueryExports",
91 a0090487 Agata Murawska
       [ ("nodes", [t| [String] |], [| id |])
92 a0090487 Agata Murawska
       , ("lock",  [t| Bool     |], [| id |])
93 a0090487 Agata Murawska
       ],
94 a0090487 Agata Murawska
       [| J.showJSON |])
95 a0090487 Agata Murawska
    , ("QueryConfigValues",
96 a0090487 Agata Murawska
       [ ("fields", [t| [String] |], [| id |]) ],
97 a0090487 Agata Murawska
       [| J.showJSON |])
98 a0090487 Agata Murawska
    , ("QueryClusterInfo",
99 a0090487 Agata Murawska
       [],
100 a0090487 Agata Murawska
       [| J.showJSON |])
101 a0090487 Agata Murawska
    , ("QueryTags",
102 a0090487 Agata Murawska
       [ ("kind", [t| String |], [| id |])
103 a0090487 Agata Murawska
       , ("name", [t| String |], [| id |])
104 a0090487 Agata Murawska
       ],
105 a0090487 Agata Murawska
       [| J.showJSON |])
106 a0090487 Agata Murawska
    , ("SubmitJob",
107 a0090487 Agata Murawska
       [ ("job", [t| [OpCode] |], [| id |]) ],
108 a0090487 Agata Murawska
       [| J.showJSON |])
109 a0090487 Agata Murawska
    , ("SubmitManyJobs",
110 a0090487 Agata Murawska
       [ ("ops", [t| [[OpCode]] |], [| id |]) ],
111 a0090487 Agata Murawska
       [| J.showJSON |])
112 a0090487 Agata Murawska
    , ("WaitForJobChange",
113 a0090487 Agata Murawska
       [ ("job",      [t| Int     |], [| J.showJSON |])
114 a0090487 Agata Murawska
       , ("fields",   [t| [String]|], [| J.showJSON |])
115 a0090487 Agata Murawska
       , ("prev_job", [t| JSValue |], [| J.showJSON |])
116 a0090487 Agata Murawska
       , ("prev_log", [t| JSValue |], [| J.showJSON |])
117 a0090487 Agata Murawska
       , ("tmout",    [t| Int     |], [| J.showJSON |])
118 a0090487 Agata Murawska
       ],
119 a0090487 Agata Murawska
       [| \(j, f, pj, pl, t) -> JSArray [j, f, pj, pl, t] |])
120 a0090487 Agata Murawska
    , ("ArchiveJob",
121 a0090487 Agata Murawska
       [ ("job", [t| Int |], [| show |]) ],
122 a0090487 Agata Murawska
       [| J.showJSON |])
123 a0090487 Agata Murawska
    , ("AutoArchiveJobs",
124 a0090487 Agata Murawska
       [ ("age",   [t| Int |], [| id |])
125 a0090487 Agata Murawska
       , ("tmout", [t| Int |], [| id |])
126 a0090487 Agata Murawska
       ],
127 a0090487 Agata Murawska
       [| J.showJSON |])
128 a0090487 Agata Murawska
    , ("CancelJob",
129 a0090487 Agata Murawska
       [("job", [t| Int |], [| show |]) ],
130 a0090487 Agata Murawska
       [| J.showJSON |])
131 a0090487 Agata Murawska
    , ("SetDrainFlag",
132 a0090487 Agata Murawska
       [ ("flag", [t| Bool |], [| id |]) ],
133 a0090487 Agata Murawska
       [| J.showJSON |])
134 a0090487 Agata Murawska
    , ("SetWatcherPause",
135 a0090487 Agata Murawska
       [ ("duration", [t| Double |], [| \x -> [x] |]) ],
136 a0090487 Agata Murawska
       [| J.showJSON |])
137 a0090487 Agata Murawska
  ])
138 6583e677 Iustin Pop
139 6583e677 Iustin Pop
-- | The serialisation of LuxiOps into strings in messages.
140 a0090487 Agata Murawska
$(genStrOfOp ''LuxiOp "strOfOp")
141 6583e677 Iustin Pop
142 6583e677 Iustin Pop
-- | The end-of-message separator.
143 6583e677 Iustin Pop
eOM :: Char
144 6583e677 Iustin Pop
eOM = '\3'
145 6583e677 Iustin Pop
146 6583e677 Iustin Pop
-- | Valid keys in the requests and responses.
147 6583e677 Iustin Pop
data MsgKeys = Method
148 6583e677 Iustin Pop
             | Args
149 6583e677 Iustin Pop
             | Success
150 6583e677 Iustin Pop
             | Result
151 6583e677 Iustin Pop
152 6583e677 Iustin Pop
-- | The serialisation of MsgKeys into strings in messages.
153 a0090487 Agata Murawska
$(genStrOfKey ''MsgKeys "strOfKey")
154 6583e677 Iustin Pop
155 6583e677 Iustin Pop
-- | Luxi client encapsulation.
156 6583e677 Iustin Pop
data Client = Client { socket :: S.Socket   -- ^ The socket of the client
157 6583e677 Iustin Pop
                     , rbuf :: IORef String -- ^ Already received buffer
158 6583e677 Iustin Pop
                     }
159 6583e677 Iustin Pop
160 6583e677 Iustin Pop
-- | Connects to the master daemon and returns a luxi Client.
161 6583e677 Iustin Pop
getClient :: String -> IO Client
162 6583e677 Iustin Pop
getClient path = do
163 6583e677 Iustin Pop
    s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
164 6583e677 Iustin Pop
    withTimeout connTimeout "creating luxi connection" $
165 6583e677 Iustin Pop
                S.connect s (S.SockAddrUnix path)
166 6583e677 Iustin Pop
    rf <- newIORef ""
167 6583e677 Iustin Pop
    return Client { socket=s, rbuf=rf}
168 6583e677 Iustin Pop
169 6583e677 Iustin Pop
-- | Closes the client socket.
170 6583e677 Iustin Pop
closeClient :: Client -> IO ()
171 6583e677 Iustin Pop
closeClient = S.sClose . socket
172 6583e677 Iustin Pop
173 6583e677 Iustin Pop
-- | Sends a message over a luxi transport.
174 6583e677 Iustin Pop
sendMsg :: Client -> String -> IO ()
175 6583e677 Iustin Pop
sendMsg s buf =
176 6583e677 Iustin Pop
    let _send obuf = do
177 6583e677 Iustin Pop
          sbytes <- withTimeout queryTimeout
178 6583e677 Iustin Pop
                    "sending luxi message" $
179 6583e677 Iustin Pop
                    S.send (socket s) obuf
180 3a3c1eb4 Iustin Pop
          unless (sbytes == length obuf) $ _send (drop sbytes obuf)
181 6583e677 Iustin Pop
    in _send (buf ++ [eOM])
182 6583e677 Iustin Pop
183 6583e677 Iustin Pop
-- | Waits for a message over a luxi transport.
184 6583e677 Iustin Pop
recvMsg :: Client -> IO String
185 6583e677 Iustin Pop
recvMsg s = do
186 6583e677 Iustin Pop
  let _recv obuf = do
187 6583e677 Iustin Pop
              nbuf <- withTimeout queryTimeout "reading luxi response" $
188 6583e677 Iustin Pop
                      S.recv (socket s) 4096
189 95f490de Iustin Pop
              let (msg, remaining) = break (eOM ==) nbuf
190 6583e677 Iustin Pop
              (if null remaining
191 95f490de Iustin Pop
               then _recv (obuf ++ msg)
192 95f490de Iustin Pop
               else return (obuf ++ msg, tail remaining))
193 6583e677 Iustin Pop
  cbuf <- readIORef $ rbuf s
194 95f490de Iustin Pop
  let (imsg, ibuf) = break (eOM ==) cbuf
195 95f490de Iustin Pop
  (msg, nbuf) <-
196 95f490de Iustin Pop
      (if null ibuf      -- if old buffer didn't contain a full message
197 95f490de Iustin Pop
       then _recv cbuf   -- then we read from network
198 95f490de Iustin Pop
       else return (imsg, tail ibuf)) -- else we return data from our buffer
199 6583e677 Iustin Pop
  writeIORef (rbuf s) nbuf
200 6583e677 Iustin Pop
  return msg
201 6583e677 Iustin Pop
202 6583e677 Iustin Pop
-- | Serialize a request to String.
203 6583e677 Iustin Pop
buildCall :: LuxiOp  -- ^ The method
204 6583e677 Iustin Pop
          -> String  -- ^ The serialized form
205 683b1ca7 Iustin Pop
buildCall lo =
206 683b1ca7 Iustin Pop
    let ja = [ (strOfKey Method, JSString $ toJSString $ strOfOp lo::JSValue)
207 683b1ca7 Iustin Pop
             , (strOfKey Args, opToArgs lo::JSValue)
208 6583e677 Iustin Pop
             ]
209 6583e677 Iustin Pop
        jo = toJSObject ja
210 6583e677 Iustin Pop
    in encodeStrict jo
211 6583e677 Iustin Pop
212 6583e677 Iustin Pop
-- | Check that luxi responses contain the required keys and that the
213 6583e677 Iustin Pop
-- call was successful.
214 6583e677 Iustin Pop
validateResult :: String -> Result JSValue
215 6583e677 Iustin Pop
validateResult s = do
216 c96d44df Iustin Pop
  oarr <- fromJResult "Parsing LUXI response"
217 c96d44df Iustin Pop
          (decodeStrict s)::Result (JSObject JSValue)
218 262f3e6c Iustin Pop
  let arr = J.fromJSObject oarr
219 e8230242 Iustin Pop
  status <- fromObj arr (strOfKey Success)::Result Bool
220 6583e677 Iustin Pop
  let rkey = strOfKey Result
221 6583e677 Iustin Pop
  (if status
222 e8230242 Iustin Pop
   then fromObj arr rkey
223 e8230242 Iustin Pop
   else fromObj arr rkey >>= fail)
224 6583e677 Iustin Pop
225 6583e677 Iustin Pop
-- | Generic luxi method call.
226 683b1ca7 Iustin Pop
callMethod :: LuxiOp -> Client -> IO (Result JSValue)
227 683b1ca7 Iustin Pop
callMethod method s = do
228 683b1ca7 Iustin Pop
  sendMsg s $ buildCall method
229 6583e677 Iustin Pop
  result <- recvMsg s
230 6583e677 Iustin Pop
  let rval = validateResult result
231 6583e677 Iustin Pop
  return rval
232 9a2ff880 Iustin Pop
233 9a2ff880 Iustin Pop
-- | Specialized submitManyJobs call.
234 683b1ca7 Iustin Pop
submitManyJobs :: Client -> [[OpCode]] -> IO (Result [String])
235 9a2ff880 Iustin Pop
submitManyJobs s jobs = do
236 683b1ca7 Iustin Pop
  rval <- callMethod (SubmitManyJobs jobs) s
237 9a2ff880 Iustin Pop
  -- map each result (status, payload) pair into a nice Result ADT
238 9a2ff880 Iustin Pop
  return $ case rval of
239 9a2ff880 Iustin Pop
             Bad x -> Bad x
240 9a2ff880 Iustin Pop
             Ok (JSArray r) ->
241 9a2ff880 Iustin Pop
                 mapM (\v -> case v of
242 9a2ff880 Iustin Pop
                               JSArray [JSBool True, JSString x] ->
243 9a2ff880 Iustin Pop
                                   Ok (fromJSString x)
244 9a2ff880 Iustin Pop
                               JSArray [JSBool False, JSString x] ->
245 9a2ff880 Iustin Pop
                                   Bad (fromJSString x)
246 9a2ff880 Iustin Pop
                               _ -> Bad "Unknown result from the master daemon"
247 9a2ff880 Iustin Pop
                      ) r
248 9a2ff880 Iustin Pop
             x -> Bad ("Cannot parse response from Ganeti: " ++ show x)
249 9a2ff880 Iustin Pop
250 9a2ff880 Iustin Pop
-- | Custom queryJobs call.
251 9a2ff880 Iustin Pop
queryJobsStatus :: Client -> [String] -> IO (Result [JobStatus])
252 9a2ff880 Iustin Pop
queryJobsStatus s jids = do
253 683b1ca7 Iustin Pop
  rval <- callMethod (QueryJobs (map read jids) ["status"]) s
254 9a2ff880 Iustin Pop
  return $ case rval of
255 9a2ff880 Iustin Pop
             Bad x -> Bad x
256 9a2ff880 Iustin Pop
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
257 9a2ff880 Iustin Pop
                       J.Ok vals -> if any null vals
258 9a2ff880 Iustin Pop
                                    then Bad "Missing job status field"
259 9a2ff880 Iustin Pop
                                    else Ok (map head vals)
260 9a2ff880 Iustin Pop
                       J.Error x -> Bad x