root / src / Ganeti / Query / Query.hs @ d286d795
History | View | Annotate | Download (14.1 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 _ _ _ FieldUnknown = rsUnknown |
101 |
|
102 |
-- * Main query execution |
103 |
|
104 |
-- | Helper to build the list of requested fields. This transforms the |
105 |
-- list of string fields to a list of field defs and getters, with |
106 |
-- some of them possibly being unknown fields. |
107 |
getSelectedFields :: FieldMap a b -- ^ Defined fields |
108 |
-> [String] -- ^ Requested fields |
109 |
-> FieldList a b -- ^ Selected fields |
110 |
getSelectedFields defined = |
111 |
map (\name -> fromMaybe (mkUnknownFDef name) $ name `Map.lookup` defined) |
112 |
|
113 |
-- | Check whether list of queried fields contains live fields. |
114 |
needsLiveData :: [FieldGetter a b] -> Bool |
115 |
needsLiveData = any isRuntimeField |
116 |
|
117 |
-- | Checks whether we have requested exactly some names. This is a |
118 |
-- simple wrapper over 'requestedNames' and 'nameField'. |
119 |
needsNames :: Query -> Maybe [FilterValue] |
120 |
needsNames (Query kind _ qfilter) = requestedNames (nameField kind) qfilter |
121 |
|
122 |
-- | Computes the name field for different query types. |
123 |
nameField :: ItemType -> FilterField |
124 |
nameField (ItemTypeLuxi QRJob) = "id" |
125 |
nameField (ItemTypeOpCode QRExport) = "node" |
126 |
nameField _ = "name" |
127 |
|
128 |
-- | Extracts all quoted strings from a list, ignoring the |
129 |
-- 'NumericValue' entries. |
130 |
getAllQuotedStrings :: [FilterValue] -> [String] |
131 |
getAllQuotedStrings = |
132 |
concatMap extractor |
133 |
where extractor (NumericValue _) = [] |
134 |
extractor (QuotedString val) = [val] |
135 |
|
136 |
-- | Checks that we have either requested a valid set of names, or we |
137 |
-- have a more complex filter. |
138 |
getRequestedNames :: Query -> [String] |
139 |
getRequestedNames qry = |
140 |
case needsNames qry of |
141 |
Just names -> getAllQuotedStrings names |
142 |
Nothing -> [] |
143 |
|
144 |
-- | Compute the requested job IDs. This is custom since we need to |
145 |
-- handle both strings and integers. |
146 |
getRequestedJobIDs :: Filter FilterField -> Result [JobId] |
147 |
getRequestedJobIDs qfilter = |
148 |
case requestedNames (nameField (ItemTypeLuxi QRJob)) qfilter of |
149 |
Nothing -> Ok [] |
150 |
Just [] -> Ok [] |
151 |
Just vals -> |
152 |
mapM (\e -> case e of |
153 |
QuotedString s -> makeJobIdS s |
154 |
NumericValue i -> makeJobId $ fromIntegral i |
155 |
) vals |
156 |
|
157 |
-- | Generic query implementation for resources that are backed by |
158 |
-- some configuration objects. |
159 |
-- |
160 |
-- Different query types use the same 'genericQuery' function by providing |
161 |
-- a collector function and a field map. The collector function retrieves |
162 |
-- live data, and the field map provides both the requirements and the logic |
163 |
-- necessary to retrieve the data needed for the field. |
164 |
-- |
165 |
-- The 'b' type in the specification is the runtime. Every query can gather |
166 |
-- additional live data related to the configuration object using the collector |
167 |
-- to perform RPC calls. |
168 |
-- |
169 |
-- The gathered data, or the failure to get it, is expressed through a runtime |
170 |
-- object. The type of a runtime object is determined by every query type for |
171 |
-- itself, and used exclusively by that query. |
172 |
genericQuery :: FieldMap a b -- ^ Field map |
173 |
-> (Bool -> ConfigData -> [a] -> IO [(a, b)]) -- ^ Collector |
174 |
-> (a -> String) -- ^ Object to name function |
175 |
-> (ConfigData -> Container a) -- ^ Get all objects from config |
176 |
-> (ConfigData -> String -> ErrorResult a) -- ^ Lookup object |
177 |
-> ConfigData -- ^ The config to run the query against |
178 |
-> Bool -- ^ Whether the query should be run live |
179 |
-> [String] -- ^ List of requested fields |
180 |
-> Filter FilterField -- ^ Filter field |
181 |
-> [String] -- ^ List of requested names |
182 |
-> IO (ErrorResult QueryResult) |
183 |
genericQuery fieldsMap collector nameFn configFn getFn cfg |
184 |
live fields qfilter wanted = |
185 |
runResultT $ do |
186 |
cfilter <- resultT $ compileFilter fieldsMap qfilter |
187 |
let selected = getSelectedFields fieldsMap fields |
188 |
(fdefs, fgetters, _) = unzip3 selected |
189 |
live' = live && needsLiveData fgetters |
190 |
objects <- resultT $ case wanted of |
191 |
[] -> Ok . niceSortKey nameFn . |
192 |
Map.elems . fromContainer $ configFn cfg |
193 |
_ -> mapM (getFn cfg) wanted |
194 |
-- runs first pass of the filter, without a runtime context; this |
195 |
-- will limit the objects that we'll contact for exports |
196 |
fobjects <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter) |
197 |
objects |
198 |
-- here run the runtime data gathering... |
199 |
runtimes <- lift $ collector live' cfg fobjects |
200 |
-- ... then filter again the results, based on gathered runtime data |
201 |
let fdata = map (\(obj, runtime) -> |
202 |
map (execGetter cfg runtime obj) fgetters) |
203 |
runtimes |
204 |
return QueryResult { qresFields = fdefs, qresData = fdata } |
205 |
|
206 |
-- | Main query execution function. |
207 |
query :: ConfigData -- ^ The current configuration |
208 |
-> Bool -- ^ Whether to collect live data |
209 |
-> Query -- ^ The query (item, fields, filter) |
210 |
-> IO (ErrorResult QueryResult) -- ^ Result |
211 |
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) = |
212 |
queryJobs cfg live fields qfilter |
213 |
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry |
214 |
|
215 |
-- | Dummy data collection fuction |
216 |
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)] |
217 |
dummyCollectLiveData _ _ = return . map (, NoDataRuntime) |
218 |
|
219 |
-- | Inner query execution function. |
220 |
queryInner :: ConfigData -- ^ The current configuration |
221 |
-> Bool -- ^ Whether to collect live data |
222 |
-> Query -- ^ The query (item, fields, filter) |
223 |
-> [String] -- ^ Requested names |
224 |
-> IO (ErrorResult QueryResult) -- ^ Result |
225 |
|
226 |
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted = |
227 |
genericQuery Node.fieldsMap Node.collectLiveData nodeName configNodes getNode |
228 |
cfg live fields qfilter wanted |
229 |
|
230 |
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted = |
231 |
genericQuery Instance.fieldsMap dummyCollectLiveData instName |
232 |
configInstances getInstance cfg live fields qfilter wanted |
233 |
|
234 |
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted = |
235 |
genericQuery Group.fieldsMap dummyCollectLiveData groupName configNodegroups |
236 |
getGroup cfg live fields qfilter wanted |
237 |
|
238 |
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted = |
239 |
genericQuery Network.fieldsMap dummyCollectLiveData |
240 |
(fromNonEmpty . networkName) |
241 |
configNetworks getNetwork cfg live fields qfilter wanted |
242 |
|
243 |
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted = |
244 |
genericQuery Export.fieldsMap Export.collectLiveData nodeName configNodes |
245 |
getNode cfg live fields qfilter wanted |
246 |
|
247 |
queryInner _ _ (Query qkind _ _) _ = |
248 |
return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported" |
249 |
|
250 |
-- | Query jobs specific query function, needed as we need to accept |
251 |
-- both 'QuotedString' and 'NumericValue' as wanted names. |
252 |
queryJobs :: ConfigData -- ^ The current configuration |
253 |
-> Bool -- ^ Whether to collect live data |
254 |
-> [FilterField] -- ^ Item |
255 |
-> Filter FilterField -- ^ Filter |
256 |
-> IO (ErrorResult QueryResult) -- ^ Result |
257 |
queryJobs cfg live fields qfilter = |
258 |
runResultT $ do |
259 |
rootdir <- lift queueDir |
260 |
let wanted_names = getRequestedJobIDs qfilter |
261 |
want_arch = Query.Job.wantArchived fields |
262 |
rjids <- case wanted_names of |
263 |
Bad msg -> resultT . Bad $ GenericError msg |
264 |
Ok [] -> if live |
265 |
-- we can check the filesystem for actual jobs |
266 |
then do |
267 |
maybeJobIDs <- |
268 |
lift (determineJobDirectories rootdir want_arch |
269 |
>>= getJobIDs) |
270 |
case maybeJobIDs of |
271 |
Left e -> (resultT . Bad) . BlockDeviceError $ |
272 |
"Unable to fetch the job list: " ++ show e |
273 |
Right jobIDs -> resultT . Ok $ sortJobIDs jobIDs |
274 |
-- else we shouldn't look at the filesystem... |
275 |
else return [] |
276 |
Ok v -> resultT $ Ok v |
277 |
cfilter <- resultT $ compileFilter Query.Job.fieldsMap qfilter |
278 |
let selected = getSelectedFields Query.Job.fieldsMap fields |
279 |
(fdefs, fgetters, _) = unzip3 selected |
280 |
live' = live && needsLiveData fgetters |
281 |
disabled_data = Bad "live data disabled" |
282 |
-- runs first pass of the filter, without a runtime context; this |
283 |
-- will limit the jobs that we'll load from disk |
284 |
jids <- resultT $ |
285 |
filterM (\jid -> evaluateFilter cfg Nothing jid cfilter) rjids |
286 |
-- here we run the runtime data gathering, filtering and evaluation, |
287 |
-- all in the same step, so that we don't keep jobs in memory longer |
288 |
-- than we need; we can't be fully lazy due to the multiple monad |
289 |
-- wrapping across different steps |
290 |
qdir <- lift queueDir |
291 |
fdata <- foldM |
292 |
-- big lambda, but we use many variables from outside it... |
293 |
(\lst jid -> do |
294 |
job <- lift $ if live' |
295 |
then loadJobFromDisk qdir True jid |
296 |
else return disabled_data |
297 |
pass <- resultT $ evaluateFilter cfg (Just job) jid cfilter |
298 |
let nlst = if pass |
299 |
then let row = map (execGetter cfg job jid) fgetters |
300 |
in rnf row `seq` row:lst |
301 |
else lst |
302 |
-- evaluate nlst (to WHNF), otherwise we're too lazy |
303 |
return $! nlst |
304 |
) [] jids |
305 |
return QueryResult { qresFields = fdefs, qresData = reverse fdata } |
306 |
|
307 |
-- | Helper for 'queryFields'. |
308 |
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult |
309 |
fieldsExtractor fieldsMap fields = |
310 |
let selected = if null fields |
311 |
then map snd $ Map.toAscList fieldsMap |
312 |
else getSelectedFields fieldsMap fields |
313 |
in QueryFieldsResult (map (\(defs, _, _) -> defs) selected) |
314 |
|
315 |
-- | Query fields call. |
316 |
queryFields :: QueryFields -> ErrorResult QueryFieldsResult |
317 |
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) = |
318 |
Ok $ fieldsExtractor Node.fieldsMap fields |
319 |
|
320 |
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) = |
321 |
Ok $ fieldsExtractor Group.fieldsMap fields |
322 |
|
323 |
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) = |
324 |
Ok $ fieldsExtractor Network.fieldsMap fields |
325 |
|
326 |
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) = |
327 |
Ok $ fieldsExtractor Query.Job.fieldsMap fields |
328 |
|
329 |
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) = |
330 |
Ok $ fieldsExtractor Export.fieldsMap fields |
331 |
|
332 |
queryFields (QueryFields qkind _) = |
333 |
Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported" |
334 |
|
335 |
-- | Classic query converter. It gets a standard query result on input |
336 |
-- and computes the classic style results. |
337 |
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]] |
338 |
queryCompat (QueryResult fields qrdata) = |
339 |
case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of |
340 |
[] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata |
341 |
unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++ |
342 |
intercalate ", " unknown) ECodeInval |