Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (7.3 kB)

1
{-# LANGUAGE Rank2Types #-}
2

    
3
{-| Implementation of the Ganeti Query2 filterning.
4

    
5
The filtering of results should be done in two phases.
6

    
7
In the first phase, before contacting any remote nodes for runtime
8
data, the filtering should be executed with 'Nothing' for the runtime
9
context. This will make all non-runtime filters filter correctly,
10
whereas all runtime filters will respond successfully. As described in
11
the Python version too, this makes for example /Or/ filters very
12
inefficient if they contain runtime fields.
13

    
14
Once this first filtering phase has been done, we hopefully eliminated
15
some remote nodes out of the list of candidates, we run the remote
16
data gathering, and we evaluate the filter again, this time with a
17
'Just' runtime context. This will make all filters work correctly.
18

    
19
Note that the second run will re-evaluate the config/simple fields,
20
without caching; this is not perfect, but we consider config accesses
21
very cheap (and the configuration snapshot we have won't change
22
between the two runs, hence we will not get inconsistent results).
23

    
24
-}
25

    
26
{-
27

    
28
Copyright (C) 2012 Google Inc.
29

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

    
35
This program is distributed in the hope that it will be useful, but
36
WITHOUT ANY WARRANTY; without even the implied warranty of
37
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
38
General Public License for more details.
39

    
40
You should have received a copy of the GNU General Public License
41
along with this program; if not, write to the Free Software
42
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
43
02110-1301, USA.
44

    
45
-}
46

    
47
module Ganeti.Query.Filter
48
  ( compileFilter
49
  , evaluateFilter
50
  , requestedNames
51
  ) where
52

    
53
import Control.Applicative
54
import Control.Monad (liftM)
55
import qualified Data.Map as Map
56
import Data.Traversable (traverse)
57
import Text.JSON (JSValue(..), fromJSString)
58
import Text.JSON.Pretty (pp_value)
59
import qualified Text.Regex.PCRE as PCRE
60

    
61
import Ganeti.BasicTypes
62
import Ganeti.Objects
63
import Ganeti.Query.Language
64
import Ganeti.Query.Types
65
import Ganeti.JSON
66

    
67
-- | Compiles a filter based on field names to one based on getters.
68
compileFilter :: FieldMap a b
69
              -> Filter FilterField
70
              -> Result (Filter (FieldGetter a b))
71
compileFilter fm =
72
  traverse (\field -> maybe (Bad $ "Can't find field named '" ++ field ++ "'")
73
                      (Ok . snd) (field `Map.lookup` fm))
74

    
75
-- | Wraps a getter, filter pair. If the getter is 'FieldRuntime' but
76
-- we don't have a runtime context, we skip the filtering, returning
77
-- \"pass\". Otherwise, we pass the actual value to the filter.
78
wrapGetter :: ConfigData
79
           -> Maybe b
80
           -> a
81
           -> FieldGetter a b
82
           -> (JSValue -> Result Bool)
83
           -> Result Bool
84
wrapGetter cfg b a getter faction =
85
  case tryGetter cfg b a getter of
86
    Nothing -> Ok True -- runtime missing, accepting the value
87
    Just v ->
88
      case v of
89
        ResultEntry RSNormal (Just fval) -> faction fval
90
        ResultEntry RSNormal Nothing ->
91
          Bad "Internal error: Getter returned RSNormal/Nothing"
92
        _ -> Ok True -- filter has no data to work, accepting it
93

    
94
-- | Helper to evaluate a filter getter (and the value it generates) in
95
-- a boolean context.
96
trueFilter :: JSValue -> Result Bool
97
trueFilter (JSBool x) = Ok x
98
trueFilter v = Bad $ "Unexpected value '" ++ show (pp_value v) ++
99
               "' in boolean context"
100

    
101
-- | A type synonim for a rank-2 comparator function. This is used so
102
-- that we can pass the usual '<=', '>', '==' functions to 'binOpFilter'
103
-- and for them to be used in multiple contexts.
104
type Comparator = (Eq a, Ord a) => a -> a -> Bool
105

    
106
-- | Helper to evaluate a filder getter (and the value it generates)
107
-- in a boolean context. Note the order of arguments is reversed from
108
-- the filter definitions (due to the call chain), make sure to
109
-- compare in the reverse order too!.
110
binOpFilter :: Comparator -> FilterValue -> JSValue -> Result Bool
111
binOpFilter comp (QuotedString y) (JSString x) =
112
  Ok $ fromJSString x `comp` y
113
binOpFilter comp (NumericValue y) (JSRational _ x) =
114
  Ok $ x `comp` fromIntegral y
115
binOpFilter _ expr actual =
116
  Bad $ "Invalid types in comparison, trying to compare " ++
117
      show (pp_value actual) ++ " with '" ++ show expr ++ "'"
118

    
119
-- | Implements the 'RegexpFilter' matching.
120
regexpFilter :: FilterRegex -> JSValue -> Result Bool
121
regexpFilter re (JSString val) =
122
  Ok $ PCRE.match (compiledRegex re) (fromJSString val)
123
regexpFilter _ x =
124
  Bad $ "Invalid field value used in regexp matching,\
125
        \ expecting string but got '" ++ show (pp_value x) ++ "'"
126

    
127
-- | Implements the 'ContainsFilter' matching.
128
containsFilter :: FilterValue -> JSValue -> Result Bool
129
-- note: the next two implementations are the same, but we have to
130
-- repeat them due to the encapsulation done by FilterValue
131
containsFilter (QuotedString val) lst = do
132
  lst' <- fromJVal lst
133
  return $ val `elem` lst'
134
containsFilter (NumericValue val) lst = do
135
  lst' <- fromJVal lst
136
  return $ val `elem` lst'
137

    
138
-- | Verifies if a given item passes a filter. The runtime context
139
-- might be missing, in which case most of the filters will consider
140
-- this as passing the filter.
141
evaluateFilter :: ConfigData -> Maybe b -> a
142
               -> Filter (FieldGetter a b)
143
               -> Result Bool
144
evaluateFilter _ _  _ EmptyFilter = Ok True
145
evaluateFilter c mb a (AndFilter flts) =
146
  all id <$> mapM (evaluateFilter c mb a) flts
147
evaluateFilter c mb a (OrFilter flts)  =
148
  any id <$> mapM (evaluateFilter c mb a) flts
149
evaluateFilter c mb a (NotFilter flt)  =
150
  not <$> evaluateFilter c mb a flt
151
evaluateFilter c mb a (TrueFilter getter)  =
152
  wrapGetter c mb a getter trueFilter
153
evaluateFilter c mb a (EQFilter getter val) =
154
  wrapGetter c mb a getter (binOpFilter (==) val)
155
evaluateFilter c mb a (LTFilter getter val) =
156
  wrapGetter c mb a getter (binOpFilter (<) val)
157
evaluateFilter c mb a (LEFilter getter val) =
158
  wrapGetter c mb a getter (binOpFilter (<=) val)
159
evaluateFilter c mb a (GTFilter getter val) =
160
  wrapGetter c mb a getter (binOpFilter (>) val)
161
evaluateFilter c mb a (GEFilter getter val) =
162
  wrapGetter c mb a getter (binOpFilter (>=) val)
163
evaluateFilter c mb a (RegexpFilter getter re) =
164
  wrapGetter c mb a getter (regexpFilter re)
165
evaluateFilter c mb a (ContainsFilter getter val) =
166
  wrapGetter c mb a getter (containsFilter val)
167

    
168
-- | Runs a getter with potentially missing runtime context.
169
tryGetter :: ConfigData -> Maybe b -> a -> FieldGetter a b -> Maybe ResultEntry
170
tryGetter _   _ item (FieldSimple getter)  = Just $ getter item
171
tryGetter cfg _ item (FieldConfig getter)  = Just $ getter cfg item
172
tryGetter _  rt item (FieldRuntime getter) =
173
  maybe Nothing (\rt' -> Just $ getter rt' item) rt
174
tryGetter _   _ _    FieldUnknown          = Just $
175
                                             ResultEntry RSUnknown Nothing
176

    
177
-- | Computes the requested names, if only names were requested (and
178
-- with equality). Otherwise returns 'Nothing'.
179
requestedNames :: FilterField -> Filter FilterField -> Maybe [FilterValue]
180
requestedNames _ EmptyFilter = Just []
181
requestedNames namefield (OrFilter flts) =
182
  liftM concat $ mapM (requestedNames namefield) flts
183
requestedNames namefield (EQFilter fld val) =
184
  if namefield == fld
185
    then Just [val]
186
    else Nothing
187
requestedNames _ _ = Nothing