Statistics
| Branch: | Tag: | Revision:

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

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