Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Luxi.hs @ aa4a4b76

History | View | Annotate | Download (10.7 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
  , opToArgs
39
  , getLuxiClient
40
  , getLuxiServer
41
  , acceptClient
42
  , closeClient
43
  , closeServer
44
  , callMethod
45
  , submitManyJobs
46
  , queryJobsStatus
47
  , buildCall
48
  , buildResponse
49
  , decodeLuxiCall
50
  , recvMsg
51
  , recvMsgExt
52
  , sendMsg
53
  , allLuxiCalls
54
  ) where
55

    
56
import Control.Applicative (optional)
57
import Control.Monad
58
import qualified Text.JSON as J
59
import Text.JSON.Pretty (pp_value)
60
import Text.JSON.Types
61

    
62
import Ganeti.BasicTypes
63
import Ganeti.Constants
64
import Ganeti.Errors
65
import Ganeti.JSON
66
import Ganeti.UDSServer
67
import Ganeti.OpParams (pTagsObject)
68
import Ganeti.OpCodes
69
import qualified Ganeti.Query.Language as Qlang
70
import Ganeti.Runtime (GanetiDaemon(..))
71
import Ganeti.THH
72
import Ganeti.THH.Field
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

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

    
287
-- | Generic luxi method call
288
callMethod :: LuxiOp -> Client -> IO (ErrorResult JSValue)
289
callMethod method s = do
290
  sendMsg s $ buildCall (strOfOp method) (opToArgs method)
291
  result <- recvMsg s
292
  return $ parseResponse result
293

    
294
-- | Parse job submission result.
295
parseSubmitJobResult :: JSValue -> ErrorResult JobId
296
parseSubmitJobResult (JSArray [JSBool True, v]) =
297
  case J.readJSON v of
298
    J.Error msg -> Bad $ LuxiError msg
299
    J.Ok v' -> Ok v'
300
parseSubmitJobResult (JSArray [JSBool False, JSString x]) =
301
  Bad . LuxiError $ fromJSString x
302
parseSubmitJobResult v =
303
  Bad . LuxiError $ "Unknown result from the master daemon: " ++
304
      show (pp_value v)
305

    
306
-- | Specialized submitManyJobs call.
307
submitManyJobs :: Client -> [[MetaOpCode]] -> IO (ErrorResult [JobId])
308
submitManyJobs s jobs = do
309
  rval <- callMethod (SubmitManyJobs jobs) s
310
  -- map each result (status, payload) pair into a nice Result ADT
311
  return $ case rval of
312
             Bad x -> Bad x
313
             Ok (JSArray r) -> mapM parseSubmitJobResult r
314
             x -> Bad . LuxiError $
315
                  "Cannot parse response from Ganeti: " ++ show x
316

    
317
-- | Custom queryJobs call.
318
queryJobsStatus :: Client -> [JobId] -> IO (ErrorResult [JobStatus])
319
queryJobsStatus s jids = do
320
  rval <- callMethod (QueryJobs jids ["status"]) s
321
  return $ case rval of
322
             Bad x -> Bad x
323
             Ok y -> case J.readJSON y::(J.Result [[JobStatus]]) of
324
                       J.Ok vals -> if any null vals
325
                                    then Bad $
326
                                         LuxiError "Missing job status field"
327
                                    else Ok (map head vals)
328
                       J.Error x -> Bad $ LuxiError x