Statistics
| Branch: | Tag: | Revision:

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

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

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

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

    
86
-- * Helper functions
87

    
88
-- | Builds an unknown field definition.
89
mkUnknownFDef :: String -> FieldData a b
90
mkUnknownFDef name =
91
  ( FieldDefinition name name QFTUnknown ("Unknown field '" ++ name ++ "'")
92
  , FieldUnknown
93
  , QffNormal )
94

    
95
-- | Runs a field getter on the existing contexts.
96
execGetter :: ConfigData -> b -> a -> FieldGetter a b -> ResultEntry
97
execGetter _   _  item (FieldSimple getter)        = getter item
98
execGetter cfg _  item (FieldConfig getter)        = getter cfg item
99
execGetter _   rt item (FieldRuntime getter)       = getter rt item
100
execGetter cfg rt item (FieldConfigRuntime getter) = getter cfg rt item
101
execGetter _   _  _    FieldUnknown                = rsUnknown
102

    
103
-- * Main query execution
104

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

    
114
-- | Check whether list of queried fields contains live fields.
115
needsLiveData :: [FieldGetter a b] -> Bool
116
needsLiveData = any isRuntimeField
117

    
118
-- | Checks whether we have requested exactly some names. This is a
119
-- simple wrapper over 'requestedNames' and 'nameField'.
120
needsNames :: Query -> Maybe [FilterValue]
121
needsNames (Query kind _ qfilter) = requestedNames (nameField kind) qfilter
122

    
123
-- | Computes the name field for different query types.
124
nameField :: ItemType -> FilterField
125
nameField (ItemTypeLuxi QRJob) = "id"
126
nameField (ItemTypeOpCode QRExport) = "node"
127
nameField _ = "name"
128

    
129
-- | Extracts all quoted strings from a list, ignoring the
130
-- 'NumericValue' entries.
131
getAllQuotedStrings :: [FilterValue] -> [String]
132
getAllQuotedStrings =
133
  concatMap extractor
134
    where extractor (NumericValue _)   = []
135
          extractor (QuotedString val) = [val]
136

    
137
-- | Checks that we have either requested a valid set of names, or we
138
-- have a more complex filter.
139
getRequestedNames :: Query -> [String]
140
getRequestedNames qry =
141
  case needsNames qry of
142
    Just names -> getAllQuotedStrings names
143
    Nothing    -> []
144

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

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

    
207
-- | Main query execution function.
208
query :: ConfigData   -- ^ The current configuration
209
      -> Bool         -- ^ Whether to collect live data
210
      -> Query        -- ^ The query (item, fields, filter)
211
      -> IO (ErrorResult QueryResult) -- ^ Result
212
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
213
  queryJobs cfg live fields qfilter
214
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
215

    
216
-- | Dummy data collection fuction
217
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
218
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
219

    
220
-- | Inner query execution function.
221
queryInner :: ConfigData   -- ^ The current configuration
222
           -> Bool         -- ^ Whether to collect live data
223
           -> Query        -- ^ The query (item, fields, filter)
224
           -> [String]     -- ^ Requested names
225
           -> IO (ErrorResult QueryResult) -- ^ Result
226

    
227
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
228
  genericQuery Node.fieldsMap Node.collectLiveData nodeName configNodes getNode
229
               cfg live fields qfilter wanted
230

    
231
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
232
  genericQuery Instance.fieldsMap Instance.collectLiveData instName
233
               configInstances getInstance cfg live fields qfilter wanted
234

    
235
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
236
  genericQuery Group.fieldsMap dummyCollectLiveData groupName configNodegroups
237
               getGroup cfg live fields qfilter wanted
238

    
239
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
240
  genericQuery Network.fieldsMap dummyCollectLiveData
241
               (fromNonEmpty . networkName)
242
               configNetworks getNetwork cfg live fields qfilter wanted
243

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

    
248
queryInner _ _ (Query qkind _ _) _ =
249
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
250

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

    
308
-- | Helper for 'queryFields'.
309
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
310
fieldsExtractor fieldsMap fields =
311
  let selected = if null fields
312
                   then map snd $ Map.toAscList fieldsMap
313
                   else getSelectedFields fieldsMap fields
314
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
315

    
316
-- | Query fields call.
317
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
318
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
319
  Ok $ fieldsExtractor Node.fieldsMap fields
320

    
321
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
322
  Ok $ fieldsExtractor Group.fieldsMap fields
323

    
324
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
325
  Ok $ fieldsExtractor Network.fieldsMap fields
326

    
327
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
328
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
329

    
330
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
331
  Ok $ fieldsExtractor Export.fieldsMap fields
332

    
333
queryFields (QueryFields qkind _) =
334
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
335

    
336
-- | Classic query converter. It gets a standard query result on input
337
-- and computes the classic style results.
338
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
339
queryCompat (QueryResult fields qrdata) =
340
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
341
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
342
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
343
                                    intercalate ", " unknown) ECodeInval