Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ 178ad717

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

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

    
92
-- * Helper functions
93

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

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

    
109
-- * Main query execution
110

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

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

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

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

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

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

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

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

    
215
-- | Main query execution function.
216
query :: ConfigData   -- ^ The current configuration
217
      -> Bool         -- ^ Whether to collect live data
218
      -> Query        -- ^ The query (item, fields, filter)
219
      -> IO (ErrorResult QueryResult) -- ^ Result
220
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
221
  queryJobs cfg live fields qfilter
222
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
223

    
224
-- | Dummy data collection fuction
225
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
226
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
227

    
228
-- | Inner query execution function.
229
queryInner :: ConfigData   -- ^ The current configuration
230
           -> Bool         -- ^ Whether to collect live data
231
           -> Query        -- ^ The query (item, fields, filter)
232
           -> [String]     -- ^ Requested names
233
           -> IO (ErrorResult QueryResult) -- ^ Result
234

    
235
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
236
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
237
               nodeName configNodes getNode cfg live fields qfilter wanted
238

    
239
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
240
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
241
               instName configInstances getInstance cfg live fields qfilter
242
               wanted
243

    
244
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
245
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
246
               configNodegroups getGroup cfg live fields qfilter wanted
247

    
248
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
249
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
250
               (fromNonEmpty . networkName)
251
               configNetworks getNetwork cfg live fields qfilter wanted
252

    
253
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
254
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
255
               nodeName configNodes getNode cfg live fields qfilter wanted
256

    
257
queryInner _ _ (Query qkind _ _) _ =
258
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
259

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

    
319
-- | Helper for 'queryFields'.
320
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
321
fieldsExtractor fieldsMap fields =
322
  let selected = if null fields
323
                   then map snd . niceSortKey fst $ Map.toList fieldsMap
324
                   else getSelectedFields fieldsMap fields
325
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
326

    
327
-- | Query fields call.
328
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
329
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
330
  Ok $ fieldsExtractor Node.fieldsMap fields
331

    
332
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
333
  Ok $ fieldsExtractor Group.fieldsMap fields
334

    
335
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
336
  Ok $ fieldsExtractor Network.fieldsMap fields
337

    
338
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
339
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
340

    
341
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
342
  Ok $ fieldsExtractor Export.fieldsMap fields
343

    
344
queryFields (QueryFields (ItemTypeOpCode QRInstance) fields) =
345
  Ok $ fieldsExtractor Instance.fieldsMap fields
346

    
347

    
348
queryFields (QueryFields qkind _) =
349
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
350

    
351
-- | Classic query converter. It gets a standard query result on input
352
-- and computes the classic style results.
353
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
354
queryCompat (QueryResult fields qrdata) =
355
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
356
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
357
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
358
                                    intercalate ", " unknown) ECodeInval