Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Luxi.hs @ 260d0bda

History | View | Annotate | Download (8.9 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti LUXI interface.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011 Google Inc.
10

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

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

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

    
26
-}
27

    
28
module Ganeti.Luxi
29
    ( LuxiOp(..)
30
    , QrViaLuxi(..)
31
    , ResultStatus(..)
32
    , Client
33
    , checkRS
34
    , getClient
35
    , closeClient
36
    , callMethod
37
    , submitManyJobs
38
    , queryJobsStatus
39
    ) where
40

    
41
import Data.IORef
42
import Control.Monad
43
import Text.JSON (encodeStrict, decodeStrict)
44
import qualified Text.JSON as J
45
import Text.JSON.Types
46
import System.Timeout
47
import qualified Network.Socket as S
48

    
49
import Ganeti.HTools.Utils
50
import Ganeti.HTools.Types
51

    
52
import Ganeti.Constants
53
import Ganeti.Jobs (JobStatus)
54
import Ganeti.OpCodes (OpCode)
55
import Ganeti.THH
56

    
57
-- * Utility functions
58

    
59
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
60
withTimeout :: Int -> String -> IO a -> IO a
61
withTimeout secs descr action = do
62
    result <- timeout (secs * 1000000) action
63
    (case result of
64
       Nothing -> fail $ "Timeout in " ++ descr
65
       Just v -> return v)
66

    
67
-- * Generic protocol functionality
68

    
69
$(declareSADT "QrViaLuxi"
70
     [ ("QRLock", 'qrLock)
71
     , ("QRInstance", 'qrInstance)
72
     , ("QRNode", 'qrNode)
73
     , ("QRGroup", 'qrGroup)
74
     , ("QROs", 'qrOs)
75
     ])
76
$(makeJSONInstance ''QrViaLuxi)
77

    
78
-- | Currently supported Luxi operations and JSON serialization.
79
$(genLuxiOp "LuxiOp"
80
    [("Query" ,
81
       [ ("what",    [t| QrViaLuxi |], [| id |])
82
       , ("fields",  [t| [String]  |], [| id |])
83
       , ("qfilter", [t| ()        |], [| const JSNull |])
84
       ])
85
     , ("QueryNodes",
86
       [ ("names",  [t| [String] |], [| id |])
87
       , ("fields", [t| [String] |], [| id |])
88
       , ("lock",   [t| Bool     |], [| id |])
89
       ])
90
    , ("QueryGroups",
91
       [ ("names",  [t| [String] |], [| id |])
92
       , ("fields", [t| [String] |], [| id |])
93
       , ("lock",   [t| Bool     |], [| id |])
94
       ])
95
    , ("QueryInstances",
96
       [ ("names",  [t| [String] |], [| id |])
97
       , ("fields", [t| [String] |], [| id |])
98
       , ("lock",   [t| Bool     |], [| id |])
99
       ])
100
    , ("QueryJobs",
101
       [ ("ids",    [t| [Int]    |], [| map show |])
102
       , ("fields", [t| [String] |], [| id |])
103
       ])
104
    , ("QueryExports",
105
       [ ("nodes", [t| [String] |], [| id |])
106
       , ("lock",  [t| Bool     |], [| id |])
107
       ])
108
    , ("QueryConfigValues",
109
       [ ("fields", [t| [String] |], [| id |]) ]
110
      )
111
    , ("QueryClusterInfo", [])
112
    , ("QueryTags",
113
       [ ("kind", [t| String |], [| id |])
114
       , ("name", [t| String |], [| id |])
115
       ])
116
    , ("SubmitJob",
117
       [ ("job", [t| [OpCode] |], [| id |]) ]
118
      )
119
    , ("SubmitManyJobs",
120
       [ ("ops", [t| [[OpCode]] |], [| id |]) ]
121
      )
122
    , ("WaitForJobChange",
123
       [ ("job",      [t| Int     |], [| id |])
124
       , ("fields",   [t| [String]|], [| id |])
125
       , ("prev_job", [t| JSValue |], [| id |])
126
       , ("prev_log", [t| JSValue |], [| id |])
127
       , ("tmout",    [t| Int     |], [| id |])
128
       ])
129
    , ("ArchiveJob",
130
       [ ("job", [t| Int |], [| show |]) ]
131
      )
132
    , ("AutoArchiveJobs",
133
       [ ("age",   [t| Int |], [| id |])
134
       , ("tmout", [t| Int |], [| id |])
135
       ])
136
    , ("CancelJob",
137
       [ ("job", [t| Int |], [| show |]) ]
138
      )
139
    , ("SetDrainFlag",
140
       [ ("flag", [t| Bool |], [| id |]) ]
141
      )
142
    , ("SetWatcherPause",
143
       [ ("duration", [t| Double |], [| id |]) ]
144
      )
145
  ])
146

    
147
-- | The serialisation of LuxiOps into strings in messages.
148
$(genStrOfOp ''LuxiOp "strOfOp")
149

    
150
$(declareIADT "ResultStatus"
151
     [ ("RSNormal", 'rsNormal)
152
     , ("RSUnknown", 'rsUnknown)
153
     , ("RSNoData", 'rsNodata)
154
     , ("RSUnavailable", 'rsUnavail)
155
     , ("RSOffline", 'rsOffline)
156
     ])
157
$(makeJSONInstanceInt ''ResultStatus)
158

    
159
-- | Check that ResultStatus is success or fail with descriptive message.
160
checkRS :: (Monad m) => ResultStatus -> a -> m a
161
checkRS RSNormal val    = return val
162
checkRS RSUnknown _     = fail "Unknown field"
163
checkRS RSNoData _      = fail "No data for a field"
164
checkRS RSUnavailable _ = fail "Ganeti reports unavailable data"
165
checkRS RSOffline _     = fail "Ganeti reports resource as offline"
166

    
167
-- | The end-of-message separator.
168
eOM :: Char
169
eOM = '\3'
170

    
171
-- | Valid keys in the requests and responses.
172
data MsgKeys = Method
173
             | Args
174
             | Success
175
             | Result
176

    
177
-- | The serialisation of MsgKeys into strings in messages.
178
$(genStrOfKey ''MsgKeys "strOfKey")
179

    
180
-- | Luxi client encapsulation.
181
data Client = Client { socket :: S.Socket   -- ^ The socket of the client
182
                     , rbuf :: IORef String -- ^ Already received buffer
183
                     }
184

    
185
-- | Connects to the master daemon and returns a luxi Client.
186
getClient :: String -> IO Client
187
getClient path = do
188
    s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
189
    withTimeout connTimeout "creating luxi connection" $
190
                S.connect s (S.SockAddrUnix path)
191
    rf <- newIORef ""
192
    return Client { socket=s, rbuf=rf}
193

    
194
-- | Closes the client socket.
195
closeClient :: Client -> IO ()
196
closeClient = S.sClose . socket
197

    
198
-- | Sends a message over a luxi transport.
199
sendMsg :: Client -> String -> IO ()
200
sendMsg s buf =
201
    let _send obuf = do
202
          sbytes <- withTimeout queryTimeout
203
                    "sending luxi message" $
204
                    S.send (socket s) obuf
205
          unless (sbytes == length obuf) $ _send (drop sbytes obuf)
206
    in _send (buf ++ [eOM])
207

    
208
-- | Waits for a message over a luxi transport.
209
recvMsg :: Client -> IO String
210
recvMsg s = do
211
  let _recv obuf = do
212
              nbuf <- withTimeout queryTimeout "reading luxi response" $
213
                      S.recv (socket s) 4096
214
              let (msg, remaining) = break (eOM ==) nbuf
215
              (if null remaining
216
               then _recv (obuf ++ msg)
217
               else return (obuf ++ msg, tail remaining))
218
  cbuf <- readIORef $ rbuf s
219
  let (imsg, ibuf) = break (eOM ==) cbuf
220
  (msg, nbuf) <-
221
      (if null ibuf      -- if old buffer didn't contain a full message
222
       then _recv cbuf   -- then we read from network
223
       else return (imsg, tail ibuf)) -- else we return data from our buffer
224
  writeIORef (rbuf s) nbuf
225
  return msg
226

    
227
-- | Serialize a request to String.
228
buildCall :: LuxiOp  -- ^ The method
229
          -> String  -- ^ The serialized form
230
buildCall lo =
231
    let ja = [ (strOfKey Method, JSString $ toJSString $ strOfOp lo::JSValue)
232
             , (strOfKey Args, opToArgs lo::JSValue)
233
             ]
234
        jo = toJSObject ja
235
    in encodeStrict jo
236

    
237
-- | Check that luxi responses contain the required keys and that the
238
-- call was successful.
239
validateResult :: String -> Result JSValue
240
validateResult s = do
241
  oarr <- fromJResult "Parsing LUXI response"
242
          (decodeStrict s)::Result (JSObject JSValue)
243
  let arr = J.fromJSObject oarr
244
  status <- fromObj arr (strOfKey Success)::Result Bool
245
  let rkey = strOfKey Result
246
  (if status
247
   then fromObj arr rkey
248
   else fromObj arr rkey >>= fail)
249

    
250
-- | Generic luxi method call.
251
callMethod :: LuxiOp -> Client -> IO (Result JSValue)
252
callMethod method s = do
253
  sendMsg s $ buildCall method
254
  result <- recvMsg s
255
  let rval = validateResult result
256
  return rval
257

    
258
-- | Specialized submitManyJobs call.
259
submitManyJobs :: Client -> [[OpCode]] -> IO (Result [String])
260
submitManyJobs s jobs = do
261
  rval <- callMethod (SubmitManyJobs jobs) s
262
  -- map each result (status, payload) pair into a nice Result ADT
263
  return $ case rval of
264
             Bad x -> Bad x
265
             Ok (JSArray r) ->
266
                 mapM (\v -> case v of
267
                               JSArray [JSBool True, JSString x] ->
268
                                   Ok (fromJSString x)
269
                               JSArray [JSBool False, JSString x] ->
270
                                   Bad (fromJSString x)
271
                               _ -> Bad "Unknown result from the master daemon"
272
                      ) r
273
             x -> Bad ("Cannot parse response from Ganeti: " ++ show x)
274

    
275
-- | Custom queryJobs call.
276
queryJobsStatus :: Client -> [String] -> IO (Result [JobStatus])
277
queryJobsStatus s jids = do
278
  rval <- callMethod (QueryJobs (map read jids) ["status"]) s
279
  return $ case rval of
280
             Bad x -> Bad x
281
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
282
                       J.Ok vals -> if any null vals
283
                                    then Bad "Missing job status field"
284
                                    else Ok (map head vals)
285
                       J.Error x -> Bad x