Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (14.7 kB)

1 d286d795 Hrvoje Ribicic
{-# LANGUAGE TupleSections #-}
2 d286d795 Hrvoje Ribicic
3 4cbe9bda Iustin Pop
{-| Implementation of the Ganeti Query2 functionality.
4 4cbe9bda Iustin Pop
5 4cbe9bda Iustin Pop
 -}
6 4cbe9bda Iustin Pop
7 4cbe9bda Iustin Pop
{-
8 4cbe9bda Iustin Pop
9 c4bf507b Iustin Pop
Copyright (C) 2012, 2013 Google Inc.
10 4cbe9bda Iustin Pop
11 4cbe9bda Iustin Pop
This program is free software; you can redistribute it and/or modify
12 4cbe9bda Iustin Pop
it under the terms of the GNU General Public License as published by
13 4cbe9bda Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 4cbe9bda Iustin Pop
(at your option) any later version.
15 4cbe9bda Iustin Pop
16 4cbe9bda Iustin Pop
This program is distributed in the hope that it will be useful, but
17 4cbe9bda Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 4cbe9bda Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 4cbe9bda Iustin Pop
General Public License for more details.
20 4cbe9bda Iustin Pop
21 4cbe9bda Iustin Pop
You should have received a copy of the GNU General Public License
22 4cbe9bda Iustin Pop
along with this program; if not, write to the Free Software
23 4cbe9bda Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 4cbe9bda Iustin Pop
02110-1301, USA.
25 4cbe9bda Iustin Pop
26 4cbe9bda Iustin Pop
-}
27 4cbe9bda Iustin Pop
28 8a65c02b Iustin Pop
{-
29 8a65c02b Iustin Pop
30 8a65c02b Iustin Pop
TODO: problems with the current model:
31 8a65c02b Iustin Pop
32 8a65c02b Iustin Pop
1. There's nothing preventing a result such as ResultEntry RSNormal
33 8a65c02b Iustin Pop
Nothing, or ResultEntry RSNoData (Just ...); ideally, we would
34 8a65c02b Iustin Pop
separate the the RSNormal and other types; we would need a new data
35 8a65c02b Iustin Pop
type for this, though, with JSON encoding/decoding
36 8a65c02b Iustin Pop
37 8a65c02b Iustin Pop
2. We don't have a way to 'bind' a FieldDefinition's field type
38 8a65c02b Iustin Pop
(e.q. QFTBool) with the actual value that is returned from a
39 8a65c02b Iustin Pop
FieldGetter. This means that the various getter functions can return
40 8a65c02b Iustin Pop
divergent types for the same field when evaluated against multiple
41 8a65c02b Iustin Pop
items. This is bad; it only works today because we 'hide' everything
42 8a65c02b Iustin Pop
behind JSValue, but is not nice at all. We should probably remove the
43 8a65c02b Iustin Pop
separation between FieldDefinition and the FieldGetter, and introduce
44 8a65c02b Iustin Pop
a new abstract data type, similar to QFT*, that contains the values
45 8a65c02b Iustin Pop
too.
46 8a65c02b Iustin Pop
47 8a65c02b Iustin Pop
-}
48 8a65c02b Iustin Pop
49 4cbe9bda Iustin Pop
module Ganeti.Query.Query
50 4cbe9bda Iustin Pop
    ( query
51 518023a9 Iustin Pop
    , queryFields
52 cd67e337 Iustin Pop
    , queryCompat
53 bc4cdeef Iustin Pop
    , getRequestedNames
54 cd67e337 Iustin Pop
    , nameField
55 d286d795 Hrvoje Ribicic
    , NoDataRuntime
56 4cbe9bda Iustin Pop
    ) where
57 4cbe9bda Iustin Pop
58 a7e484c4 Iustin Pop
import Control.DeepSeq
59 be0cb2d7 Michele Tartara
import Control.Monad (filterM, foldM)
60 7f0fd838 Agata Murawska
import Control.Monad.Trans (lift)
61 cd67e337 Iustin Pop
import Data.List (intercalate)
62 046fe3f5 Iustin Pop
import Data.Maybe (fromMaybe)
63 046fe3f5 Iustin Pop
import qualified Data.Map as Map
64 cd67e337 Iustin Pop
import qualified Text.JSON as J
65 046fe3f5 Iustin Pop
66 4cbe9bda Iustin Pop
import Ganeti.BasicTypes
67 0ec87781 Iustin Pop
import Ganeti.Config
68 a7e484c4 Iustin Pop
import Ganeti.Errors
69 a7e484c4 Iustin Pop
import Ganeti.JQueue
70 f3baf5ef Iustin Pop
import Ganeti.JSON
71 a7e484c4 Iustin Pop
import Ganeti.Objects
72 046fe3f5 Iustin Pop
import Ganeti.Query.Common
73 c4bf507b Iustin Pop
import qualified Ganeti.Query.Export as Export
74 8a65c02b Iustin Pop
import Ganeti.Query.Filter
75 1df0266e Hrvoje Ribicic
import qualified Ganeti.Query.Instance as Instance
76 a7e484c4 Iustin Pop
import qualified Ganeti.Query.Job as Query.Job
77 36162faf Iustin Pop
import qualified Ganeti.Query.Group as Group
78 a7e484c4 Iustin Pop
import Ganeti.Query.Language
79 36162faf Iustin Pop
import qualified Ganeti.Query.Network as Network
80 36162faf Iustin Pop
import qualified Ganeti.Query.Node as Node
81 a7e484c4 Iustin Pop
import Ganeti.Query.Types
82 a7e484c4 Iustin Pop
import Ganeti.Path
83 a7e484c4 Iustin Pop
import Ganeti.Types
84 a41c337e Iustin Pop
import Ganeti.Utils
85 4cbe9bda Iustin Pop
86 ee8bb326 Hrvoje Ribicic
-- | Collector type
87 ee8bb326 Hrvoje Ribicic
data CollectorType a b
88 ee8bb326 Hrvoje Ribicic
  = CollectorSimple     (Bool -> ConfigData -> [a] -> IO [(a, b)])
89 ee8bb326 Hrvoje Ribicic
  | CollectorFieldAware (Bool -> ConfigData -> [String] -> [a] -> IO [(a, b)])
90 ee8bb326 Hrvoje Ribicic
91 046fe3f5 Iustin Pop
-- * Helper functions
92 046fe3f5 Iustin Pop
93 046fe3f5 Iustin Pop
-- | Builds an unknown field definition.
94 046fe3f5 Iustin Pop
mkUnknownFDef :: String -> FieldData a b
95 046fe3f5 Iustin Pop
mkUnknownFDef name =
96 046fe3f5 Iustin Pop
  ( FieldDefinition name name QFTUnknown ("Unknown field '" ++ name ++ "'")
97 f94a9680 Iustin Pop
  , FieldUnknown
98 f94a9680 Iustin Pop
  , QffNormal )
99 046fe3f5 Iustin Pop
100 046fe3f5 Iustin Pop
-- | Runs a field getter on the existing contexts.
101 046fe3f5 Iustin Pop
execGetter :: ConfigData -> b -> a -> FieldGetter a b -> ResultEntry
102 11d09d75 Hrvoje Ribicic
execGetter _   _  item (FieldSimple getter)        = getter item
103 11d09d75 Hrvoje Ribicic
execGetter cfg _  item (FieldConfig getter)        = getter cfg item
104 11d09d75 Hrvoje Ribicic
execGetter _   rt item (FieldRuntime getter)       = getter rt item
105 11d09d75 Hrvoje Ribicic
execGetter cfg rt item (FieldConfigRuntime getter) = getter cfg rt item
106 11d09d75 Hrvoje Ribicic
execGetter _   _  _    FieldUnknown                = rsUnknown
107 046fe3f5 Iustin Pop
108 046fe3f5 Iustin Pop
-- * Main query execution
109 046fe3f5 Iustin Pop
110 046fe3f5 Iustin Pop
-- | Helper to build the list of requested fields. This transforms the
111 046fe3f5 Iustin Pop
-- list of string fields to a list of field defs and getters, with
112 046fe3f5 Iustin Pop
-- some of them possibly being unknown fields.
113 046fe3f5 Iustin Pop
getSelectedFields :: FieldMap a b  -- ^ Defined fields
114 046fe3f5 Iustin Pop
                  -> [String]      -- ^ Requested fields
115 046fe3f5 Iustin Pop
                  -> FieldList a b -- ^ Selected fields
116 046fe3f5 Iustin Pop
getSelectedFields defined =
117 046fe3f5 Iustin Pop
  map (\name -> fromMaybe (mkUnknownFDef name) $ name `Map.lookup` defined)
118 046fe3f5 Iustin Pop
119 7f0fd838 Agata Murawska
-- | Check whether list of queried fields contains live fields.
120 7f0fd838 Agata Murawska
needsLiveData :: [FieldGetter a b] -> Bool
121 a2ae14e9 Iustin Pop
needsLiveData = any isRuntimeField
122 7f0fd838 Agata Murawska
123 bc4cdeef Iustin Pop
-- | Checks whether we have requested exactly some names. This is a
124 bc4cdeef Iustin Pop
-- simple wrapper over 'requestedNames' and 'nameField'.
125 bc4cdeef Iustin Pop
needsNames :: Query -> Maybe [FilterValue]
126 bc4cdeef Iustin Pop
needsNames (Query kind _ qfilter) = requestedNames (nameField kind) qfilter
127 bc4cdeef Iustin Pop
128 bc4cdeef Iustin Pop
-- | Computes the name field for different query types.
129 bc4cdeef Iustin Pop
nameField :: ItemType -> FilterField
130 1283cc38 Iustin Pop
nameField (ItemTypeLuxi QRJob) = "id"
131 c4bf507b Iustin Pop
nameField (ItemTypeOpCode QRExport) = "node"
132 1283cc38 Iustin Pop
nameField _ = "name"
133 bc4cdeef Iustin Pop
134 bc4cdeef Iustin Pop
-- | Extracts all quoted strings from a list, ignoring the
135 bc4cdeef Iustin Pop
-- 'NumericValue' entries.
136 bc4cdeef Iustin Pop
getAllQuotedStrings :: [FilterValue] -> [String]
137 bc4cdeef Iustin Pop
getAllQuotedStrings =
138 bc4cdeef Iustin Pop
  concatMap extractor
139 bc4cdeef Iustin Pop
    where extractor (NumericValue _)   = []
140 bc4cdeef Iustin Pop
          extractor (QuotedString val) = [val]
141 bc4cdeef Iustin Pop
142 bc4cdeef Iustin Pop
-- | Checks that we have either requested a valid set of names, or we
143 bc4cdeef Iustin Pop
-- have a more complex filter.
144 bc4cdeef Iustin Pop
getRequestedNames :: Query -> [String]
145 bc4cdeef Iustin Pop
getRequestedNames qry =
146 bc4cdeef Iustin Pop
  case needsNames qry of
147 bc4cdeef Iustin Pop
    Just names -> getAllQuotedStrings names
148 bc4cdeef Iustin Pop
    Nothing    -> []
149 bc4cdeef Iustin Pop
150 a7e484c4 Iustin Pop
-- | Compute the requested job IDs. This is custom since we need to
151 a7e484c4 Iustin Pop
-- handle both strings and integers.
152 a7e484c4 Iustin Pop
getRequestedJobIDs :: Filter FilterField -> Result [JobId]
153 a7e484c4 Iustin Pop
getRequestedJobIDs qfilter =
154 a7e484c4 Iustin Pop
  case requestedNames (nameField (ItemTypeLuxi QRJob)) qfilter of
155 a7e484c4 Iustin Pop
    Nothing -> Ok []
156 a7e484c4 Iustin Pop
    Just [] -> Ok []
157 a7e484c4 Iustin Pop
    Just vals ->
158 a7e484c4 Iustin Pop
      mapM (\e -> case e of
159 a7e484c4 Iustin Pop
                    QuotedString s -> makeJobIdS s
160 a7e484c4 Iustin Pop
                    NumericValue i -> makeJobId $ fromIntegral i
161 a7e484c4 Iustin Pop
           ) vals
162 a7e484c4 Iustin Pop
163 d5b2753a Iustin Pop
-- | Generic query implementation for resources that are backed by
164 d5b2753a Iustin Pop
-- some configuration objects.
165 5771c501 Hrvoje Ribicic
--
166 5771c501 Hrvoje Ribicic
-- Different query types use the same 'genericQuery' function by providing
167 5771c501 Hrvoje Ribicic
-- a collector function and a field map. The collector function retrieves
168 5771c501 Hrvoje Ribicic
-- live data, and the field map provides both the requirements and the logic
169 5771c501 Hrvoje Ribicic
-- necessary to retrieve the data needed for the field.
170 5771c501 Hrvoje Ribicic
--
171 5771c501 Hrvoje Ribicic
-- The 'b' type in the specification is the runtime. Every query can gather
172 5771c501 Hrvoje Ribicic
-- additional live data related to the configuration object using the collector
173 5771c501 Hrvoje Ribicic
-- to perform RPC calls.
174 5771c501 Hrvoje Ribicic
--
175 5771c501 Hrvoje Ribicic
-- The gathered data, or the failure to get it, is expressed through a runtime
176 5771c501 Hrvoje Ribicic
-- object. The type of a runtime object is determined by every query type for
177 5771c501 Hrvoje Ribicic
-- itself, and used exclusively by that query.
178 ee8bb326 Hrvoje Ribicic
genericQuery :: FieldMap a b       -- ^ Maps field names to field definitions
179 ee8bb326 Hrvoje Ribicic
             -> CollectorType a b  -- ^ Collector of live data
180 d5b2753a Iustin Pop
             -> (a -> String)      -- ^ Object to name function
181 d5b2753a Iustin Pop
             -> (ConfigData -> Container a) -- ^ Get all objects from config
182 d5b2753a Iustin Pop
             -> (ConfigData -> String -> ErrorResult a) -- ^ Lookup object
183 d5b2753a Iustin Pop
             -> ConfigData         -- ^ The config to run the query against
184 d5b2753a Iustin Pop
             -> Bool               -- ^ Whether the query should be run live
185 d5b2753a Iustin Pop
             -> [String]           -- ^ List of requested fields
186 d5b2753a Iustin Pop
             -> Filter FilterField -- ^ Filter field
187 d5b2753a Iustin Pop
             -> [String]           -- ^ List of requested names
188 d5b2753a Iustin Pop
             -> IO (ErrorResult QueryResult)
189 d5b2753a Iustin Pop
genericQuery fieldsMap collector nameFn configFn getFn cfg
190 d5b2753a Iustin Pop
             live fields qfilter wanted =
191 d5b2753a Iustin Pop
  runResultT $ do
192 d5b2753a Iustin Pop
  cfilter <- resultT $ compileFilter fieldsMap qfilter
193 d5b2753a Iustin Pop
  let selected = getSelectedFields fieldsMap fields
194 d5b2753a Iustin Pop
      (fdefs, fgetters, _) = unzip3 selected
195 d5b2753a Iustin Pop
      live' = live && needsLiveData fgetters
196 d5b2753a Iustin Pop
  objects <- resultT $ case wanted of
197 d5b2753a Iustin Pop
             [] -> Ok . niceSortKey nameFn .
198 d5b2753a Iustin Pop
                   Map.elems . fromContainer $ configFn cfg
199 d5b2753a Iustin Pop
             _  -> mapM (getFn cfg) wanted
200 ee8bb326 Hrvoje Ribicic
  -- Run the first pass of the filter, without a runtime context; this will
201 ee8bb326 Hrvoje Ribicic
  -- limit the objects that we'll contact for exports
202 d5b2753a Iustin Pop
  fobjects <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
203 d5b2753a Iustin Pop
                        objects
204 ee8bb326 Hrvoje Ribicic
  -- Gather the runtime data
205 ee8bb326 Hrvoje Ribicic
  runtimes <- case collector of
206 ee8bb326 Hrvoje Ribicic
    CollectorSimple     collFn -> lift $ collFn live' cfg fobjects
207 ee8bb326 Hrvoje Ribicic
    CollectorFieldAware collFn -> lift $ collFn live' cfg fields fobjects
208 ee8bb326 Hrvoje Ribicic
  -- Filter the results again, based on the gathered data
209 d5b2753a Iustin Pop
  let fdata = map (\(obj, runtime) ->
210 d5b2753a Iustin Pop
                     map (execGetter cfg runtime obj) fgetters)
211 d5b2753a Iustin Pop
              runtimes
212 d5b2753a Iustin Pop
  return QueryResult { qresFields = fdefs, qresData = fdata }
213 d5b2753a Iustin Pop
214 4cbe9bda Iustin Pop
-- | Main query execution function.
215 4cbe9bda Iustin Pop
query :: ConfigData   -- ^ The current configuration
216 fa2c927c Agata Murawska
      -> Bool         -- ^ Whether to collect live data
217 4cbe9bda Iustin Pop
      -> Query        -- ^ The query (item, fields, filter)
218 5183e8be Iustin Pop
      -> IO (ErrorResult QueryResult) -- ^ Result
219 a7e484c4 Iustin Pop
query cfg live (Query (ItemTypeLuxi QRJob) fields qfilter) =
220 a7e484c4 Iustin Pop
  queryJobs cfg live fields qfilter
221 a41c337e Iustin Pop
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
222 046fe3f5 Iustin Pop
223 d286d795 Hrvoje Ribicic
-- | Dummy data collection fuction
224 d286d795 Hrvoje Ribicic
dummyCollectLiveData :: Bool -> ConfigData -> [a] -> IO [(a, NoDataRuntime)]
225 d286d795 Hrvoje Ribicic
dummyCollectLiveData _ _ = return . map (, NoDataRuntime)
226 d286d795 Hrvoje Ribicic
227 a41c337e Iustin Pop
-- | Inner query execution function.
228 a41c337e Iustin Pop
queryInner :: ConfigData   -- ^ The current configuration
229 a41c337e Iustin Pop
           -> Bool         -- ^ Whether to collect live data
230 a41c337e Iustin Pop
           -> Query        -- ^ The query (item, fields, filter)
231 a41c337e Iustin Pop
           -> [String]     -- ^ Requested names
232 5183e8be Iustin Pop
           -> IO (ErrorResult QueryResult) -- ^ Result
233 a41c337e Iustin Pop
234 1283cc38 Iustin Pop
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
235 e86c9deb Helga Velroyen
  genericQuery Node.fieldsMap (CollectorFieldAware Node.collectLiveData)
236 e86c9deb Helga Velroyen
               nodeName configNodes getNode cfg live fields qfilter wanted
237 046fe3f5 Iustin Pop
238 1df0266e Hrvoje Ribicic
queryInner cfg live (Query (ItemTypeOpCode QRInstance) fields qfilter) wanted =
239 ee8bb326 Hrvoje Ribicic
  genericQuery Instance.fieldsMap (CollectorFieldAware Instance.collectLiveData)
240 ee8bb326 Hrvoje Ribicic
               instName configInstances getInstance cfg live fields qfilter
241 ee8bb326 Hrvoje Ribicic
               wanted
242 1df0266e Hrvoje Ribicic
243 d5b2753a Iustin Pop
queryInner cfg live (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
244 ee8bb326 Hrvoje Ribicic
  genericQuery Group.fieldsMap (CollectorSimple dummyCollectLiveData) groupName
245 ee8bb326 Hrvoje Ribicic
               configNodegroups getGroup cfg live fields qfilter wanted
246 05092772 Helga Velroyen
247 d5b2753a Iustin Pop
queryInner cfg live (Query (ItemTypeOpCode QRNetwork) fields qfilter) wanted =
248 ee8bb326 Hrvoje Ribicic
  genericQuery Network.fieldsMap (CollectorSimple dummyCollectLiveData)
249 d5b2753a Iustin Pop
               (fromNonEmpty . networkName)
250 d5b2753a Iustin Pop
               configNetworks getNetwork cfg live fields qfilter wanted
251 40246fa0 Agata Murawska
252 c4bf507b Iustin Pop
queryInner cfg live (Query (ItemTypeOpCode QRExport) fields qfilter) wanted =
253 ee8bb326 Hrvoje Ribicic
  genericQuery Export.fieldsMap (CollectorSimple Export.collectLiveData)
254 ee8bb326 Hrvoje Ribicic
               nodeName configNodes getNode cfg live fields qfilter wanted
255 c4bf507b Iustin Pop
256 a41c337e Iustin Pop
queryInner _ _ (Query qkind _ _) _ =
257 5183e8be Iustin Pop
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
258 518023a9 Iustin Pop
259 a7e484c4 Iustin Pop
-- | Query jobs specific query function, needed as we need to accept
260 a7e484c4 Iustin Pop
-- both 'QuotedString' and 'NumericValue' as wanted names.
261 a7e484c4 Iustin Pop
queryJobs :: ConfigData                   -- ^ The current configuration
262 a7e484c4 Iustin Pop
          -> Bool                         -- ^ Whether to collect live data
263 a7e484c4 Iustin Pop
          -> [FilterField]                -- ^ Item
264 a7e484c4 Iustin Pop
          -> Filter FilterField           -- ^ Filter
265 a7e484c4 Iustin Pop
          -> IO (ErrorResult QueryResult) -- ^ Result
266 a7e484c4 Iustin Pop
queryJobs cfg live fields qfilter =
267 a7e484c4 Iustin Pop
  runResultT $ do
268 a7e484c4 Iustin Pop
  rootdir <- lift queueDir
269 a7e484c4 Iustin Pop
  let wanted_names = getRequestedJobIDs qfilter
270 a7e484c4 Iustin Pop
      want_arch = Query.Job.wantArchived fields
271 a7e484c4 Iustin Pop
  rjids <- case wanted_names of
272 a7e484c4 Iustin Pop
             Bad msg -> resultT . Bad $ GenericError msg
273 a7e484c4 Iustin Pop
             Ok [] -> if live
274 a7e484c4 Iustin Pop
                        -- we can check the filesystem for actual jobs
275 be0cb2d7 Michele Tartara
                        then do
276 be0cb2d7 Michele Tartara
                          maybeJobIDs <-
277 be0cb2d7 Michele Tartara
                            lift (determineJobDirectories rootdir want_arch
278 be0cb2d7 Michele Tartara
                              >>= getJobIDs)
279 be0cb2d7 Michele Tartara
                          case maybeJobIDs of
280 be0cb2d7 Michele Tartara
                            Left e -> (resultT . Bad) . BlockDeviceError $
281 be0cb2d7 Michele Tartara
                              "Unable to fetch the job list: " ++ show e
282 be0cb2d7 Michele Tartara
                            Right jobIDs -> resultT . Ok $ sortJobIDs jobIDs
283 a7e484c4 Iustin Pop
                        -- else we shouldn't look at the filesystem...
284 a7e484c4 Iustin Pop
                        else return []
285 a7e484c4 Iustin Pop
             Ok v -> resultT $ Ok v
286 a7e484c4 Iustin Pop
  cfilter <- resultT $ compileFilter Query.Job.fieldsMap qfilter
287 a7e484c4 Iustin Pop
  let selected = getSelectedFields Query.Job.fieldsMap fields
288 a7e484c4 Iustin Pop
      (fdefs, fgetters, _) = unzip3 selected
289 a7e484c4 Iustin Pop
      live' = live && needsLiveData fgetters
290 a7e484c4 Iustin Pop
      disabled_data = Bad "live data disabled"
291 a7e484c4 Iustin Pop
  -- runs first pass of the filter, without a runtime context; this
292 a7e484c4 Iustin Pop
  -- will limit the jobs that we'll load from disk
293 a7e484c4 Iustin Pop
  jids <- resultT $
294 a7e484c4 Iustin Pop
          filterM (\jid -> evaluateFilter cfg Nothing jid cfilter) rjids
295 a7e484c4 Iustin Pop
  -- here we run the runtime data gathering, filtering and evaluation,
296 a7e484c4 Iustin Pop
  -- all in the same step, so that we don't keep jobs in memory longer
297 a7e484c4 Iustin Pop
  -- than we need; we can't be fully lazy due to the multiple monad
298 a7e484c4 Iustin Pop
  -- wrapping across different steps
299 a7e484c4 Iustin Pop
  qdir <- lift queueDir
300 a7e484c4 Iustin Pop
  fdata <- foldM
301 a7e484c4 Iustin Pop
           -- big lambda, but we use many variables from outside it...
302 a7e484c4 Iustin Pop
           (\lst jid -> do
303 a7e484c4 Iustin Pop
              job <- lift $ if live'
304 d45a824b Iustin Pop
                              then loadJobFromDisk qdir True jid
305 a7e484c4 Iustin Pop
                              else return disabled_data
306 a7e484c4 Iustin Pop
              pass <- resultT $ evaluateFilter cfg (Just job) jid cfilter
307 a7e484c4 Iustin Pop
              let nlst = if pass
308 a7e484c4 Iustin Pop
                           then let row = map (execGetter cfg job jid) fgetters
309 a7e484c4 Iustin Pop
                                in rnf row `seq` row:lst
310 a7e484c4 Iustin Pop
                           else lst
311 a7e484c4 Iustin Pop
              -- evaluate nlst (to WHNF), otherwise we're too lazy
312 a7e484c4 Iustin Pop
              return $! nlst
313 a7e484c4 Iustin Pop
           ) [] jids
314 a7e484c4 Iustin Pop
  return QueryResult { qresFields = fdefs, qresData = reverse fdata }
315 a7e484c4 Iustin Pop
316 b04dc242 Iustin Pop
-- | Helper for 'queryFields'.
317 b04dc242 Iustin Pop
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
318 b04dc242 Iustin Pop
fieldsExtractor fieldsMap fields =
319 b04dc242 Iustin Pop
  let selected = if null fields
320 b04dc242 Iustin Pop
                   then map snd $ Map.toAscList fieldsMap
321 b04dc242 Iustin Pop
                   else getSelectedFields fieldsMap fields
322 f94a9680 Iustin Pop
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
323 b04dc242 Iustin Pop
324 518023a9 Iustin Pop
-- | Query fields call.
325 5183e8be Iustin Pop
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
326 1283cc38 Iustin Pop
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
327 36162faf Iustin Pop
  Ok $ fieldsExtractor Node.fieldsMap fields
328 518023a9 Iustin Pop
329 1283cc38 Iustin Pop
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
330 36162faf Iustin Pop
  Ok $ fieldsExtractor Group.fieldsMap fields
331 40246fa0 Agata Murawska
332 dce08ad3 Iustin Pop
queryFields (QueryFields (ItemTypeOpCode QRNetwork) fields) =
333 dce08ad3 Iustin Pop
  Ok $ fieldsExtractor Network.fieldsMap fields
334 dce08ad3 Iustin Pop
335 a7e484c4 Iustin Pop
queryFields (QueryFields (ItemTypeLuxi QRJob) fields) =
336 a7e484c4 Iustin Pop
  Ok $ fieldsExtractor Query.Job.fieldsMap fields
337 a7e484c4 Iustin Pop
338 c4bf507b Iustin Pop
queryFields (QueryFields (ItemTypeOpCode QRExport) fields) =
339 c4bf507b Iustin Pop
  Ok $ fieldsExtractor Export.fieldsMap fields
340 c4bf507b Iustin Pop
341 518023a9 Iustin Pop
queryFields (QueryFields qkind _) =
342 5183e8be Iustin Pop
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
343 cd67e337 Iustin Pop
344 cd67e337 Iustin Pop
-- | Classic query converter. It gets a standard query result on input
345 cd67e337 Iustin Pop
-- and computes the classic style results.
346 5183e8be Iustin Pop
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
347 cd67e337 Iustin Pop
queryCompat (QueryResult fields qrdata) =
348 cd67e337 Iustin Pop
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
349 cd67e337 Iustin Pop
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
350 5183e8be Iustin Pop
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
351 5183e8be Iustin Pop
                                    intercalate ", " unknown) ECodeInval