Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ ea7032da

History | View | Annotate | Download (15.8 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
    ) where
57

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

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

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

    
95
-- * Helper functions
96

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

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

    
112
-- * Main query execution
113

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

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

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

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

    
138
-- | Extracts all quoted strings from a list, ignoring the
139
-- 'NumericValue' entries.
140
getAllQuotedStrings :: [FilterValue] -> [String]
141
getAllQuotedStrings =
142
  concatMap extractor
143
    where extractor (NumericValue _)   = []
144
          extractor (QuotedString val) = [val]
145

    
146
-- | Checks that we have either requested a valid set of names, or we
147
-- have a more complex filter.
148
getRequestedNames :: Query -> [String]
149
getRequestedNames qry =
150
  case needsNames qry of
151
    Just names -> getAllQuotedStrings names
152
    Nothing    -> []
153

    
154
-- | Compute the requested job IDs. This is custom since we need to
155
-- handle both strings and integers.
156
getRequestedJobIDs :: Filter FilterField -> Result [JobId]
157
getRequestedJobIDs qfilter =
158
  case requestedNames (nameField (ItemTypeLuxi QRJob)) qfilter of
159
    Nothing -> Ok []
160
    Just [] -> Ok []
161
    Just vals ->
162
      mapM (\e -> case e of
163
                    QuotedString s -> makeJobIdS s
164
                    NumericValue i -> makeJobId $ fromIntegral i
165
           ) vals
166

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

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

    
242
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
243

    
244

    
245
-- | Dummy data collection fuction
246
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
247
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
248

    
249
-- | Inner query execution function.
250
queryInner :: ConfigData   -- ^ The current configuration
251
           -> Bool         -- ^ Whether to collect live data
252
           -> Query        -- ^ The query (item, fields, filter)
253
           -> [String]     -- ^ Requested names
254
           -> IO (ErrorResult QueryResult) -- ^ Result
255

    
256
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
257
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
258
               nodeName configNodes getNode cfg live fields qfilter wanted
259

    
260
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
261
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
262
               instName configInstances getInstance cfg live fields qfilter
263
               wanted
264

    
265
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
266
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
267
               configNodegroups getGroup cfg live fields qfilter wanted
268

    
269
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
270
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
271
               (fromNonEmpty . networkName)
272
               configNetworks getNetwork cfg live fields qfilter wanted
273

    
274
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
275
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
276
               nodeName configNodes getNode cfg live fields qfilter wanted
277

    
278
queryInner _ _ (Query qkind _ _) _ =
279
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
280

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

    
340
-- | Helper for 'queryFields'.
341
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
342
fieldsExtractor fieldsMap fields =
343
  let selected = if null fields
344
                   then map snd . niceSortKey fst $ Map.toList fieldsMap
345
                   else getSelectedFields fieldsMap fields
346
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
347

    
348
-- | Query fields call.
349
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
350
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
351
  Ok $ fieldsExtractor Node.fieldsMap fields
352

    
353
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
354
  Ok $ fieldsExtractor Group.fieldsMap fields
355

    
356
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
357
  Ok $ fieldsExtractor Network.fieldsMap fields
358

    
359
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
360
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
361

    
362
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
363
  Ok $ fieldsExtractor Export.fieldsMap fields
364

    
365
queryFields (QueryFields (ItemTypeOpCode QRInstance) fields) =
366
  Ok $ fieldsExtractor Instance.fieldsMap fields
367

    
368
queryFields (QueryFields (ItemTypeLuxi QRLock) fields) =
369
  Ok $ fieldsExtractor Locks.fieldsMap fields
370

    
371
queryFields (QueryFields qkind _) =
372
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
373

    
374
-- | Classic query converter. It gets a standard query result on input
375
-- and computes the classic style results.
376
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
377
queryCompat (QueryResult fields qrdata) =
378
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
379
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
380
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
381
                                    intercalate ", " unknown) ECodeInval