Statistics
| Branch: | Tag: | Revision:

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

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