Statistics
| Branch: | Tag: | Revision:

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

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