Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ 508c7d70

History | View | Annotate | Download (16.2 kB)

1
{-# LANGUAGE TupleSections #-}
2

    
3
{-| Implementation of the Ganeti Query2 functionality.
4

    
5
 -}
6

    
7
{-
8

    
9
Copyright (C) 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
{-
29

    
30
TODO: problems with the current model:
31

    
32
1. There's nothing preventing a result such as ResultEntry RSNormal
33
Nothing, or ResultEntry RSNoData (Just ...); ideally, we would
34
separate the the RSNormal and other types; we would need a new data
35
type for this, though, with JSON encoding/decoding
36

    
37
2. We don't have a way to 'bind' a FieldDefinition's field type
38
(e.q. QFTBool) with the actual value that is returned from a
39
FieldGetter. This means that the various getter functions can return
40
divergent types for the same field when evaluated against multiple
41
items. This is bad; it only works today because we 'hide' everything
42
behind JSValue, but is not nice at all. We should probably remove the
43
separation between FieldDefinition and the FieldGetter, and introduce
44
a new abstract data type, similar to QFT*, that contains the values
45
too.
46

    
47
-}
48

    
49
module Ganeti.Query.Query
50
    ( query
51
    , queryFields
52
    , queryCompat
53
    , getRequestedNames
54
    , nameField
55
    , NoDataRuntime
56
    , uuidField
57
    ) where
58

    
59
import Control.DeepSeq
60
import Control.Monad (filterM, foldM, liftM)
61
import Control.Monad.Trans (lift)
62
import qualified Data.Foldable as Foldable
63
import Data.List (intercalate, nub)
64
import Data.Maybe (fromMaybe)
65
import qualified Data.Map as Map
66
import qualified Text.JSON as J
67

    
68
import Ganeti.BasicTypes
69
import Ganeti.Config
70
import Ganeti.Errors
71
import Ganeti.JQueue
72
import Ganeti.JSON
73
import Ganeti.Logging
74
import qualified Ganeti.Luxi as L
75
import Ganeti.Objects
76
import Ganeti.Query.Common
77
import qualified Ganeti.Query.Export as Export
78
import Ganeti.Query.Filter
79
import qualified Ganeti.Query.Instance as Instance
80
import qualified Ganeti.Query.Job as Query.Job
81
import qualified Ganeti.Query.Group as Group
82
import Ganeti.Query.Language
83
import qualified Ganeti.Query.Locks as Locks
84
import qualified Ganeti.Query.Network as Network
85
import qualified Ganeti.Query.Node as Node
86
import Ganeti.Query.Types
87
import Ganeti.Path
88
import Ganeti.Types
89
import Ganeti.Utils
90

    
91
-- | Collector type
92
data CollectorType a b
93
  = CollectorSimple     (Bool -> ConfigData -> [a] -> IO [(a, b)])
94
  | CollectorFieldAware (Bool -> ConfigData -> [String] -> [a] -> IO [(a, b)])
95

    
96
-- * Helper functions
97

    
98
-- | Builds an unknown field definition.
99
mkUnknownFDef :: String -> FieldData a b
100
mkUnknownFDef name =
101
  ( FieldDefinition name name QFTUnknown ("Unknown field '" ++ name ++ "'")
102
  , FieldUnknown
103
  , QffNormal )
104

    
105
-- | Runs a field getter on the existing contexts.
106
execGetter :: ConfigData -> b -> a -> FieldGetter a b -> ResultEntry
107
execGetter _   _  item (FieldSimple getter)        = getter item
108
execGetter cfg _  item (FieldConfig getter)        = getter cfg item
109
execGetter _   rt item (FieldRuntime getter)       = getter rt item
110
execGetter cfg rt item (FieldConfigRuntime getter) = getter cfg rt item
111
execGetter _   _  _    FieldUnknown                = rsUnknown
112

    
113
-- * Main query execution
114

    
115
-- | Helper to build the list of requested fields. This transforms the
116
-- list of string fields to a list of field defs and getters, with
117
-- some of them possibly being unknown fields.
118
getSelectedFields :: FieldMap a b  -- ^ Defined fields
119
                  -> [String]      -- ^ Requested fields
120
                  -> FieldList a b -- ^ Selected fields
121
getSelectedFields defined =
122
  map (\name -> fromMaybe (mkUnknownFDef name) $ name `Map.lookup` defined)
123

    
124
-- | Check whether list of queried fields contains live fields.
125
needsLiveData :: [FieldGetter a b] -> Bool
126
needsLiveData = any isRuntimeField
127

    
128
-- | Checks whether we have requested exactly some names. This is a
129
-- simple wrapper over 'requestedNames' and 'nameField'.
130
needsNames :: Query -> Maybe [FilterValue]
131
needsNames (Query kind _ qfilter) = requestedNames (nameField kind) qfilter
132

    
133
-- | Computes the name field for different query types.
134
nameField :: ItemType -> FilterField
135
nameField (ItemTypeLuxi QRJob) = "id"
136
nameField (ItemTypeOpCode QRExport) = "node"
137
nameField _ = "name"
138

    
139
-- | Computes the uuid field, or the best possible substitute, for different
140
-- query types.
141
uuidField :: ItemType -> FilterField
142
uuidField (ItemTypeLuxi QRJob) = nameField (ItemTypeLuxi QRJob)
143
uuidField (ItemTypeOpCode QRExport) = nameField (ItemTypeOpCode QRExport)
144
uuidField _ = "uuid"
145

    
146
-- | Extracts all quoted strings from a list, ignoring the
147
-- 'NumericValue' entries.
148
getAllQuotedStrings :: [FilterValue] -> [String]
149
getAllQuotedStrings =
150
  concatMap extractor
151
    where extractor (NumericValue _)   = []
152
          extractor (QuotedString val) = [val]
153

    
154
-- | Checks that we have either requested a valid set of names, or we
155
-- have a more complex filter.
156
getRequestedNames :: Query -> [String]
157
getRequestedNames qry =
158
  case needsNames qry of
159
    Just names -> getAllQuotedStrings names
160
    Nothing    -> []
161

    
162
-- | Compute the requested job IDs. This is custom since we need to
163
-- handle both strings and integers.
164
getRequestedJobIDs :: Filter FilterField -> Result [JobId]
165
getRequestedJobIDs qfilter =
166
  case requestedNames (nameField (ItemTypeLuxi QRJob)) qfilter of
167
    Nothing -> Ok []
168
    Just [] -> Ok []
169
    Just vals ->
170
      liftM nub $
171
      mapM (\e -> case e of
172
                    QuotedString s -> makeJobIdS s
173
                    NumericValue i -> makeJobId $ fromIntegral i
174
           ) vals
175

    
176
-- | Generic query implementation for resources that are backed by
177
-- some configuration objects.
178
--
179
-- Different query types use the same 'genericQuery' function by providing
180
-- a collector function and a field map. The collector function retrieves
181
-- live data, and the field map provides both the requirements and the logic
182
-- necessary to retrieve the data needed for the field.
183
--
184
-- The 'b' type in the specification is the runtime. Every query can gather
185
-- additional live data related to the configuration object using the collector
186
-- to perform RPC calls.
187
--
188
-- The gathered data, or the failure to get it, is expressed through a runtime
189
-- object. The type of a runtime object is determined by every query type for
190
-- itself, and used exclusively by that query.
191
genericQuery :: FieldMap a b       -- ^ Maps field names to field definitions
192
             -> CollectorType a b  -- ^ Collector of live data
193
             -> (a -> String)      -- ^ Object to name function
194
             -> (ConfigData -> Container a) -- ^ Get all objects from config
195
             -> (ConfigData -> String -> ErrorResult a) -- ^ Lookup object
196
             -> ConfigData         -- ^ The config to run the query against
197
             -> Bool               -- ^ Whether the query should be run live
198
             -> [String]           -- ^ List of requested fields
199
             -> Filter FilterField -- ^ Filter field
200
             -> [String]           -- ^ List of requested names
201
             -> IO (ErrorResult QueryResult)
202
genericQuery fieldsMap collector nameFn configFn getFn cfg
203
             live fields qfilter wanted =
204
  runResultT $ do
205
  cfilter <- resultT $ compileFilter fieldsMap qfilter
206
  let selected = getSelectedFields fieldsMap fields
207
      (fdefs, fgetters, _) = unzip3 selected
208
      live' = live && needsLiveData fgetters
209
  objects <- resultT $ case wanted of
210
             [] -> Ok . niceSortKey nameFn .
211
                   Map.elems . fromContainer $ configFn cfg
212
             _  -> mapM (getFn cfg) wanted
213
  -- Run the first pass of the filter, without a runtime context; this will
214
  -- limit the objects that we'll contact for exports
215
  fobjects <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
216
                        objects
217
  -- Gather the runtime data
218
  runtimes <- case collector of
219
    CollectorSimple     collFn -> lift $ collFn live' cfg fobjects
220
    CollectorFieldAware collFn -> lift $ collFn live' cfg fields fobjects
221
  -- Filter the results again, based on the gathered data
222
  let fdata = map (\(obj, runtime) ->
223
                     map (execGetter cfg runtime obj) fgetters)
224
              runtimes
225
  return QueryResult { qresFields = fdefs, qresData = fdata }
226

    
227
-- | Main query execution function.
228
query :: ConfigData   -- ^ The current configuration
229
      -> Bool         -- ^ Whether to collect live data
230
      -> Query        -- ^ The query (item, fields, filter)
231
      -> IO (ErrorResult QueryResult) -- ^ Result
232
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
233
  queryJobs cfg live fields qfilter
234
query _ live (Query (ItemTypeLuxi QRLock) fields qfilter) =
235
  if not live
236
    then return . Bad $ GenericError "Locks can only be queried live"
237
    else do
238
      socketpath <- defaultMasterSocket
239
      logDebug $ "Forwarding live query on locks for " ++ show fields
240
                   ++ ", " ++ show qfilter ++ " to " ++ socketpath
241
      cl <- L.getLuxiClient socketpath
242
      answer <- L.callMethod (L.Query (ItemTypeLuxi QRLock) fields qfilter) cl
243
      return
244
        . genericResult Bad
245
            (either (Bad . GenericError
246
                       . (++) "Got unparsable answer from masterd: ")
247
               Ok
248
             . J.resultToEither . J.readJSON)
249
        $ answer
250

    
251
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
252

    
253

    
254
-- | Dummy data collection fuction
255
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
256
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
257

    
258
-- | Inner query execution function.
259
queryInner :: ConfigData   -- ^ The current configuration
260
           -> Bool         -- ^ Whether to collect live data
261
           -> Query        -- ^ The query (item, fields, filter)
262
           -> [String]     -- ^ Requested names
263
           -> IO (ErrorResult QueryResult) -- ^ Result
264

    
265
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
266
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
267
               nodeName configNodes getNode cfg live fields qfilter wanted
268

    
269
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
270
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
271
               instName configInstances getInstance cfg live fields qfilter
272
               wanted
273

    
274
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
275
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
276
               configNodegroups getGroup cfg live fields qfilter wanted
277

    
278
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
279
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
280
               (fromNonEmpty . networkName)
281
               configNetworks getNetwork cfg live fields qfilter wanted
282

    
283
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
284
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
285
               nodeName configNodes getNode cfg live fields qfilter wanted
286

    
287
queryInner _ _ (Query qkind _ _) _ =
288
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
289

    
290
-- | Query jobs specific query function, needed as we need to accept
291
-- both 'QuotedString' and 'NumericValue' as wanted names.
292
queryJobs :: ConfigData                   -- ^ The current configuration
293
          -> Bool                         -- ^ Whether to collect live data
294
          -> [FilterField]                -- ^ Item
295
          -> Filter FilterField           -- ^ Filter
296
          -> IO (ErrorResult QueryResult) -- ^ Result
297
queryJobs cfg live fields qfilter =
298
  runResultT $ do
299
  rootdir <- lift queueDir
300
  let wanted_names = getRequestedJobIDs qfilter
301
      want_arch = Query.Job.wantArchived fields
302
  rjids <- case wanted_names of
303
             Bad msg -> resultT . Bad $ GenericError msg
304
             Ok [] -> if live
305
                        -- we can check the filesystem for actual jobs
306
                        then do
307
                          maybeJobIDs <-
308
                            lift (determineJobDirectories rootdir want_arch
309
                              >>= getJobIDs)
310
                          case maybeJobIDs of
311
                            Left e -> (resultT . Bad) . BlockDeviceError $
312
                              "Unable to fetch the job list: " ++ show e
313
                            Right jobIDs -> resultT . Ok $ sortJobIDs jobIDs
314
                        -- else we shouldn't look at the filesystem...
315
                        else return []
316
             Ok v -> resultT $ Ok v
317
  cfilter <- resultT $ compileFilter Query.Job.fieldsMap qfilter
318
  let selected = getSelectedFields Query.Job.fieldsMap fields
319
      (fdefs, fgetters, _) = unzip3 selected
320
      (_, filtergetters, _) = unzip3 . getSelectedFields Query.Job.fieldsMap
321
                                $ Foldable.toList qfilter
322
      live' = live && needsLiveData (fgetters ++ filtergetters)
323
      disabled_data = Bad "live data disabled"
324
  -- runs first pass of the filter, without a runtime context; this
325
  -- will limit the jobs that we'll load from disk
326
  jids <- resultT $
327
          filterM (\jid -> evaluateFilter cfg Nothing jid cfilter) rjids
328
  -- here we run the runtime data gathering, filtering and evaluation,
329
  -- all in the same step, so that we don't keep jobs in memory longer
330
  -- than we need; we can't be fully lazy due to the multiple monad
331
  -- wrapping across different steps
332
  qdir <- lift queueDir
333
  fdata <- foldM
334
           -- big lambda, but we use many variables from outside it...
335
           (\lst jid -> do
336
              job <- lift $ if live'
337
                              then loadJobFromDisk qdir True jid
338
                              else return disabled_data
339
              pass <- resultT $ evaluateFilter cfg (Just job) jid cfilter
340
              let nlst = if pass
341
                           then let row = map (execGetter cfg job jid) fgetters
342
                                in rnf row `seq` row:lst
343
                           else lst
344
              -- evaluate nlst (to WHNF), otherwise we're too lazy
345
              return $! nlst
346
           ) [] jids
347
  return QueryResult { qresFields = fdefs, qresData = reverse fdata }
348

    
349
-- | Helper for 'queryFields'.
350
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
351
fieldsExtractor fieldsMap fields =
352
  let selected = if null fields
353
                   then map snd . niceSortKey fst $ Map.toList fieldsMap
354
                   else getSelectedFields fieldsMap fields
355
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
356

    
357
-- | Query fields call.
358
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
359
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
360
  Ok $ fieldsExtractor Node.fieldsMap fields
361

    
362
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
363
  Ok $ fieldsExtractor Group.fieldsMap fields
364

    
365
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
366
  Ok $ fieldsExtractor Network.fieldsMap fields
367

    
368
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
369
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
370

    
371
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
372
  Ok $ fieldsExtractor Export.fieldsMap fields
373

    
374
queryFields (QueryFields (ItemTypeOpCode QRInstance) fields) =
375
  Ok $ fieldsExtractor Instance.fieldsMap fields
376

    
377
queryFields (QueryFields (ItemTypeLuxi QRLock) fields) =
378
  Ok $ fieldsExtractor Locks.fieldsMap fields
379

    
380
queryFields (QueryFields qkind _) =
381
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
382

    
383
-- | Classic query converter. It gets a standard query result on input
384
-- and computes the classic style results.
385
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
386
queryCompat (QueryResult fields qrdata) =
387
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
388
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
389
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
390
                                    intercalate ", " unknown) ECodeInval