Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (11.6 kB)

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

    
3
 -}
4

    
5
{-
6

    
7
Copyright (C) 2012 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
    ) where
54

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

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

    
80
-- * Helper functions
81

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

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

    
96
-- * Main query execution
97

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

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

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

    
116
-- | Computes the name field for different query types.
117
nameField :: ItemType -> FilterField
118
nameField (ItemTypeLuxi QRJob) = "id"
119
nameField _ = "name"
120

    
121
-- | Extracts all quoted strings from a list, ignoring the
122
-- 'NumericValue' entries.
123
getAllQuotedStrings :: [FilterValue] -> [String]
124
getAllQuotedStrings =
125
  concatMap extractor
126
    where extractor (NumericValue _)   = []
127
          extractor (QuotedString val) = [val]
128

    
129
-- | Checks that we have either requested a valid set of names, or we
130
-- have a more complex filter.
131
getRequestedNames :: Query -> [String]
132
getRequestedNames qry =
133
  case needsNames qry of
134
    Just names -> getAllQuotedStrings names
135
    Nothing    -> []
136

    
137
-- | Compute the requested job IDs. This is custom since we need to
138
-- handle both strings and integers.
139
getRequestedJobIDs :: Filter FilterField -> Result [JobId]
140
getRequestedJobIDs qfilter =
141
  case requestedNames (nameField (ItemTypeLuxi QRJob)) qfilter of
142
    Nothing -> Ok []
143
    Just [] -> Ok []
144
    Just vals ->
145
      mapM (\e -> case e of
146
                    QuotedString s -> makeJobIdS s
147
                    NumericValue i -> makeJobId $ fromIntegral i
148
           ) vals
149

    
150
-- | Main query execution function.
151
query :: ConfigData   -- ^ The current configuration
152
      -> Bool         -- ^ Whether to collect live data
153
      -> Query        -- ^ The query (item, fields, filter)
154
      -> IO (ErrorResult QueryResult) -- ^ Result
155
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
156
  queryJobs cfg live fields qfilter
157
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
158

    
159
-- | Inner query execution function.
160
queryInner :: ConfigData   -- ^ The current configuration
161
           -> Bool         -- ^ Whether to collect live data
162
           -> Query        -- ^ The query (item, fields, filter)
163
           -> [String]     -- ^ Requested names
164
           -> IO (ErrorResult QueryResult) -- ^ Result
165

    
166
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
167
  runResultT $ do
168
  cfilter <- resultT $ compileFilter nodeFieldsMap qfilter
169
  let selected = getSelectedFields nodeFieldsMap fields
170
      (fdefs, fgetters, _) = unzip3 selected
171
      live' = live && needsLiveData fgetters
172
  nodes <- resultT $ case wanted of
173
             [] -> Ok . niceSortKey nodeName .
174
                   Map.elems . fromContainer $ configNodes cfg
175
             _  -> mapM (getNode cfg) wanted
176
  -- runs first pass of the filter, without a runtime context; this
177
  -- will limit the nodes that we'll contact for runtime data
178
  fnodes <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
179
                      nodes
180
  -- here we would run the runtime data gathering, then filter again
181
  -- the nodes, based on existing runtime data
182
  nruntimes <- lift $ maybeCollectLiveData live' cfg fnodes
183
  let fdata = map (\(node, nrt) -> map (execGetter cfg nrt node) fgetters)
184
              nruntimes
185
  return QueryResult { qresFields = fdefs, qresData = fdata }
186

    
187
queryInner cfg _ (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
188
  return $ do
189
  cfilter <- compileFilter groupFieldsMap qfilter
190
  let selected = getSelectedFields groupFieldsMap fields
191
      (fdefs, fgetters, _) = unzip3 selected
192
  groups <- case wanted of
193
              [] -> Ok . niceSortKey groupName .
194
                    Map.elems . fromContainer $ configNodegroups cfg
195
              _  -> mapM (getGroup cfg) wanted
196
  -- there is no live data for groups, so filtering is much simpler
197
  fgroups <- filterM (\n -> evaluateFilter cfg Nothing n cfilter) groups
198
  let fdata = map (\node ->
199
                       map (execGetter cfg GroupRuntime node) fgetters) fgroups
200
  return QueryResult {qresFields = fdefs, qresData = fdata }
201

    
202
queryInner _ _ (Query qkind _ _) _ =
203
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
204

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

    
262
-- | Helper for 'queryFields'.
263
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
264
fieldsExtractor fieldsMap fields =
265
  let selected = if null fields
266
                   then map snd $ Map.toAscList fieldsMap
267
                   else getSelectedFields fieldsMap fields
268
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
269

    
270
-- | Query fields call.
271
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
272
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
273
  Ok $ fieldsExtractor nodeFieldsMap fields
274

    
275
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
276
  Ok $ fieldsExtractor groupFieldsMap fields
277

    
278
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
279
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
280

    
281
queryFields (QueryFields qkind _) =
282
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
283

    
284
-- | Classic query converter. It gets a standard query result on input
285
-- and computes the classic style results.
286
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
287
queryCompat (QueryResult fields qrdata) =
288
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
289
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
290
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
291
                                    intercalate ", " unknown) ECodeInval