Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ 560ef132

History | View | Annotate | Download (15.5 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, unless)
60
import Control.Monad.IO.Class
61
import Control.Monad.Trans (lift)
62
import qualified Data.Foldable as Foldable
63
import Data.List (intercalate)
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
-- | Extracts all quoted strings from a list, ignoring the
140
-- 'NumericValue' entries.
141
getAllQuotedStrings :: [FilterValue] -> [String]
142
getAllQuotedStrings =
143
  concatMap extractor
144
    where extractor (NumericValue _)   = []
145
          extractor (QuotedString val) = [val]
146

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

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

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

    
219
-- | Main query execution function.
220
query :: ConfigData   -- ^ The current configuration
221
      -> Bool         -- ^ Whether to collect live data
222
      -> Query        -- ^ The query (item, fields, filter)
223
      -> IO (ErrorResult QueryResult) -- ^ Result
224
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
225
  queryJobs cfg live fields qfilter
226
query _ live (Query (ItemTypeLuxi QRLock) fields qfilter) = runResultT $ do
227
  unless live (failError "Locks can only be queried live")
228
  cl <- liftIO $ do
229
    socketpath <- liftIO defaultMasterSocket
230
    logDebug $ "Forwarding live query on locks for " ++ show fields
231
                 ++ ", " ++ show qfilter ++ " to " ++ socketpath
232
    liftIO $ L.getLuxiClient socketpath
233
  answer <- ResultT $ L.callMethod (L.Query (ItemTypeLuxi QRLock)
234
                                            fields qfilter) cl
235
  fromJResultE "Got unparsable answer from masterd: " $ J.readJSON answer
236

    
237
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
238

    
239

    
240
-- | Dummy data collection fuction
241
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
242
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
243

    
244
-- | Inner query execution function.
245
queryInner :: ConfigData   -- ^ The current configuration
246
           -> Bool         -- ^ Whether to collect live data
247
           -> Query        -- ^ The query (item, fields, filter)
248
           -> [String]     -- ^ Requested names
249
           -> IO (ErrorResult QueryResult) -- ^ Result
250

    
251
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
252
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
253
               nodeName configNodes getNode cfg live fields qfilter wanted
254

    
255
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
256
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
257
               instName configInstances getInstance cfg live fields qfilter
258
               wanted
259

    
260
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
261
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
262
               configNodegroups getGroup cfg live fields qfilter wanted
263

    
264
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
265
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
266
               (fromNonEmpty . networkName)
267
               configNetworks getNetwork cfg live fields qfilter wanted
268

    
269
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
270
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
271
               nodeName configNodes getNode cfg live fields qfilter wanted
272

    
273
queryInner _ _ (Query qkind _ _) _ =
274
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
275

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

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

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

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

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

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

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

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

    
357
queryFields (QueryFields (ItemTypeLuxi QRLock) fields) =
358
  Ok $ fieldsExtractor Locks.fieldsMap fields
359

    
360
queryFields (QueryFields qkind _) =
361
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
362

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