Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ 13d26b66

History | View | Annotate | Download (11.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

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

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011, 2012, 2013 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
  , LuxiReq(..)
31
  , Client
32
  , Server
33
  , JobId
34
  , fromJobId
35
  , makeJobId
36
  , RecvResult(..)
37
  , strOfOp
38
  , getLuxiClient
39
  , getLuxiServer
40
  , acceptClient
41
  , closeClient
42
  , closeServer
43
  , callMethod
44
  , submitManyJobs
45
  , queryJobsStatus
46
  , buildCall
47
  , buildResponse
48
  , decodeLuxiCall
49
  , recvMsg
50
  , recvMsgExt
51
  , sendMsg
52
  , allLuxiCalls
53
  ) where
54

    
55
import Control.Applicative (optional)
56
import Control.Monad
57
import qualified Data.ByteString.UTF8 as UTF8
58
import Text.JSON (encodeStrict, decodeStrict)
59
import qualified Text.JSON as J
60
import Text.JSON.Pretty (pp_value)
61
import Text.JSON.Types
62

    
63
import Ganeti.BasicTypes
64
import Ganeti.Constants
65
import Ganeti.Errors
66
import Ganeti.JSON
67
import Ganeti.UDSServer
68
import Ganeti.OpParams (pTagsObject)
69
import Ganeti.OpCodes
70
import qualified Ganeti.Query.Language as Qlang
71
import Ganeti.Runtime (GanetiDaemon(..))
72
import Ganeti.THH
73
import Ganeti.Types
74

    
75

    
76
-- | Currently supported Luxi operations and JSON serialization.
77
$(genLuxiOp "LuxiOp"
78
  [ (luxiReqQuery,
79
    [ simpleField "what"    [t| Qlang.ItemType |]
80
    , simpleField "fields"  [t| [String]  |]
81
    , simpleField "qfilter" [t| Qlang.Filter Qlang.FilterField |]
82
    ])
83
  , (luxiReqQueryFields,
84
    [ simpleField "what"    [t| Qlang.ItemType |]
85
    , simpleField "fields"  [t| [String]  |]
86
    ])
87
  , (luxiReqQueryNodes,
88
     [ simpleField "names"  [t| [String] |]
89
     , simpleField "fields" [t| [String] |]
90
     , simpleField "lock"   [t| Bool     |]
91
     ])
92
  , (luxiReqQueryGroups,
93
     [ simpleField "names"  [t| [String] |]
94
     , simpleField "fields" [t| [String] |]
95
     , simpleField "lock"   [t| Bool     |]
96
     ])
97
  , (luxiReqQueryNetworks,
98
     [ simpleField "names"  [t| [String] |]
99
     , simpleField "fields" [t| [String] |]
100
     , simpleField "lock"   [t| Bool     |]
101
     ])
102
  , (luxiReqQueryInstances,
103
     [ simpleField "names"  [t| [String] |]
104
     , simpleField "fields" [t| [String] |]
105
     , simpleField "lock"   [t| Bool     |]
106
     ])
107
  , (luxiReqQueryJobs,
108
     [ simpleField "ids"    [t| [JobId]  |]
109
     , simpleField "fields" [t| [String] |]
110
     ])
111
  , (luxiReqQueryExports,
112
     [ simpleField "nodes" [t| [String] |]
113
     , simpleField "lock"  [t| Bool     |]
114
     ])
115
  , (luxiReqQueryConfigValues,
116
     [ simpleField "fields" [t| [String] |] ]
117
    )
118
  , (luxiReqQueryClusterInfo, [])
119
  , (luxiReqQueryTags,
120
     [ pTagsObject
121
     , simpleField "name" [t| String |]
122
     ])
123
  , (luxiReqSubmitJob,
124
     [ simpleField "job" [t| [MetaOpCode] |] ]
125
    )
126
  , (luxiReqSubmitJobToDrainedQueue,
127
     [ simpleField "job" [t| [MetaOpCode] |] ]
128
    )
129
  , (luxiReqSubmitManyJobs,
130
     [ simpleField "ops" [t| [[MetaOpCode]] |] ]
131
    )
132
  , (luxiReqWaitForJobChange,
133
     [ simpleField "job"      [t| JobId   |]
134
     , simpleField "fields"   [t| [String]|]
135
     , simpleField "prev_job" [t| JSValue |]
136
     , simpleField "prev_log" [t| JSValue |]
137
     , simpleField "tmout"    [t| Int     |]
138
     ])
139
  , (luxiReqPickupJob,
140
     [ simpleField "job" [t| JobId |] ]
141
    )
142
  , (luxiReqArchiveJob,
143
     [ simpleField "job" [t| JobId |] ]
144
    )
145
  , (luxiReqAutoArchiveJobs,
146
     [ simpleField "age"   [t| Int |]
147
     , simpleField "tmout" [t| Int |]
148
     ])
149
  , (luxiReqCancelJob,
150
     [ simpleField "job" [t| JobId |] ]
151
    )
152
  , (luxiReqChangeJobPriority,
153
     [ simpleField "job"      [t| JobId |]
154
     , simpleField "priority" [t| Int |] ]
155
    )
156
  , (luxiReqSetDrainFlag,
157
     [ simpleField "flag" [t| Bool |] ]
158
    )
159
  , (luxiReqSetWatcherPause,
160
     [ optionalNullSerField
161
         $ timeAsDoubleField "duration" ]
162
    )
163
  ])
164

    
165
$(makeJSONInstance ''LuxiReq)
166

    
167
-- | List of all defined Luxi calls.
168
$(genAllConstr (drop 3) ''LuxiReq "allLuxiCalls")
169

    
170
-- | The serialisation of LuxiOps into strings in messages.
171
$(genStrOfOp ''LuxiOp "strOfOp")
172

    
173

    
174
luxiConnectConfig :: ConnectConfig
175
luxiConnectConfig = ConnectConfig { connDaemon = GanetiLuxid
176
                                  , recvTmo    = luxiDefRwto
177
                                  , sendTmo    = luxiDefRwto
178
                                  }
179

    
180
-- | Connects to the master daemon and returns a luxi Client.
181
getLuxiClient :: String -> IO Client
182
getLuxiClient = connectClient luxiConnectConfig luxiDefCtmo
183

    
184
-- | Creates and returns a server endpoint.
185
getLuxiServer :: Bool -> FilePath -> IO Server
186
getLuxiServer = connectServer luxiConnectConfig
187

    
188
-- | Serialize a request to String.
189
buildCall :: LuxiOp  -- ^ The method
190
          -> String  -- ^ The serialized form
191
buildCall lo =
192
  let ja = [ (strOfKey Method, J.showJSON $ strOfOp lo)
193
           , (strOfKey Args, opToArgs lo)
194
           ]
195
      jo = toJSObject ja
196
  in encodeStrict jo
197

    
198

    
199
-- | Converts Luxi call arguments into a 'LuxiOp' data structure.
200
-- This is used for building a Luxi 'Handler'.
201
--
202
-- This is currently hand-coded until we make it more uniform so that
203
-- it can be generated using TH.
204
decodeLuxiCall :: JSValue -> JSValue -> Result LuxiOp
205
decodeLuxiCall method args = do
206
  call <- fromJResult "Unable to parse LUXI request method" $ J.readJSON method
207
  case call of
208
    ReqQueryJobs -> do
209
              (jids, jargs) <- fromJVal args
210
              jids' <- case jids of
211
                         JSNull -> return []
212
                         _ -> fromJVal jids
213
              return $ QueryJobs jids' jargs
214
    ReqQueryInstances -> do
215
              (names, fields, locking) <- fromJVal args
216
              return $ QueryInstances names fields locking
217
    ReqQueryNodes -> do
218
              (names, fields, locking) <- fromJVal args
219
              return $ QueryNodes names fields locking
220
    ReqQueryGroups -> do
221
              (names, fields, locking) <- fromJVal args
222
              return $ QueryGroups names fields locking
223
    ReqQueryClusterInfo ->
224
              return QueryClusterInfo
225
    ReqQueryNetworks -> do
226
              (names, fields, locking) <- fromJVal args
227
              return $ QueryNetworks names fields locking
228
    ReqQuery -> do
229
              (what, fields, qfilter) <- fromJVal args
230
              return $ Query what fields qfilter
231
    ReqQueryFields -> do
232
              (what, fields) <- fromJVal args
233
              fields' <- case fields of
234
                           JSNull -> return []
235
                           _ -> fromJVal fields
236
              return $ QueryFields what fields'
237
    ReqSubmitJob -> do
238
              [ops1] <- fromJVal args
239
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
240
              return $ SubmitJob ops2
241
    ReqSubmitJobToDrainedQueue -> do
242
              [ops1] <- fromJVal args
243
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
244
              return $ SubmitJobToDrainedQueue ops2
245
    ReqSubmitManyJobs -> do
246
              [ops1] <- fromJVal args
247
              ops2 <- mapM (fromJResult (luxiReqToRaw call) . J.readJSON) ops1
248
              return $ SubmitManyJobs ops2
249
    ReqWaitForJobChange -> do
250
              (jid, fields, pinfo, pidx, wtmout) <-
251
                -- No instance for 5-tuple, code copied from the
252
                -- json sources and adapted
253
                fromJResult "Parsing WaitForJobChange message" $
254
                case args of
255
                  JSArray [a, b, c, d, e] ->
256
                    (,,,,) `fmap`
257
                    J.readJSON a `ap`
258
                    J.readJSON b `ap`
259
                    J.readJSON c `ap`
260
                    J.readJSON d `ap`
261
                    J.readJSON e
262
                  _ -> J.Error "Not enough values"
263
              return $ WaitForJobChange jid fields pinfo pidx wtmout
264
    ReqPickupJob -> do
265
              [jid] <- fromJVal args
266
              return $ PickupJob jid
267
    ReqArchiveJob -> do
268
              [jid] <- fromJVal args
269
              return $ ArchiveJob jid
270
    ReqAutoArchiveJobs -> do
271
              (age, tmout) <- fromJVal args
272
              return $ AutoArchiveJobs age tmout
273
    ReqQueryExports -> do
274
              (nodes, lock) <- fromJVal args
275
              return $ QueryExports nodes lock
276
    ReqQueryConfigValues -> do
277
              [fields] <- fromJVal args
278
              return $ QueryConfigValues fields
279
    ReqQueryTags -> do
280
              (kind, name) <- fromJVal args
281
              return $ QueryTags kind name
282
    ReqCancelJob -> do
283
              [jid] <- fromJVal args
284
              return $ CancelJob jid
285
    ReqChangeJobPriority -> do
286
              (jid, priority) <- fromJVal args
287
              return $ ChangeJobPriority jid priority
288
    ReqSetDrainFlag -> do
289
              [flag] <- fromJVal args
290
              return $ SetDrainFlag flag
291
    ReqSetWatcherPause -> do
292
              duration <- optional $ do
293
                [x] <- fromJVal args
294
                liftM unTimeAsDoubleJSON $ fromJVal x
295
              return $ SetWatcherPause duration
296

    
297
-- | Check that luxi responses contain the required keys and that the
298
-- call was successful.
299
validateResult :: String -> ErrorResult JSValue
300
validateResult s = do
301
  when (UTF8.replacement_char `elem` s) $
302
       fail "Failed to decode UTF-8, detected replacement char after decoding"
303
  oarr <- fromJResult "Parsing LUXI response" (decodeStrict s)
304
  let arr = J.fromJSObject oarr
305
  status <- fromObj arr (strOfKey Success)
306
  result <- fromObj arr (strOfKey Result)
307
  if status
308
    then return result
309
    else decodeError result
310

    
311
-- | Try to decode an error from the server response. This function
312
-- will always fail, since it's called only on the error path (when
313
-- status is False).
314
decodeError :: JSValue -> ErrorResult JSValue
315
decodeError val =
316
  case fromJVal val of
317
    Ok e -> Bad e
318
    Bad msg -> Bad $ GenericError msg
319

    
320
-- | Generic luxi method call.
321
callMethod :: LuxiOp -> Client -> IO (ErrorResult JSValue)
322
callMethod method s = do
323
  sendMsg s $ buildCall method
324
  result <- recvMsg s
325
  let rval = validateResult result
326
  return rval
327

    
328
-- | Parse job submission result.
329
parseSubmitJobResult :: JSValue -> ErrorResult JobId
330
parseSubmitJobResult (JSArray [JSBool True, v]) =
331
  case J.readJSON v of
332
    J.Error msg -> Bad $ LuxiError msg
333
    J.Ok v' -> Ok v'
334
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
335
  Bad . LuxiError $ fromJSString x
336
parseSubmitJobResult v =
337
  Bad . LuxiError $ "Unknown result from the master daemon: " ++
338
      show (pp_value v)
339

    
340
-- | Specialized submitManyJobs call.
341
submitManyJobs :: Client -> [[MetaOpCode]] -> IO (ErrorResult [JobId])
342
submitManyJobs s jobs = do
343
  rval <- callMethod (SubmitManyJobs jobs) s
344
  -- map each result (status, payload) pair into a nice Result ADT
345
  return $ case rval of
346
             Bad x -> Bad x
347
             Ok (JSArray r) -> mapM parseSubmitJobResult r
348
             x -> Bad . LuxiError $
349
                  "Cannot parse response from Ganeti: " ++ show x
350

    
351
-- | Custom queryJobs call.
352
queryJobsStatus :: Client -> [JobId] -> IO (ErrorResult [JobStatus])
353
queryJobsStatus s jids = do
354
  rval <- callMethod (QueryJobs jids ["status"]) s
355
  return $ case rval of
356
             Bad x -> Bad x
357
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
358
                       J.Ok vals -> if any null vals
359
                                    then Bad $
360
                                         LuxiError "Missing job status field"
361
                                    else Ok (map head vals)
362
                       J.Error x -> Bad $ LuxiError x