Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Filter.hs @ 1ba01ff7

History | View | Annotate | Download (8.7 kB)

1 8a65c02b Iustin Pop
{-# LANGUAGE Rank2Types #-}
2 8a65c02b Iustin Pop
3 8a65c02b Iustin Pop
{-| Implementation of the Ganeti Query2 filterning.
4 8a65c02b Iustin Pop
5 8a65c02b Iustin Pop
The filtering of results should be done in two phases.
6 8a65c02b Iustin Pop
7 8a65c02b Iustin Pop
In the first phase, before contacting any remote nodes for runtime
8 8a65c02b Iustin Pop
data, the filtering should be executed with 'Nothing' for the runtime
9 8a65c02b Iustin Pop
context. This will make all non-runtime filters filter correctly,
10 8a65c02b Iustin Pop
whereas all runtime filters will respond successfully. As described in
11 8a65c02b Iustin Pop
the Python version too, this makes for example /Or/ filters very
12 8a65c02b Iustin Pop
inefficient if they contain runtime fields.
13 8a65c02b Iustin Pop
14 8a65c02b Iustin Pop
Once this first filtering phase has been done, we hopefully eliminated
15 8a65c02b Iustin Pop
some remote nodes out of the list of candidates, we run the remote
16 8a65c02b Iustin Pop
data gathering, and we evaluate the filter again, this time with a
17 8a65c02b Iustin Pop
'Just' runtime context. This will make all filters work correctly.
18 8a65c02b Iustin Pop
19 8a65c02b Iustin Pop
Note that the second run will re-evaluate the config/simple fields,
20 8a65c02b Iustin Pop
without caching; this is not perfect, but we consider config accesses
21 8a65c02b Iustin Pop
very cheap (and the configuration snapshot we have won't change
22 8a65c02b Iustin Pop
between the two runs, hence we will not get inconsistent results).
23 8a65c02b Iustin Pop
24 8a65c02b Iustin Pop
-}
25 8a65c02b Iustin Pop
26 8a65c02b Iustin Pop
{-
27 8a65c02b Iustin Pop
28 8a65c02b Iustin Pop
Copyright (C) 2012 Google Inc.
29 8a65c02b Iustin Pop
30 8a65c02b Iustin Pop
This program is free software; you can redistribute it and/or modify
31 8a65c02b Iustin Pop
it under the terms of the GNU General Public License as published by
32 8a65c02b Iustin Pop
the Free Software Foundation; either version 2 of the License, or
33 8a65c02b Iustin Pop
(at your option) any later version.
34 8a65c02b Iustin Pop
35 8a65c02b Iustin Pop
This program is distributed in the hope that it will be useful, but
36 8a65c02b Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
37 8a65c02b Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
38 8a65c02b Iustin Pop
General Public License for more details.
39 8a65c02b Iustin Pop
40 8a65c02b Iustin Pop
You should have received a copy of the GNU General Public License
41 8a65c02b Iustin Pop
along with this program; if not, write to the Free Software
42 8a65c02b Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
43 8a65c02b Iustin Pop
02110-1301, USA.
44 8a65c02b Iustin Pop
45 8a65c02b Iustin Pop
-}
46 8a65c02b Iustin Pop
47 8a65c02b Iustin Pop
module Ganeti.Query.Filter
48 8a65c02b Iustin Pop
  ( compileFilter
49 8a65c02b Iustin Pop
  , evaluateFilter
50 bc4cdeef Iustin Pop
  , requestedNames
51 b3d17f52 Iustin Pop
  , makeSimpleFilter
52 8a65c02b Iustin Pop
  ) where
53 8a65c02b Iustin Pop
54 8a65c02b Iustin Pop
import Control.Applicative
55 bc4cdeef Iustin Pop
import Control.Monad (liftM)
56 8a65c02b Iustin Pop
import qualified Data.Map as Map
57 8a65c02b Iustin Pop
import Data.Traversable (traverse)
58 8a65c02b Iustin Pop
import Text.JSON (JSValue(..), fromJSString)
59 8a65c02b Iustin Pop
import Text.JSON.Pretty (pp_value)
60 01606931 Iustin Pop
import qualified Text.Regex.PCRE as PCRE
61 8a65c02b Iustin Pop
62 8a65c02b Iustin Pop
import Ganeti.BasicTypes
63 5183e8be Iustin Pop
import Ganeti.Errors
64 8a65c02b Iustin Pop
import Ganeti.Objects
65 4cab6703 Iustin Pop
import Ganeti.Query.Language
66 8a65c02b Iustin Pop
import Ganeti.Query.Types
67 f3baf5ef Iustin Pop
import Ganeti.JSON
68 8a65c02b Iustin Pop
69 8a65c02b Iustin Pop
-- | Compiles a filter based on field names to one based on getters.
70 8a65c02b Iustin Pop
compileFilter :: FieldMap a b
71 8a65c02b Iustin Pop
              -> Filter FilterField
72 f94a9680 Iustin Pop
              -> ErrorResult (Filter (FieldGetter a b, QffMode))
73 8a65c02b Iustin Pop
compileFilter fm =
74 5183e8be Iustin Pop
  traverse (\field -> maybe
75 5183e8be Iustin Pop
                      (Bad . ParameterError $ "Can't find field named '" ++
76 5183e8be Iustin Pop
                           field ++ "'")
77 f94a9680 Iustin Pop
                      (\(_, g, q) -> Ok (g, q)) (field `Map.lookup` fm))
78 f94a9680 Iustin Pop
79 f94a9680 Iustin Pop
-- | Processes a field value given a QffMode.
80 f94a9680 Iustin Pop
qffField :: QffMode -> JSValue -> ErrorResult JSValue
81 f94a9680 Iustin Pop
qffField QffNormal    v = Ok v
82 f94a9680 Iustin Pop
qffField QffTimestamp v =
83 f94a9680 Iustin Pop
  case v of
84 f94a9680 Iustin Pop
    JSArray [secs@(JSRational _ _), JSRational _ _] -> return secs
85 f94a9680 Iustin Pop
    _ -> Bad $ ProgrammerError
86 f94a9680 Iustin Pop
         "Internal error: Getter returned non-timestamp for QffTimestamp"
87 8a65c02b Iustin Pop
88 8a65c02b Iustin Pop
-- | Wraps a getter, filter pair. If the getter is 'FieldRuntime' but
89 8a65c02b Iustin Pop
-- we don't have a runtime context, we skip the filtering, returning
90 8a65c02b Iustin Pop
-- \"pass\". Otherwise, we pass the actual value to the filter.
91 8a65c02b Iustin Pop
wrapGetter :: ConfigData
92 8a65c02b Iustin Pop
           -> Maybe b
93 8a65c02b Iustin Pop
           -> a
94 f94a9680 Iustin Pop
           -> (FieldGetter a b, QffMode)
95 5183e8be Iustin Pop
           -> (JSValue -> ErrorResult Bool)
96 5183e8be Iustin Pop
           -> ErrorResult Bool
97 f94a9680 Iustin Pop
wrapGetter cfg b a (getter, qff) faction =
98 8a65c02b Iustin Pop
  case tryGetter cfg b a getter of
99 8a65c02b Iustin Pop
    Nothing -> Ok True -- runtime missing, accepting the value
100 8a65c02b Iustin Pop
    Just v ->
101 8a65c02b Iustin Pop
      case v of
102 f94a9680 Iustin Pop
        ResultEntry RSNormal (Just fval) -> qffField qff fval >>= faction
103 8a65c02b Iustin Pop
        ResultEntry RSNormal Nothing ->
104 5183e8be Iustin Pop
          Bad $ ProgrammerError
105 5183e8be Iustin Pop
                "Internal error: Getter returned RSNormal/Nothing"
106 8a65c02b Iustin Pop
        _ -> Ok True -- filter has no data to work, accepting it
107 8a65c02b Iustin Pop
108 8a65c02b Iustin Pop
-- | Helper to evaluate a filter getter (and the value it generates) in
109 8a65c02b Iustin Pop
-- a boolean context.
110 5183e8be Iustin Pop
trueFilter :: JSValue -> ErrorResult Bool
111 228ef0f2 Iustin Pop
trueFilter (JSBool x) = Ok $! x
112 5183e8be Iustin Pop
trueFilter v = Bad . ParameterError $
113 5183e8be Iustin Pop
               "Unexpected value '" ++ show (pp_value v) ++
114 8a65c02b Iustin Pop
               "' in boolean context"
115 8a65c02b Iustin Pop
116 8a65c02b Iustin Pop
-- | A type synonim for a rank-2 comparator function. This is used so
117 8a65c02b Iustin Pop
-- that we can pass the usual '<=', '>', '==' functions to 'binOpFilter'
118 8a65c02b Iustin Pop
-- and for them to be used in multiple contexts.
119 8a65c02b Iustin Pop
type Comparator = (Eq a, Ord a) => a -> a -> Bool
120 8a65c02b Iustin Pop
121 8a65c02b Iustin Pop
-- | Helper to evaluate a filder getter (and the value it generates)
122 8a65c02b Iustin Pop
-- in a boolean context. Note the order of arguments is reversed from
123 8a65c02b Iustin Pop
-- the filter definitions (due to the call chain), make sure to
124 8a65c02b Iustin Pop
-- compare in the reverse order too!.
125 5183e8be Iustin Pop
binOpFilter :: Comparator -> FilterValue -> JSValue -> ErrorResult Bool
126 8a65c02b Iustin Pop
binOpFilter comp (QuotedString y) (JSString x) =
127 228ef0f2 Iustin Pop
  Ok $! fromJSString x `comp` y
128 8a65c02b Iustin Pop
binOpFilter comp (NumericValue y) (JSRational _ x) =
129 228ef0f2 Iustin Pop
  Ok $! x `comp` fromIntegral y
130 8a65c02b Iustin Pop
binOpFilter _ expr actual =
131 5183e8be Iustin Pop
  Bad . ParameterError $ "Invalid types in comparison, trying to compare " ++
132 8a65c02b Iustin Pop
      show (pp_value actual) ++ " with '" ++ show expr ++ "'"
133 8a65c02b Iustin Pop
134 8a65c02b Iustin Pop
-- | Implements the 'RegexpFilter' matching.
135 5183e8be Iustin Pop
regexpFilter :: FilterRegex -> JSValue -> ErrorResult Bool
136 01606931 Iustin Pop
regexpFilter re (JSString val) =
137 228ef0f2 Iustin Pop
  Ok $! PCRE.match (compiledRegex re) (fromJSString val)
138 8a65c02b Iustin Pop
regexpFilter _ x =
139 5183e8be Iustin Pop
  Bad . ParameterError $ "Invalid field value used in regexp matching,\
140 8a65c02b Iustin Pop
        \ expecting string but got '" ++ show (pp_value x) ++ "'"
141 8a65c02b Iustin Pop
142 8a65c02b Iustin Pop
-- | Implements the 'ContainsFilter' matching.
143 5183e8be Iustin Pop
containsFilter :: FilterValue -> JSValue -> ErrorResult Bool
144 8a65c02b Iustin Pop
-- note: the next two implementations are the same, but we have to
145 8a65c02b Iustin Pop
-- repeat them due to the encapsulation done by FilterValue
146 8a65c02b Iustin Pop
containsFilter (QuotedString val) lst = do
147 8a65c02b Iustin Pop
  lst' <- fromJVal lst
148 228ef0f2 Iustin Pop
  return $! val `elem` lst'
149 8a65c02b Iustin Pop
containsFilter (NumericValue val) lst = do
150 8a65c02b Iustin Pop
  lst' <- fromJVal lst
151 228ef0f2 Iustin Pop
  return $! val `elem` lst'
152 8a65c02b Iustin Pop
153 8a65c02b Iustin Pop
-- | Verifies if a given item passes a filter. The runtime context
154 8a65c02b Iustin Pop
-- might be missing, in which case most of the filters will consider
155 8a65c02b Iustin Pop
-- this as passing the filter.
156 d277b075 Iustin Pop
--
157 d277b075 Iustin Pop
-- Note: we use explicit recursion to reduce unneeded memory use;
158 d277b075 Iustin Pop
-- 'any' and 'all' do not play nice with monadic values, resulting in
159 d277b075 Iustin Pop
-- either too much memory use or in too many thunks being created.
160 8a65c02b Iustin Pop
evaluateFilter :: ConfigData -> Maybe b -> a
161 f94a9680 Iustin Pop
               -> Filter (FieldGetter a b, QffMode)
162 5183e8be Iustin Pop
               -> ErrorResult Bool
163 8a65c02b Iustin Pop
evaluateFilter _ _  _ EmptyFilter = Ok True
164 d277b075 Iustin Pop
evaluateFilter c mb a (AndFilter flts) = helper flts
165 d277b075 Iustin Pop
  where helper [] = Ok True
166 d277b075 Iustin Pop
        helper (f:fs) = do
167 d277b075 Iustin Pop
          v <- evaluateFilter c mb a f
168 d277b075 Iustin Pop
          if v
169 d277b075 Iustin Pop
            then helper fs
170 d277b075 Iustin Pop
            else Ok False
171 d277b075 Iustin Pop
evaluateFilter c mb a (OrFilter flts) = helper flts
172 d277b075 Iustin Pop
  where helper [] = Ok False
173 d277b075 Iustin Pop
        helper (f:fs) = do
174 d277b075 Iustin Pop
          v <- evaluateFilter c mb a f
175 d277b075 Iustin Pop
          if v
176 d277b075 Iustin Pop
            then Ok True
177 d277b075 Iustin Pop
            else helper fs
178 8a65c02b Iustin Pop
evaluateFilter c mb a (NotFilter flt)  =
179 8a65c02b Iustin Pop
  not <$> evaluateFilter c mb a flt
180 8a65c02b Iustin Pop
evaluateFilter c mb a (TrueFilter getter)  =
181 8a65c02b Iustin Pop
  wrapGetter c mb a getter trueFilter
182 8a65c02b Iustin Pop
evaluateFilter c mb a (EQFilter getter val) =
183 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (==) val)
184 8a65c02b Iustin Pop
evaluateFilter c mb a (LTFilter getter val) =
185 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (<) val)
186 8a65c02b Iustin Pop
evaluateFilter c mb a (LEFilter getter val) =
187 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (<=) val)
188 8a65c02b Iustin Pop
evaluateFilter c mb a (GTFilter getter val) =
189 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (>) val)
190 8a65c02b Iustin Pop
evaluateFilter c mb a (GEFilter getter val) =
191 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (>=) val)
192 8a65c02b Iustin Pop
evaluateFilter c mb a (RegexpFilter getter re) =
193 8a65c02b Iustin Pop
  wrapGetter c mb a getter (regexpFilter re)
194 8a65c02b Iustin Pop
evaluateFilter c mb a (ContainsFilter getter val) =
195 8a65c02b Iustin Pop
  wrapGetter c mb a getter (containsFilter val)
196 8a65c02b Iustin Pop
197 8a65c02b Iustin Pop
-- | Runs a getter with potentially missing runtime context.
198 8a65c02b Iustin Pop
tryGetter :: ConfigData -> Maybe b -> a -> FieldGetter a b -> Maybe ResultEntry
199 8a65c02b Iustin Pop
tryGetter _   _ item (FieldSimple getter)  = Just $ getter item
200 8a65c02b Iustin Pop
tryGetter cfg _ item (FieldConfig getter)  = Just $ getter cfg item
201 8a65c02b Iustin Pop
tryGetter _  rt item (FieldRuntime getter) =
202 8a65c02b Iustin Pop
  maybe Nothing (\rt' -> Just $ getter rt' item) rt
203 8a65c02b Iustin Pop
tryGetter _   _ _    FieldUnknown          = Just $
204 8a65c02b Iustin Pop
                                             ResultEntry RSUnknown Nothing
205 bc4cdeef Iustin Pop
206 bc4cdeef Iustin Pop
-- | Computes the requested names, if only names were requested (and
207 bc4cdeef Iustin Pop
-- with equality). Otherwise returns 'Nothing'.
208 bc4cdeef Iustin Pop
requestedNames :: FilterField -> Filter FilterField -> Maybe [FilterValue]
209 bc4cdeef Iustin Pop
requestedNames _ EmptyFilter = Just []
210 bc4cdeef Iustin Pop
requestedNames namefield (OrFilter flts) =
211 bc4cdeef Iustin Pop
  liftM concat $ mapM (requestedNames namefield) flts
212 bc4cdeef Iustin Pop
requestedNames namefield (EQFilter fld val) =
213 bc4cdeef Iustin Pop
  if namefield == fld
214 bc4cdeef Iustin Pop
    then Just [val]
215 bc4cdeef Iustin Pop
    else Nothing
216 bc4cdeef Iustin Pop
requestedNames _ _ = Nothing
217 b3d17f52 Iustin Pop
218 b3d17f52 Iustin Pop
-- | Builds a simple filter from a list of names.
219 037762a9 Iustin Pop
makeSimpleFilter :: String -> [Either String Integer] -> Filter FilterField
220 b3d17f52 Iustin Pop
makeSimpleFilter _ [] = EmptyFilter
221 b3d17f52 Iustin Pop
makeSimpleFilter namefield vals =
222 037762a9 Iustin Pop
  OrFilter $ map (EQFilter namefield . either QuotedString NumericValue) vals