Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ b20cbf06

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 92678b3c Iustin Pop
    , QrViaLuxi(..)
31 6583e677 Iustin Pop
    , Client
32 6583e677 Iustin Pop
    , getClient
33 6583e677 Iustin Pop
    , closeClient
34 6583e677 Iustin Pop
    , callMethod
35 9a2ff880 Iustin Pop
    , submitManyJobs
36 9a2ff880 Iustin Pop
    , queryJobsStatus
37 6583e677 Iustin Pop
    ) where
38 6583e677 Iustin Pop
39 6583e677 Iustin Pop
import Data.IORef
40 6583e677 Iustin Pop
import Control.Monad
41 0903280b Iustin Pop
import Text.JSON (encodeStrict, decodeStrict)
42 6583e677 Iustin Pop
import qualified Text.JSON as J
43 6583e677 Iustin Pop
import Text.JSON.Types
44 6583e677 Iustin Pop
import System.Timeout
45 6583e677 Iustin Pop
import qualified Network.Socket as S
46 6583e677 Iustin Pop
47 6583e677 Iustin Pop
import Ganeti.HTools.Utils
48 6583e677 Iustin Pop
import Ganeti.HTools.Types
49 6583e677 Iustin Pop
50 92678b3c Iustin Pop
import Ganeti.Constants
51 9a2ff880 Iustin Pop
import Ganeti.Jobs (JobStatus)
52 683b1ca7 Iustin Pop
import Ganeti.OpCodes (OpCode)
53 a0090487 Agata Murawska
import Ganeti.THH
54 9a2ff880 Iustin Pop
55 6583e677 Iustin Pop
-- * Utility functions
56 6583e677 Iustin Pop
57 6583e677 Iustin Pop
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
58 6583e677 Iustin Pop
withTimeout :: Int -> String -> IO a -> IO a
59 6583e677 Iustin Pop
withTimeout secs descr action = do
60 6583e677 Iustin Pop
    result <- timeout (secs * 1000000) action
61 6583e677 Iustin Pop
    (case result of
62 6583e677 Iustin Pop
       Nothing -> fail $ "Timeout in " ++ descr
63 6583e677 Iustin Pop
       Just v -> return v)
64 6583e677 Iustin Pop
65 6583e677 Iustin Pop
-- * Generic protocol functionality
66 6583e677 Iustin Pop
67 92678b3c Iustin Pop
$(declareSADT "QrViaLuxi"
68 92678b3c Iustin Pop
     [ ("QRLock", 'qrLock)
69 92678b3c Iustin Pop
     , ("QRInstance", 'qrInstance)
70 92678b3c Iustin Pop
     , ("QRNode", 'qrNode)
71 92678b3c Iustin Pop
     , ("QRGroup", 'qrGroup)
72 92678b3c Iustin Pop
     , ("QROs", 'qrOs)
73 92678b3c Iustin Pop
     ])
74 92678b3c Iustin Pop
$(makeJSONInstance ''QrViaLuxi)
75 92678b3c Iustin Pop
76 a0090487 Agata Murawska
-- | Currently supported Luxi operations and JSON serialization.
77 a0090487 Agata Murawska
$(genLuxiOp "LuxiOp"
78 92678b3c Iustin Pop
    [("Query" ,
79 b20cbf06 Iustin Pop
       [ ("what",    [t| QrViaLuxi |], [| id |])
80 b20cbf06 Iustin Pop
       , ("fields",  [t| [String]  |], [| id |])
81 b20cbf06 Iustin Pop
       , ("qfilter", [t| ()        |], [| const JSNull |])
82 b20cbf06 Iustin Pop
       ])
83 92678b3c Iustin Pop
     , ("QueryNodes",
84 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
85 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
86 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
87 b20cbf06 Iustin Pop
       ])
88 a0090487 Agata Murawska
    , ("QueryGroups",
89 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
90 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
91 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
92 b20cbf06 Iustin Pop
       ])
93 a0090487 Agata Murawska
    , ("QueryInstances",
94 a0090487 Agata Murawska
       [ ("names",  [t| [String] |], [| id |])
95 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
96 a0090487 Agata Murawska
       , ("lock",   [t| Bool     |], [| id |])
97 b20cbf06 Iustin Pop
       ])
98 a0090487 Agata Murawska
    , ("QueryJobs",
99 a0090487 Agata Murawska
       [ ("ids",    [t| [Int]    |], [| map show |])
100 a0090487 Agata Murawska
       , ("fields", [t| [String] |], [| id |])
101 b20cbf06 Iustin Pop
       ])
102 a0090487 Agata Murawska
    , ("QueryExports",
103 a0090487 Agata Murawska
       [ ("nodes", [t| [String] |], [| id |])
104 a0090487 Agata Murawska
       , ("lock",  [t| Bool     |], [| id |])
105 b20cbf06 Iustin Pop
       ])
106 a0090487 Agata Murawska
    , ("QueryConfigValues",
107 b20cbf06 Iustin Pop
       [ ("fields", [t| [String] |], [| id |]) ]
108 b20cbf06 Iustin Pop
      )
109 b20cbf06 Iustin Pop
    , ("QueryClusterInfo", [])
110 a0090487 Agata Murawska
    , ("QueryTags",
111 a0090487 Agata Murawska
       [ ("kind", [t| String |], [| id |])
112 a0090487 Agata Murawska
       , ("name", [t| String |], [| id |])
113 b20cbf06 Iustin Pop
       ])
114 a0090487 Agata Murawska
    , ("SubmitJob",
115 b20cbf06 Iustin Pop
       [ ("job", [t| [OpCode] |], [| id |]) ]
116 b20cbf06 Iustin Pop
      )
117 a0090487 Agata Murawska
    , ("SubmitManyJobs",
118 b20cbf06 Iustin Pop
       [ ("ops", [t| [[OpCode]] |], [| id |]) ]
119 b20cbf06 Iustin Pop
      )
120 a0090487 Agata Murawska
    , ("WaitForJobChange",
121 9d74cb04 Agata Murawska
       [ ("job",      [t| Int     |], [| id |])
122 9d74cb04 Agata Murawska
       , ("fields",   [t| [String]|], [| id |])
123 9d74cb04 Agata Murawska
       , ("prev_job", [t| JSValue |], [| id |])
124 9d74cb04 Agata Murawska
       , ("prev_log", [t| JSValue |], [| id |])
125 9d74cb04 Agata Murawska
       , ("tmout",    [t| Int     |], [| id |])
126 b20cbf06 Iustin Pop
       ])
127 a0090487 Agata Murawska
    , ("ArchiveJob",
128 b20cbf06 Iustin Pop
       [ ("job", [t| Int |], [| show |]) ]
129 b20cbf06 Iustin Pop
      )
130 a0090487 Agata Murawska
    , ("AutoArchiveJobs",
131 a0090487 Agata Murawska
       [ ("age",   [t| Int |], [| id |])
132 a0090487 Agata Murawska
       , ("tmout", [t| Int |], [| id |])
133 b20cbf06 Iustin Pop
       ])
134 a0090487 Agata Murawska
    , ("CancelJob",
135 b20cbf06 Iustin Pop
       [ ("job", [t| Int |], [| show |]) ]
136 b20cbf06 Iustin Pop
      )
137 a0090487 Agata Murawska
    , ("SetDrainFlag",
138 b20cbf06 Iustin Pop
       [ ("flag", [t| Bool |], [| id |]) ]
139 b20cbf06 Iustin Pop
      )
140 a0090487 Agata Murawska
    , ("SetWatcherPause",
141 b20cbf06 Iustin Pop
       [ ("duration", [t| Double |], [| id |]) ]
142 b20cbf06 Iustin Pop
      )
143 a0090487 Agata Murawska
  ])
144 6583e677 Iustin Pop
145 6583e677 Iustin Pop
-- | The serialisation of LuxiOps into strings in messages.
146 a0090487 Agata Murawska
$(genStrOfOp ''LuxiOp "strOfOp")
147 6583e677 Iustin Pop
148 6583e677 Iustin Pop
-- | The end-of-message separator.
149 6583e677 Iustin Pop
eOM :: Char
150 6583e677 Iustin Pop
eOM = '\3'
151 6583e677 Iustin Pop
152 6583e677 Iustin Pop
-- | Valid keys in the requests and responses.
153 6583e677 Iustin Pop
data MsgKeys = Method
154 6583e677 Iustin Pop
             | Args
155 6583e677 Iustin Pop
             | Success
156 6583e677 Iustin Pop
             | Result
157 6583e677 Iustin Pop
158 6583e677 Iustin Pop
-- | The serialisation of MsgKeys into strings in messages.
159 a0090487 Agata Murawska
$(genStrOfKey ''MsgKeys "strOfKey")
160 6583e677 Iustin Pop
161 6583e677 Iustin Pop
-- | Luxi client encapsulation.
162 6583e677 Iustin Pop
data Client = Client { socket :: S.Socket   -- ^ The socket of the client
163 6583e677 Iustin Pop
                     , rbuf :: IORef String -- ^ Already received buffer
164 6583e677 Iustin Pop
                     }
165 6583e677 Iustin Pop
166 6583e677 Iustin Pop
-- | Connects to the master daemon and returns a luxi Client.
167 6583e677 Iustin Pop
getClient :: String -> IO Client
168 6583e677 Iustin Pop
getClient path = do
169 6583e677 Iustin Pop
    s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
170 6583e677 Iustin Pop
    withTimeout connTimeout "creating luxi connection" $
171 6583e677 Iustin Pop
                S.connect s (S.SockAddrUnix path)
172 6583e677 Iustin Pop
    rf <- newIORef ""
173 6583e677 Iustin Pop
    return Client { socket=s, rbuf=rf}
174 6583e677 Iustin Pop
175 6583e677 Iustin Pop
-- | Closes the client socket.
176 6583e677 Iustin Pop
closeClient :: Client -> IO ()
177 6583e677 Iustin Pop
closeClient = S.sClose . socket
178 6583e677 Iustin Pop
179 6583e677 Iustin Pop
-- | Sends a message over a luxi transport.
180 6583e677 Iustin Pop
sendMsg :: Client -> String -> IO ()
181 6583e677 Iustin Pop
sendMsg s buf =
182 6583e677 Iustin Pop
    let _send obuf = do
183 6583e677 Iustin Pop
          sbytes <- withTimeout queryTimeout
184 6583e677 Iustin Pop
                    "sending luxi message" $
185 6583e677 Iustin Pop
                    S.send (socket s) obuf
186 3a3c1eb4 Iustin Pop
          unless (sbytes == length obuf) $ _send (drop sbytes obuf)
187 6583e677 Iustin Pop
    in _send (buf ++ [eOM])
188 6583e677 Iustin Pop
189 6583e677 Iustin Pop
-- | Waits for a message over a luxi transport.
190 6583e677 Iustin Pop
recvMsg :: Client -> IO String
191 6583e677 Iustin Pop
recvMsg s = do
192 6583e677 Iustin Pop
  let _recv obuf = do
193 6583e677 Iustin Pop
              nbuf <- withTimeout queryTimeout "reading luxi response" $
194 6583e677 Iustin Pop
                      S.recv (socket s) 4096
195 95f490de Iustin Pop
              let (msg, remaining) = break (eOM ==) nbuf
196 6583e677 Iustin Pop
              (if null remaining
197 95f490de Iustin Pop
               then _recv (obuf ++ msg)
198 95f490de Iustin Pop
               else return (obuf ++ msg, tail remaining))
199 6583e677 Iustin Pop
  cbuf <- readIORef $ rbuf s
200 95f490de Iustin Pop
  let (imsg, ibuf) = break (eOM ==) cbuf
201 95f490de Iustin Pop
  (msg, nbuf) <-
202 95f490de Iustin Pop
      (if null ibuf      -- if old buffer didn't contain a full message
203 95f490de Iustin Pop
       then _recv cbuf   -- then we read from network
204 95f490de Iustin Pop
       else return (imsg, tail ibuf)) -- else we return data from our buffer
205 6583e677 Iustin Pop
  writeIORef (rbuf s) nbuf
206 6583e677 Iustin Pop
  return msg
207 6583e677 Iustin Pop
208 6583e677 Iustin Pop
-- | Serialize a request to String.
209 6583e677 Iustin Pop
buildCall :: LuxiOp  -- ^ The method
210 6583e677 Iustin Pop
          -> String  -- ^ The serialized form
211 683b1ca7 Iustin Pop
buildCall lo =
212 683b1ca7 Iustin Pop
    let ja = [ (strOfKey Method, JSString $ toJSString $ strOfOp lo::JSValue)
213 683b1ca7 Iustin Pop
             , (strOfKey Args, opToArgs lo::JSValue)
214 6583e677 Iustin Pop
             ]
215 6583e677 Iustin Pop
        jo = toJSObject ja
216 6583e677 Iustin Pop
    in encodeStrict jo
217 6583e677 Iustin Pop
218 6583e677 Iustin Pop
-- | Check that luxi responses contain the required keys and that the
219 6583e677 Iustin Pop
-- call was successful.
220 6583e677 Iustin Pop
validateResult :: String -> Result JSValue
221 6583e677 Iustin Pop
validateResult s = do
222 c96d44df Iustin Pop
  oarr <- fromJResult "Parsing LUXI response"
223 c96d44df Iustin Pop
          (decodeStrict s)::Result (JSObject JSValue)
224 262f3e6c Iustin Pop
  let arr = J.fromJSObject oarr
225 e8230242 Iustin Pop
  status <- fromObj arr (strOfKey Success)::Result Bool
226 6583e677 Iustin Pop
  let rkey = strOfKey Result
227 6583e677 Iustin Pop
  (if status
228 e8230242 Iustin Pop
   then fromObj arr rkey
229 e8230242 Iustin Pop
   else fromObj arr rkey >>= fail)
230 6583e677 Iustin Pop
231 6583e677 Iustin Pop
-- | Generic luxi method call.
232 683b1ca7 Iustin Pop
callMethod :: LuxiOp -> Client -> IO (Result JSValue)
233 683b1ca7 Iustin Pop
callMethod method s = do
234 683b1ca7 Iustin Pop
  sendMsg s $ buildCall method
235 6583e677 Iustin Pop
  result <- recvMsg s
236 6583e677 Iustin Pop
  let rval = validateResult result
237 6583e677 Iustin Pop
  return rval
238 9a2ff880 Iustin Pop
239 9a2ff880 Iustin Pop
-- | Specialized submitManyJobs call.
240 683b1ca7 Iustin Pop
submitManyJobs :: Client -> [[OpCode]] -> IO (Result [String])
241 9a2ff880 Iustin Pop
submitManyJobs s jobs = do
242 683b1ca7 Iustin Pop
  rval <- callMethod (SubmitManyJobs jobs) s
243 9a2ff880 Iustin Pop
  -- map each result (status, payload) pair into a nice Result ADT
244 9a2ff880 Iustin Pop
  return $ case rval of
245 9a2ff880 Iustin Pop
             Bad x -> Bad x
246 9a2ff880 Iustin Pop
             Ok (JSArray r) ->
247 9a2ff880 Iustin Pop
                 mapM (\v -> case v of
248 9a2ff880 Iustin Pop
                               JSArray [JSBool True, JSString x] ->
249 9a2ff880 Iustin Pop
                                   Ok (fromJSString x)
250 9a2ff880 Iustin Pop
                               JSArray [JSBool False, JSString x] ->
251 9a2ff880 Iustin Pop
                                   Bad (fromJSString x)
252 9a2ff880 Iustin Pop
                               _ -> Bad "Unknown result from the master daemon"
253 9a2ff880 Iustin Pop
                      ) r
254 9a2ff880 Iustin Pop
             x -> Bad ("Cannot parse response from Ganeti: " ++ show x)
255 9a2ff880 Iustin Pop
256 9a2ff880 Iustin Pop
-- | Custom queryJobs call.
257 9a2ff880 Iustin Pop
queryJobsStatus :: Client -> [String] -> IO (Result [JobStatus])
258 9a2ff880 Iustin Pop
queryJobsStatus s jids = do
259 683b1ca7 Iustin Pop
  rval <- callMethod (QueryJobs (map read jids) ["status"]) s
260 9a2ff880 Iustin Pop
  return $ case rval of
261 9a2ff880 Iustin Pop
             Bad x -> Bad x
262 9a2ff880 Iustin Pop
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
263 9a2ff880 Iustin Pop
                       J.Ok vals -> if any null vals
264 9a2ff880 Iustin Pop
                                    then Bad "Missing job status field"
265 9a2ff880 Iustin Pop
                                    else Ok (map head vals)
266 9a2ff880 Iustin Pop
                       J.Error x -> Bad x