Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Query.hs @ f94a9680

History | View | Annotate | Download (8.6 kB)

1
{-| Implementation of the Ganeti Query2 functionality.
2

    
3
 -}
4

    
5
{-
6

    
7
Copyright (C) 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
{-
27

    
28
TODO: problems with the current model:
29

    
30
1. There's nothing preventing a result such as ResultEntry RSNormal
31
Nothing, or ResultEntry RSNoData (Just ...); ideally, we would
32
separate the the RSNormal and other types; we would need a new data
33
type for this, though, with JSON encoding/decoding
34

    
35
2. We don't have a way to 'bind' a FieldDefinition's field type
36
(e.q. QFTBool) with the actual value that is returned from a
37
FieldGetter. This means that the various getter functions can return
38
divergent types for the same field when evaluated against multiple
39
items. This is bad; it only works today because we 'hide' everything
40
behind JSValue, but is not nice at all. We should probably remove the
41
separation between FieldDefinition and the FieldGetter, and introduce
42
a new abstract data type, similar to QFT*, that contains the values
43
too.
44

    
45
-}
46

    
47
module Ganeti.Query.Query
48
    ( query
49
    , queryFields
50
    , queryCompat
51
    , getRequestedNames
52
    , nameField
53
    ) where
54

    
55
import Control.Monad (filterM)
56
import Control.Monad.Trans (lift)
57
import Data.List (intercalate)
58
import Data.Maybe (fromMaybe)
59
import qualified Data.Map as Map
60
import qualified Text.JSON as J
61

    
62
import Ganeti.BasicTypes
63
import Ganeti.Errors
64
import Ganeti.Config
65
import Ganeti.JSON
66
import Ganeti.Rpc
67
import Ganeti.Query.Language
68
import Ganeti.Query.Common
69
import Ganeti.Query.Filter
70
import Ganeti.Query.Types
71
import Ganeti.Query.Node
72
import Ganeti.Query.Group
73
import Ganeti.Objects
74
import Ganeti.Utils
75

    
76
-- * Helper functions
77

    
78
-- | Builds an unknown field definition.
79
mkUnknownFDef :: String -> FieldData a b
80
mkUnknownFDef name =
81
  ( FieldDefinition name name QFTUnknown ("Unknown field '" ++ name ++ "'")
82
  , FieldUnknown
83
  , QffNormal )
84

    
85
-- | Runs a field getter on the existing contexts.
86
execGetter :: ConfigData -> b -> a -> FieldGetter a b -> ResultEntry
87
execGetter _   _ item (FieldSimple getter)  = getter item
88
execGetter cfg _ item (FieldConfig getter)  = getter cfg item
89
execGetter _  rt item (FieldRuntime getter) = getter rt item
90
execGetter _   _ _    FieldUnknown          = rsUnknown
91

    
92
-- * Main query execution
93

    
94
-- | Helper to build the list of requested fields. This transforms the
95
-- list of string fields to a list of field defs and getters, with
96
-- some of them possibly being unknown fields.
97
getSelectedFields :: FieldMap a b  -- ^ Defined fields
98
                  -> [String]      -- ^ Requested fields
99
                  -> FieldList a b -- ^ Selected fields
100
getSelectedFields defined =
101
  map (\name -> fromMaybe (mkUnknownFDef name) $ name `Map.lookup` defined)
102

    
103
-- | Collect live data from RPC query if enabled.
104
-- FIXME: Check which fields we actually need and possibly send empty
105
-- hvs/vgs if no info from hypervisor/volume group respectively
106
-- is required
107
maybeCollectLiveData:: Bool -> ConfigData -> [Node] -> IO [(Node, NodeRuntime)]
108

    
109
maybeCollectLiveData False _ nodes =
110
  return $ zip nodes (repeat $ Left (RpcResultError "Live data disabled"))
111

    
112
maybeCollectLiveData True cfg nodes = do
113
  let vgs = [clusterVolumeGroupName $ configCluster cfg]
114
      hvs = [getDefaultHypervisor cfg]
115
  executeRpcCall nodes (RpcCallNodeInfo vgs hvs)
116

    
117
-- | Check whether list of queried fields contains live fields.
118
needsLiveData :: [FieldGetter a b] -> Bool
119
needsLiveData = any isRuntimeField
120

    
121
-- | Checks whether we have requested exactly some names. This is a
122
-- simple wrapper over 'requestedNames' and 'nameField'.
123
needsNames :: Query -> Maybe [FilterValue]
124
needsNames (Query kind _ qfilter) = requestedNames (nameField kind) qfilter
125

    
126
-- | Computes the name field for different query types.
127
nameField :: ItemType -> FilterField
128
nameField (ItemTypeLuxi QRJob) = "id"
129
nameField _ = "name"
130

    
131
-- | Extracts all quoted strings from a list, ignoring the
132
-- 'NumericValue' entries.
133
getAllQuotedStrings :: [FilterValue] -> [String]
134
getAllQuotedStrings =
135
  concatMap extractor
136
    where extractor (NumericValue _)   = []
137
          extractor (QuotedString val) = [val]
138

    
139
-- | Checks that we have either requested a valid set of names, or we
140
-- have a more complex filter.
141
getRequestedNames :: Query -> [String]
142
getRequestedNames qry =
143
  case needsNames qry of
144
    Just names -> getAllQuotedStrings names
145
    Nothing    -> []
146

    
147
-- | Main query execution function.
148
query :: ConfigData   -- ^ The current configuration
149
      -> Bool         -- ^ Whether to collect live data
150
      -> Query        -- ^ The query (item, fields, filter)
151
      -> IO (ErrorResult QueryResult) -- ^ Result
152
query cfg live qry = queryInner cfg live qry $ getRequestedNames qry
153

    
154
-- | Inner query execution function.
155
queryInner :: ConfigData   -- ^ The current configuration
156
           -> Bool         -- ^ Whether to collect live data
157
           -> Query        -- ^ The query (item, fields, filter)
158
           -> [String]     -- ^ Requested names
159
           -> IO (ErrorResult QueryResult) -- ^ Result
160

    
161
queryInner cfg live (Query (ItemTypeOpCode QRNode) fields qfilter) wanted =
162
  runResultT $ do
163
  cfilter <- resultT $ compileFilter nodeFieldsMap qfilter
164
  let selected = getSelectedFields nodeFieldsMap fields
165
      (fdefs, fgetters, _) = unzip3 selected
166
      live' = live && needsLiveData fgetters
167
  nodes <- resultT $ case wanted of
168
             [] -> Ok . niceSortKey nodeName .
169
                   Map.elems . fromContainer $ configNodes cfg
170
             _  -> mapM (getNode cfg) wanted
171
  -- runs first pass of the filter, without a runtime context; this
172
  -- will limit the nodes that we'll contact for runtime data
173
  fnodes <- resultT $ filterM (\n -> evaluateFilter cfg Nothing n cfilter)
174
                      nodes
175
  -- here we would run the runtime data gathering, then filter again
176
  -- the nodes, based on existing runtime data
177
  nruntimes <- lift $ maybeCollectLiveData live' cfg fnodes
178
  let fdata = map (\(node, nrt) -> map (execGetter cfg nrt node) fgetters)
179
              nruntimes
180
  return QueryResult { qresFields = fdefs, qresData = fdata }
181

    
182
queryInner cfg _ (Query (ItemTypeOpCode QRGroup) fields qfilter) wanted =
183
  return $ do
184
  cfilter <- compileFilter groupFieldsMap qfilter
185
  let selected = getSelectedFields groupFieldsMap fields
186
      (fdefs, fgetters, _) = unzip3 selected
187
  groups <- case wanted of
188
              [] -> Ok . niceSortKey groupName .
189
                    Map.elems . fromContainer $ configNodegroups cfg
190
              _  -> mapM (getGroup cfg) wanted
191
  -- there is no live data for groups, so filtering is much simpler
192
  fgroups <- filterM (\n -> evaluateFilter cfg Nothing n cfilter) groups
193
  let fdata = map (\node ->
194
                       map (execGetter cfg GroupRuntime node) fgetters) fgroups
195
  return QueryResult {qresFields = fdefs, qresData = fdata }
196

    
197
queryInner _ _ (Query qkind _ _) _ =
198
  return . Bad . GenericError $ "Query '" ++ show qkind ++ "' not supported"
199

    
200
-- | Helper for 'queryFields'.
201
fieldsExtractor :: FieldMap a b -> [FilterField] -> QueryFieldsResult
202
fieldsExtractor fieldsMap fields =
203
  let selected = if null fields
204
                   then map snd $ Map.toAscList fieldsMap
205
                   else getSelectedFields fieldsMap fields
206
  in QueryFieldsResult (map (\(defs, _, _) -> defs) selected)
207

    
208
-- | Query fields call.
209
queryFields :: QueryFields -> ErrorResult QueryFieldsResult
210
queryFields (QueryFields (ItemTypeOpCode QRNode) fields) =
211
  Ok $ fieldsExtractor nodeFieldsMap fields
212

    
213
queryFields (QueryFields (ItemTypeOpCode QRGroup) fields) =
214
  Ok $ fieldsExtractor groupFieldsMap fields
215

    
216
queryFields (QueryFields qkind _) =
217
  Bad . GenericError $ "QueryFields '" ++ show qkind ++ "' not supported"
218

    
219
-- | Classic query converter. It gets a standard query result on input
220
-- and computes the classic style results.
221
queryCompat :: QueryResult -> ErrorResult [[J.JSValue]]
222
queryCompat (QueryResult fields qrdata) =
223
  case map fdefName $ filter ((== QFTUnknown) . fdefKind) fields of
224
    [] -> Ok $ map (map (maybe J.JSNull J.showJSON . rentryValue)) qrdata
225
    unknown -> Bad $ OpPrereqError ("Unknown output fields selected: " ++
226
                                    intercalate ", " unknown) ECodeInval