Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Query / Query.hs @ 36162faf

History | View | Annotate | Download (13.7 kB)

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