Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (15.3 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.Objects
74
import Ganeti.Query.Common
75
import qualified Ganeti.Query.Export as Export
76
import Ganeti.Query.Filter
77
import qualified Ganeti.Query.Instance as Instance
78
import qualified Ganeti.Query.Job as Query.Job
79
import qualified Ganeti.Query.Group as Group
80
import Ganeti.Query.Language
81
import qualified Ganeti.Query.Network as Network
82
import qualified Ganeti.Query.Node as Node
83
import Ganeti.Query.Types
84
import Ganeti.Path
85
import Ganeti.Types
86
import Ganeti.Utils
87

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

    
93
-- * Helper functions
94

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

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

    
110
-- * Main query execution
111

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

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

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

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

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

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

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

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

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

    
224
-- | Main query execution function.
225
query :: ConfigData   -- ^ The current configuration
226
      -> Bool         -- ^ Whether to collect live data
227
      -> Query        -- ^ The query (item, fields, filter)
228
      -> IO (ErrorResult QueryResult) -- ^ Result
229
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
230
  queryJobs cfg live fields qfilter
231
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
232

    
233
-- | Dummy data collection fuction
234
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
235
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
236

    
237
-- | Inner query execution function.
238
queryInner :: ConfigData   -- ^ The current configuration
239
           -> Bool         -- ^ Whether to collect live data
240
           -> Query        -- ^ The query (item, fields, filter)
241
           -> [String]     -- ^ Requested names
242
           -> IO (ErrorResult QueryResult) -- ^ Result
243

    
244
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
245
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
246
               nodeName configNodes getNode cfg live fields qfilter wanted
247

    
248
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
249
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
250
               instName configInstances getInstance cfg live fields qfilter
251
               wanted
252

    
253
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
254
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
255
               configNodegroups getGroup cfg live fields qfilter wanted
256

    
257
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
258
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
259
               (fromNonEmpty . networkName)
260
               configNetworks getNetwork cfg live fields qfilter wanted
261

    
262
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
263
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
264
               nodeName configNodes getNode cfg live fields qfilter wanted
265

    
266
queryInner _ _ (Query qkind _ _) _ =
267
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
268

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

    
328
-- | Helper for 'queryFields'.
329
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
330
fieldsExtractor fieldsMap fields =
331
  let selected = if null fields
332
                   then map snd . niceSortKey fst $ Map.toList fieldsMap
333
                   else getSelectedFields fieldsMap fields
334
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
335

    
336
-- | Query fields call.
337
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
338
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
339
  Ok $ fieldsExtractor Node.fieldsMap fields
340

    
341
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
342
  Ok $ fieldsExtractor Group.fieldsMap fields
343

    
344
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
345
  Ok $ fieldsExtractor Network.fieldsMap fields
346

    
347
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
348
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
349

    
350
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
351
  Ok $ fieldsExtractor Export.fieldsMap fields
352

    
353
queryFields (QueryFields (ItemTypeOpCode QRInstance) fields) =
354
  Ok $ fieldsExtractor Instance.fieldsMap fields
355

    
356

    
357
queryFields (QueryFields qkind _) =
358
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
359

    
360
-- | Classic query converter. It gets a standard query result on input
361
-- and computes the classic style results.
362
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
363
queryCompat (QueryResult fields qrdata) =
364
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
365
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
366
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
367
                                    intercalate ", " unknown) ECodeInval