Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Query.hs @ a7e484c4

History | View | Annotate | Download (12 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, liftM, 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.Rpc
69
import Ganeti.Objects
70
import Ganeti.Query.Common
71
import Ganeti.Query.Filter
72
import qualified Ganeti.Query.Job as Query.Job
73
import Ganeti.Query.Group
74
import Ganeti.Query.Language
75
import Ganeti.Query.Node
76
import Ganeti.Query.Types
77
import Ganeti.Path
78
import Ganeti.Types
79
import Ganeti.Utils
80

    
81
-- * Helper functions
82

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

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

    
97
-- * Main query execution
98

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

    
108
-- | Collect live data from RPC query if enabled.
109
-- FIXME: Check which fields we actually need and possibly send empty
110
-- hvs/vgs if no info from hypervisor/volume group respectively
111
-- is required
112
maybeCollectLiveData:: Bool -> ConfigData -> [Node] -> IO [(Node, NodeRuntime)]
113

    
114
maybeCollectLiveData False _ nodes =
115
  return $ zip nodes (repeat $ Left (RpcResultError "Live data disabled"))
116

    
117
maybeCollectLiveData True cfg nodes = do
118
  let vgs = [clusterVolumeGroupName $ configCluster cfg]
119
      hvs = [getDefaultHypervisor cfg]
120
  executeRpcCall nodes (RpcCallNodeInfo vgs hvs)
121

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

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

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

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

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

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

    
165
-- | Main query execution function.
166
query :: ConfigData   -- ^ The current configuration
167
      -> Bool         -- ^ Whether to collect live data
168
      -> Query        -- ^ The query (item, fields, filter)
169
      -> IO (ErrorResult QueryResult) -- ^ Result
170
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
171
  queryJobs cfg live fields qfilter
172
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
173

    
174
-- | Inner query execution function.
175
queryInner :: ConfigData   -- ^ The current configuration
176
           -> Bool         -- ^ Whether to collect live data
177
           -> Query        -- ^ The query (item, fields, filter)
178
           -> [String]     -- ^ Requested names
179
           -> IO (ErrorResult QueryResult) -- ^ Result
180

    
181
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
182
  runResultT $ do
183
  cfilter <- resultT $ compileFilter nodeFieldsMap qfilter
184
  let selected = getSelectedFields nodeFieldsMap fields
185
      (fdefs, fgetters, _) = unzip3 selected
186
      live' = live && needsLiveData fgetters
187
  nodes <- resultT $ case wanted of
188
             [] -> Ok . niceSortKey nodeName .
189
                   Map.elems . fromContainer $ configNodes cfg
190
             _  -> mapM (getNode cfg) wanted
191
  -- runs first pass of the filter, without a runtime context; this
192
  -- will limit the nodes that we'll contact for runtime data
193
  fnodes <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
194
                      nodes
195
  -- here we would run the runtime data gathering, then filter again
196
  -- the nodes, based on existing runtime data
197
  nruntimes <- lift $ maybeCollectLiveData live' cfg fnodes
198
  let fdata = map (\(node, nrt) -> map (execGetter cfg nrt node) fgetters)
199
              nruntimes
200
  return QueryResult { qresFields = fdefs, qresData = fdata }
201

    
202
queryInner cfg _ (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
203
  return $ do
204
  cfilter <- compileFilter groupFieldsMap qfilter
205
  let selected = getSelectedFields groupFieldsMap fields
206
      (fdefs, fgetters, _) = unzip3 selected
207
  groups <- case wanted of
208
              [] -> Ok . niceSortKey groupName .
209
                    Map.elems . fromContainer $ configNodegroups cfg
210
              _  -> mapM (getGroup cfg) wanted
211
  -- there is no live data for groups, so filtering is much simpler
212
  fgroups <- filterM (\n -> evaluateFilter cfg Nothing n cfilter) groups
213
  let fdata = map (\node ->
214
                       map (execGetter cfg GroupRuntime node) fgetters) fgroups
215
  return QueryResult {qresFields = fdefs, qresData = fdata }
216

    
217
queryInner _ _ (Query qkind _ _) _ =
218
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
219

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

    
272
-- | Helper for 'queryFields'.
273
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
274
fieldsExtractor fieldsMap fields =
275
  let selected = if null fields
276
                   then map snd $ Map.toAscList fieldsMap
277
                   else getSelectedFields fieldsMap fields
278
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
279

    
280
-- | Query fields call.
281
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
282
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
283
  Ok $ fieldsExtractor nodeFieldsMap fields
284

    
285
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
286
  Ok $ fieldsExtractor groupFieldsMap fields
287

    
288
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
289
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
290

    
291
queryFields (QueryFields qkind _) =
292
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
293

    
294
-- | Classic query converter. It gets a standard query result on input
295
-- and computes the classic style results.
296
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
297
queryCompat (QueryResult fields qrdata) =
298
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
299
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
300
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
301
                                    intercalate ", " unknown) ECodeInval