Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Filter.hs @ bc4cdeef

History | View | Annotate | Download (7.3 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 8a65c02b Iustin Pop
  ) where
52 8a65c02b Iustin Pop
53 8a65c02b Iustin Pop
import Control.Applicative
54 bc4cdeef Iustin Pop
import Control.Monad (liftM)
55 8a65c02b Iustin Pop
import qualified Data.Map as Map
56 8a65c02b Iustin Pop
import Data.Traversable (traverse)
57 8a65c02b Iustin Pop
import Text.JSON (JSValue(..), fromJSString)
58 8a65c02b Iustin Pop
import Text.JSON.Pretty (pp_value)
59 01606931 Iustin Pop
import qualified Text.Regex.PCRE as PCRE
60 8a65c02b Iustin Pop
61 8a65c02b Iustin Pop
import Ganeti.BasicTypes
62 8a65c02b Iustin Pop
import Ganeti.Objects
63 4cab6703 Iustin Pop
import Ganeti.Query.Language
64 8a65c02b Iustin Pop
import Ganeti.Query.Types
65 f3baf5ef Iustin Pop
import Ganeti.JSON
66 8a65c02b Iustin Pop
67 8a65c02b Iustin Pop
-- | Compiles a filter based on field names to one based on getters.
68 8a65c02b Iustin Pop
compileFilter :: FieldMap a b
69 8a65c02b Iustin Pop
              -> Filter FilterField
70 8a65c02b Iustin Pop
              -> Result (Filter (FieldGetter a b))
71 8a65c02b Iustin Pop
compileFilter fm =
72 8a65c02b Iustin Pop
  traverse (\field -> maybe (Bad $ "Can't find field named '" ++ field ++ "'")
73 8a65c02b Iustin Pop
                      (Ok . snd) (field `Map.lookup` fm))
74 8a65c02b Iustin Pop
75 8a65c02b Iustin Pop
-- | Wraps a getter, filter pair. If the getter is 'FieldRuntime' but
76 8a65c02b Iustin Pop
-- we don't have a runtime context, we skip the filtering, returning
77 8a65c02b Iustin Pop
-- \"pass\". Otherwise, we pass the actual value to the filter.
78 8a65c02b Iustin Pop
wrapGetter :: ConfigData
79 8a65c02b Iustin Pop
           -> Maybe b
80 8a65c02b Iustin Pop
           -> a
81 8a65c02b Iustin Pop
           -> FieldGetter a b
82 8a65c02b Iustin Pop
           -> (JSValue -> Result Bool)
83 8a65c02b Iustin Pop
           -> Result Bool
84 8a65c02b Iustin Pop
wrapGetter cfg b a getter faction =
85 8a65c02b Iustin Pop
  case tryGetter cfg b a getter of
86 8a65c02b Iustin Pop
    Nothing -> Ok True -- runtime missing, accepting the value
87 8a65c02b Iustin Pop
    Just v ->
88 8a65c02b Iustin Pop
      case v of
89 8a65c02b Iustin Pop
        ResultEntry RSNormal (Just fval) -> faction fval
90 8a65c02b Iustin Pop
        ResultEntry RSNormal Nothing ->
91 8a65c02b Iustin Pop
          Bad "Internal error: Getter returned RSNormal/Nothing"
92 8a65c02b Iustin Pop
        _ -> Ok True -- filter has no data to work, accepting it
93 8a65c02b Iustin Pop
94 8a65c02b Iustin Pop
-- | Helper to evaluate a filter getter (and the value it generates) in
95 8a65c02b Iustin Pop
-- a boolean context.
96 8a65c02b Iustin Pop
trueFilter :: JSValue -> Result Bool
97 8a65c02b Iustin Pop
trueFilter (JSBool x) = Ok x
98 8a65c02b Iustin Pop
trueFilter v = Bad $ "Unexpected value '" ++ show (pp_value v) ++
99 8a65c02b Iustin Pop
               "' in boolean context"
100 8a65c02b Iustin Pop
101 8a65c02b Iustin Pop
-- | A type synonim for a rank-2 comparator function. This is used so
102 8a65c02b Iustin Pop
-- that we can pass the usual '<=', '>', '==' functions to 'binOpFilter'
103 8a65c02b Iustin Pop
-- and for them to be used in multiple contexts.
104 8a65c02b Iustin Pop
type Comparator = (Eq a, Ord a) => a -> a -> Bool
105 8a65c02b Iustin Pop
106 8a65c02b Iustin Pop
-- | Helper to evaluate a filder getter (and the value it generates)
107 8a65c02b Iustin Pop
-- in a boolean context. Note the order of arguments is reversed from
108 8a65c02b Iustin Pop
-- the filter definitions (due to the call chain), make sure to
109 8a65c02b Iustin Pop
-- compare in the reverse order too!.
110 8a65c02b Iustin Pop
binOpFilter :: Comparator -> FilterValue -> JSValue -> Result Bool
111 8a65c02b Iustin Pop
binOpFilter comp (QuotedString y) (JSString x) =
112 8a65c02b Iustin Pop
  Ok $ fromJSString x `comp` y
113 8a65c02b Iustin Pop
binOpFilter comp (NumericValue y) (JSRational _ x) =
114 8a65c02b Iustin Pop
  Ok $ x `comp` fromIntegral y
115 8a65c02b Iustin Pop
binOpFilter _ expr actual =
116 8a65c02b Iustin Pop
  Bad $ "Invalid types in comparison, trying to compare " ++
117 8a65c02b Iustin Pop
      show (pp_value actual) ++ " with '" ++ show expr ++ "'"
118 8a65c02b Iustin Pop
119 8a65c02b Iustin Pop
-- | Implements the 'RegexpFilter' matching.
120 01606931 Iustin Pop
regexpFilter :: FilterRegex -> JSValue -> Result Bool
121 01606931 Iustin Pop
regexpFilter re (JSString val) =
122 01606931 Iustin Pop
  Ok $ PCRE.match (compiledRegex re) (fromJSString val)
123 8a65c02b Iustin Pop
regexpFilter _ x =
124 8a65c02b Iustin Pop
  Bad $ "Invalid field value used in regexp matching,\
125 8a65c02b Iustin Pop
        \ expecting string but got '" ++ show (pp_value x) ++ "'"
126 8a65c02b Iustin Pop
127 8a65c02b Iustin Pop
-- | Implements the 'ContainsFilter' matching.
128 8a65c02b Iustin Pop
containsFilter :: FilterValue -> JSValue -> Result Bool
129 8a65c02b Iustin Pop
-- note: the next two implementations are the same, but we have to
130 8a65c02b Iustin Pop
-- repeat them due to the encapsulation done by FilterValue
131 8a65c02b Iustin Pop
containsFilter (QuotedString val) lst = do
132 8a65c02b Iustin Pop
  lst' <- fromJVal lst
133 8a65c02b Iustin Pop
  return $ val `elem` lst'
134 8a65c02b Iustin Pop
containsFilter (NumericValue val) lst = do
135 8a65c02b Iustin Pop
  lst' <- fromJVal lst
136 8a65c02b Iustin Pop
  return $ val `elem` lst'
137 8a65c02b Iustin Pop
138 8a65c02b Iustin Pop
-- | Verifies if a given item passes a filter. The runtime context
139 8a65c02b Iustin Pop
-- might be missing, in which case most of the filters will consider
140 8a65c02b Iustin Pop
-- this as passing the filter.
141 8a65c02b Iustin Pop
evaluateFilter :: ConfigData -> Maybe b -> a
142 8a65c02b Iustin Pop
               -> Filter (FieldGetter a b)
143 8a65c02b Iustin Pop
               -> Result Bool
144 8a65c02b Iustin Pop
evaluateFilter _ _  _ EmptyFilter = Ok True
145 8a65c02b Iustin Pop
evaluateFilter c mb a (AndFilter flts) =
146 8a65c02b Iustin Pop
  all id <$> mapM (evaluateFilter c mb a) flts
147 8a65c02b Iustin Pop
evaluateFilter c mb a (OrFilter flts)  =
148 8a65c02b Iustin Pop
  any id <$> mapM (evaluateFilter c mb a) flts
149 8a65c02b Iustin Pop
evaluateFilter c mb a (NotFilter flt)  =
150 8a65c02b Iustin Pop
  not <$> evaluateFilter c mb a flt
151 8a65c02b Iustin Pop
evaluateFilter c mb a (TrueFilter getter)  =
152 8a65c02b Iustin Pop
  wrapGetter c mb a getter trueFilter
153 8a65c02b Iustin Pop
evaluateFilter c mb a (EQFilter getter val) =
154 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (==) val)
155 8a65c02b Iustin Pop
evaluateFilter c mb a (LTFilter getter val) =
156 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (<) val)
157 8a65c02b Iustin Pop
evaluateFilter c mb a (LEFilter getter val) =
158 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (<=) val)
159 8a65c02b Iustin Pop
evaluateFilter c mb a (GTFilter getter val) =
160 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (>) val)
161 8a65c02b Iustin Pop
evaluateFilter c mb a (GEFilter getter val) =
162 8a65c02b Iustin Pop
  wrapGetter c mb a getter (binOpFilter (>=) val)
163 8a65c02b Iustin Pop
evaluateFilter c mb a (RegexpFilter getter re) =
164 8a65c02b Iustin Pop
  wrapGetter c mb a getter (regexpFilter re)
165 8a65c02b Iustin Pop
evaluateFilter c mb a (ContainsFilter getter val) =
166 8a65c02b Iustin Pop
  wrapGetter c mb a getter (containsFilter val)
167 8a65c02b Iustin Pop
168 8a65c02b Iustin Pop
-- | Runs a getter with potentially missing runtime context.
169 8a65c02b Iustin Pop
tryGetter :: ConfigData -> Maybe b -> a -> FieldGetter a b -> Maybe ResultEntry
170 8a65c02b Iustin Pop
tryGetter _   _ item (FieldSimple getter)  = Just $ getter item
171 8a65c02b Iustin Pop
tryGetter cfg _ item (FieldConfig getter)  = Just $ getter cfg item
172 8a65c02b Iustin Pop
tryGetter _  rt item (FieldRuntime getter) =
173 8a65c02b Iustin Pop
  maybe Nothing (\rt' -> Just $ getter rt' item) rt
174 8a65c02b Iustin Pop
tryGetter _   _ _    FieldUnknown          = Just $
175 8a65c02b Iustin Pop
                                             ResultEntry RSUnknown Nothing
176 bc4cdeef Iustin Pop
177 bc4cdeef Iustin Pop
-- | Computes the requested names, if only names were requested (and
178 bc4cdeef Iustin Pop
-- with equality). Otherwise returns 'Nothing'.
179 bc4cdeef Iustin Pop
requestedNames :: FilterField -> Filter FilterField -> Maybe [FilterValue]
180 bc4cdeef Iustin Pop
requestedNames _ EmptyFilter = Just []
181 bc4cdeef Iustin Pop
requestedNames namefield (OrFilter flts) =
182 bc4cdeef Iustin Pop
  liftM concat $ mapM (requestedNames namefield) flts
183 bc4cdeef Iustin Pop
requestedNames namefield (EQFilter fld val) =
184 bc4cdeef Iustin Pop
  if namefield == fld
185 bc4cdeef Iustin Pop
    then Just [val]
186 bc4cdeef Iustin Pop
    else Nothing
187 bc4cdeef Iustin Pop
requestedNames _ _ = Nothing