Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ 0fbc8447

History | View | Annotate | Download (12 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
  , validateCall
49
  , decodeCall
50
  , recvMsg
51
  , recvMsgExt
52
  , sendMsg
53
  , allLuxiCalls
54
  ) where
55

    
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
     [ simpleField "duration" [t| Double |] ]
161
    )
162
  ])
163

    
164
$(makeJSONInstance ''LuxiReq)
165

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

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

    
172
-- | Type holding the initial (unparsed) Luxi call.
173
data LuxiCall = LuxiCall LuxiReq JSValue
174

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

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

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

    
189

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

    
200
-- | Check that luxi request contains the required keys and parse it.
201
validateCall :: String -> Result LuxiCall
202
validateCall s = do
203
  arr <- fromJResult "parsing top-level luxi message" $
204
         decodeStrict s::Result (JSObject JSValue)
205
  let aobj = fromJSObject arr
206
  call <- fromObj aobj (strOfKey Method)::Result LuxiReq
207
  args <- fromObj aobj (strOfKey Args)
208
  return (LuxiCall call args)
209

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

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

    
318
-- | Try to decode an error from the server response. This function
319
-- will always fail, since it's called only on the error path (when
320
-- status is False).
321
decodeError :: JSValue -> ErrorResult JSValue
322
decodeError val =
323
  case fromJVal val of
324
    Ok e -> Bad e
325
    Bad msg -> Bad $ GenericError msg
326

    
327
-- | Generic luxi method call.
328
callMethod :: LuxiOp -> Client -> IO (ErrorResult JSValue)
329
callMethod method s = do
330
  sendMsg s $ buildCall method
331
  result <- recvMsg s
332
  let rval = validateResult result
333
  return rval
334

    
335
-- | Parse job submission result.
336
parseSubmitJobResult :: JSValue -> ErrorResult JobId
337
parseSubmitJobResult (JSArray [JSBool True, v]) =
338
  case J.readJSON v of
339
    J.Error msg -> Bad $ LuxiError msg
340
    J.Ok v' -> Ok v'
341
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
342
  Bad . LuxiError $ fromJSString x
343
parseSubmitJobResult v =
344
  Bad . LuxiError $ "Unknown result from the master daemon: " ++
345
      show (pp_value v)
346

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

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