Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ 3daaab6c

History | View | Annotate | Download (13.3 kB)

1
{-| Implementation of the Ganeti Query2 functionality.
2

    
3
 -}
4

    
5
{-
6

    
7
Copyright (C) 2012, 2013 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
{-
27

    
28
TODO: problems with the current model:
29

    
30
1. There's nothing preventing a result such as ResultEntry RSNormal
31
Nothing, or ResultEntry RSNoData (Just ...); ideally, we would
32
separate the the RSNormal and other types; we would need a new data
33
type for this, though, with JSON encoding/decoding
34

    
35
2. We don't have a way to 'bind' a FieldDefinition's field type
36
(e.q. QFTBool) with the actual value that is returned from a
37
FieldGetter. This means that the various getter functions can return
38
divergent types for the same field when evaluated against multiple
39
items. This is bad; it only works today because we 'hide' everything
40
behind JSValue, but is not nice at all. We should probably remove the
41
separation between FieldDefinition and the FieldGetter, and introduce
42
a new abstract data type, similar to QFT*, that contains the values
43
too.
44

    
45
-}
46

    
47
module Ganeti.Query.Query
48
    ( query
49
    , queryFields
50
    , queryCompat
51
    , getRequestedNames
52
    , nameField
53
    , uuidField
54
    ) where
55

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

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

    
83
-- * Helper functions
84

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

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

    
99
-- * Main query execution
100

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

    
110
-- | Check whether list of queried fields contains live fields.
111
needsLiveData :: [FieldGetter a b] -> Bool
112
needsLiveData = any isRuntimeField
113

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

    
119
-- | Computes the name field for different query types.
120
nameField :: ItemType -> FilterField
121
nameField (ItemTypeLuxi QRJob) = "id"
122
nameField (ItemTypeOpCode QRExport) = "node"
123
nameField _ = "name"
124

    
125
-- | Computes the uuid field, or the best possible substitute, for different
126
-- query types.
127
uuidField :: ItemType -> FilterField
128
uuidField (ItemTypeLuxi QRJob) = nameField (ItemTypeLuxi QRJob)
129
uuidField (ItemTypeOpCode QRExport) = nameField (ItemTypeOpCode QRExport)
130
uuidField _ = "uuid"
131

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

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

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

    
161
-- | Generic query implementation for resources that are backed by
162
-- some configuration objects.
163
genericQuery :: FieldMap a b       -- ^ Field map
164
             -> (Bool -> ConfigData -> [a] -> IO [(a, b)]) -- ^ Collector
165
             -> (a -> String)      -- ^ Object to name function
166
             -> (ConfigData -> Container a) -- ^ Get all objects from config
167
             -> (ConfigData -> String -> ErrorResult a) -- ^ Lookup object
168
             -> ConfigData         -- ^ The config to run the query against
169
             -> Bool               -- ^ Whether the query should be run live
170
             -> [String]           -- ^ List of requested fields
171
             -> Filter FilterField -- ^ Filter field
172
             -> [String]           -- ^ List of requested names
173
             -> IO (ErrorResult QueryResult)
174
genericQuery fieldsMap collector nameFn configFn getFn cfg
175
             live fields qfilter wanted =
176
  runResultT $ do
177
  cfilter <- resultT $ compileFilter fieldsMap qfilter
178
  let selected = getSelectedFields fieldsMap fields
179
      (fdefs, fgetters, _) = unzip3 selected
180
      live' = live && needsLiveData fgetters
181
  objects <- resultT $ case wanted of
182
             [] -> Ok . niceSortKey nameFn .
183
                   Map.elems . fromContainer $ configFn cfg
184
             _  -> mapM (getFn cfg) wanted
185
  -- runs first pass of the filter, without a runtime context; this
186
  -- will limit the objects that we'll contact for exports
187
  fobjects <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
188
                        objects
189
  -- here run the runtime data gathering...
190
  runtimes <- lift $ collector live' cfg fobjects
191
  -- ... then filter again the results, based on gathered runtime data
192
  let fdata = map (\(obj, runtime) ->
193
                     map (execGetter cfg runtime obj) fgetters)
194
              runtimes
195
  return QueryResult { qresFields = fdefs, qresData = fdata }
196

    
197
-- | Main query execution function.
198
query :: ConfigData   -- ^ The current configuration
199
      -> Bool         -- ^ Whether to collect live data
200
      -> Query        -- ^ The query (item, fields, filter)
201
      -> IO (ErrorResult QueryResult) -- ^ Result
202
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
203
  queryJobs cfg live fields qfilter
204
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
205

    
206
-- | Inner query execution function.
207
queryInner :: ConfigData   -- ^ The current configuration
208
           -> Bool         -- ^ Whether to collect live data
209
           -> Query        -- ^ The query (item, fields, filter)
210
           -> [String]     -- ^ Requested names
211
           -> IO (ErrorResult QueryResult) -- ^ Result
212

    
213
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
214
  genericQuery Node.fieldsMap Node.collectLiveData nodeName configNodes getNode
215
               cfg live fields qfilter wanted
216

    
217
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
218
  genericQuery Group.fieldsMap Group.collectLiveData groupName configNodegroups
219
               getGroup cfg live fields qfilter wanted
220

    
221
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
222
  genericQuery Network.fieldsMap Network.collectLiveData
223
               (fromNonEmpty . networkName)
224
               configNetworks getNetwork cfg live fields qfilter wanted
225

    
226
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
227
  genericQuery Export.fieldsMap Export.collectLiveData nodeName configNodes
228
               getNode cfg live fields qfilter wanted
229

    
230
queryInner _ _ (Query qkind _ _) _ =
231
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
232

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

    
290
-- | Helper for 'queryFields'.
291
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
292
fieldsExtractor fieldsMap fields =
293
  let selected = if null fields
294
                   then map snd $ Map.toAscList fieldsMap
295
                   else getSelectedFields fieldsMap fields
296
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
297

    
298
-- | Query fields call.
299
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
300
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
301
  Ok $ fieldsExtractor Node.fieldsMap fields
302

    
303
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
304
  Ok $ fieldsExtractor Group.fieldsMap fields
305

    
306
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
307
  Ok $ fieldsExtractor Network.fieldsMap fields
308

    
309
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
310
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
311

    
312
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
313
  Ok $ fieldsExtractor Export.fieldsMap fields
314

    
315
queryFields (QueryFields qkind _) =
316
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
317

    
318
-- | Classic query converter. It gets a standard query result on input
319
-- and computes the classic style results.
320
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
321
queryCompat (QueryResult fields qrdata) =
322
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
323
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
324
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
325
                                    intercalate ", " unknown) ECodeInval