Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Language.hs @ ad1c1e41

History | View | Annotate | Download (15 kB)

1
{-# LANGUAGE TemplateHaskell, CPP #-}
2

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

    
5
 -}
6

    
7
{-
8

    
9
Copyright (C) 2012 Google Inc.
10

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

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

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

    
26
-}
27

    
28
module Ganeti.Query.Language
29
    ( Filter(..)
30
    , FilterField
31
    , FilterValue(..)
32
    , FilterRegex -- note: we don't export the constructor, must use helpers
33
    , mkRegex
34
    , stringRegex
35
    , compiledRegex
36
    , Fields
37
    , Query(..)
38
    , QueryResult(..)
39
    , QueryFields(..)
40
    , QueryFieldsResult(..)
41
    , FieldName
42
    , FieldTitle
43
    , FieldType(..)
44
    , FieldDoc
45
    , FieldDefinition(..)
46
    , ResultEntry(..)
47
    , ResultStatus(..)
48
    , ResultValue
49
    , ItemType(..)
50
    , QueryTypeOp(..)
51
    , queryTypeOpToRaw
52
    , QueryTypeLuxi(..)
53
    , checkRS
54
    ) where
55

    
56
import Control.Applicative
57
import Data.Foldable
58
import Data.Traversable (Traversable, traverse, fmapDefault, foldMapDefault)
59
import Data.Ratio (numerator, denominator)
60
import Text.JSON.Pretty (pp_value)
61
import Text.JSON.Types
62
import Text.JSON
63
#ifndef NO_REGEX_PCRE
64
import qualified Text.Regex.PCRE as PCRE
65
#endif
66

    
67
import qualified Ganeti.Constants as C
68
import Ganeti.THH
69

    
70
-- * THH declarations, that require ordering.
71

    
72
-- | Status of a query field.
73
$(declareIADT "ResultStatus"
74
  [ ("RSNormal",  'C.rsNormal )
75
  , ("RSUnknown", 'C.rsUnknown )
76
  , ("RSNoData",  'C.rsNodata )
77
  , ("RSUnavail", 'C.rsUnavail )
78
  , ("RSOffline", 'C.rsOffline )
79
  ])
80
$(makeJSONInstance ''ResultStatus)
81

    
82
-- | Check that ResultStatus is success or fail with descriptive
83
-- message.
84
checkRS :: (Monad m) => ResultStatus -> a -> m a
85
checkRS RSNormal val = return val
86
checkRS RSUnknown  _ = fail "Unknown field"
87
checkRS RSNoData   _ = fail "No data for a field"
88
checkRS RSUnavail  _ = fail "Ganeti reports unavailable data"
89
checkRS RSOffline  _ = fail "Ganeti reports resource as offline"
90

    
91
-- | Type of a query field.
92
$(declareSADT "FieldType"
93
  [ ("QFTUnknown",   'C.qftUnknown )
94
  , ("QFTText",      'C.qftText )
95
  , ("QFTBool",      'C.qftBool )
96
  , ("QFTNumber",    'C.qftNumber )
97
  , ("QFTUnit",      'C.qftUnit )
98
  , ("QFTTimestamp", 'C.qftTimestamp )
99
  , ("QFTOther",     'C.qftOther )
100
  ])
101
$(makeJSONInstance ''FieldType)
102

    
103
-- | Supported items on which Qlang works.
104
$(declareSADT "QueryTypeOp"
105
  [ ("QRCluster",  'C.qrCluster )
106
  , ("QRInstance", 'C.qrInstance )
107
  , ("QRNode",     'C.qrNode )
108
  , ("QRGroup",    'C.qrGroup )
109
  , ("QROs",       'C.qrOs )
110
  , ("QRExport",   'C.qrExport )
111
  ])
112
$(makeJSONInstance ''QueryTypeOp)
113

    
114
-- | Supported items on which Qlang works.
115
$(declareSADT "QueryTypeLuxi"
116
  [ ("QRLock",     'C.qrLock )
117
  , ("QRJob",      'C.qrJob )
118
  ])
119
$(makeJSONInstance ''QueryTypeLuxi)
120

    
121
-- | Overall query type.
122
data ItemType = ItemTypeLuxi QueryTypeLuxi
123
              | ItemTypeOpCode QueryTypeOp
124
                deriving (Show, Eq)
125

    
126
-- | Custom JSON decoder for 'ItemType'.
127
decodeItemType :: (Monad m) => JSValue -> m ItemType
128
decodeItemType (JSString s) =
129
  case queryTypeOpFromRaw s' of
130
    Just v -> return $ ItemTypeOpCode v
131
    Nothing ->
132
      case queryTypeLuxiFromRaw s' of
133
        Just v -> return $ ItemTypeLuxi v
134
        Nothing ->
135
          fail $ "Can't parse value '" ++ s' ++ "' as neither"
136
                 ++ "QueryTypeLuxi nor QueryTypeOp"
137
  where s' = fromJSString s
138
decodeItemType v = fail $ "Invalid value '" ++ show (pp_value v) ++
139
                   "for query type"
140

    
141
-- | Custom JSON instance for 'ItemType' since its encoding is not
142
-- consistent with the data type itself.
143
instance JSON ItemType where
144
  showJSON (ItemTypeLuxi x)  = showJSON x
145
  showJSON (ItemTypeOpCode y) = showJSON y
146
  readJSON = decodeItemType
147

    
148
-- * Sub data types for query2 queries and responses.
149

    
150
-- | Internal type of a regex expression (not exported).
151
#ifndef NO_REGEX_PCRE
152
type RegexType = PCRE.Regex
153
#else
154
type RegexType = ()
155
#endif
156

    
157
-- | List of requested fields.
158
type Fields = [ String ]
159

    
160
-- | Query2 filter expression. It's a parameteric type since we can
161
-- filter different \"things\"; e.g. field names, or actual field
162
-- getters, etc.
163
data Filter a
164
    = EmptyFilter                   -- ^ No filter at all
165
    | AndFilter      [ Filter a ]   -- ^ @&@ [/expression/, ...]
166
    | OrFilter       [ Filter a ]   -- ^ @|@ [/expression/, ...]
167
    | NotFilter      (Filter a)     -- ^ @!@ /expression/
168
    | TrueFilter     a              -- ^ @?@ /field/
169
    | EQFilter       a FilterValue  -- ^ @(=|!=)@ /field/ /value/
170
    | LTFilter       a FilterValue  -- ^ @<@ /field/ /value/
171
    | GTFilter       a FilterValue  -- ^ @>@ /field/ /value/
172
    | LEFilter       a FilterValue  -- ^ @<=@ /field/ /value/
173
    | GEFilter       a FilterValue  -- ^ @>=@ /field/ /value/
174
    | RegexpFilter   a FilterRegex  -- ^ @=~@ /field/ /regexp/
175
    | ContainsFilter a FilterValue  -- ^ @=[]@ /list-field/ /value/
176
      deriving (Show, Eq)
177

    
178
-- | Serialiser for the 'Filter' data type.
179
showFilter :: (JSON a) => Filter a -> JSValue
180
showFilter (EmptyFilter)          = JSNull
181
showFilter (AndFilter exprs)      =
182
  JSArray $ showJSON C.qlangOpAnd : map showJSON exprs
183
showFilter (OrFilter  exprs)      =
184
  JSArray $ showJSON C.qlangOpOr : map showJSON exprs
185
showFilter (NotFilter flt)        =
186
  JSArray [showJSON C.qlangOpNot, showJSON flt]
187
showFilter (TrueFilter field)     =
188
  JSArray [showJSON C.qlangOpTrue, showJSON field]
189
showFilter (EQFilter field value) =
190
  JSArray [showJSON C.qlangOpEqual, showJSON field, showJSON value]
191
showFilter (LTFilter field value) =
192
  JSArray [showJSON C.qlangOpLt, showJSON field, showJSON value]
193
showFilter (GTFilter field value) =
194
  JSArray [showJSON C.qlangOpGt, showJSON field, showJSON value]
195
showFilter (LEFilter field value) =
196
  JSArray [showJSON C.qlangOpLe, showJSON field, showJSON value]
197
showFilter (GEFilter field value) =
198
  JSArray [showJSON C.qlangOpGe, showJSON field, showJSON value]
199
showFilter (RegexpFilter field regexp) =
200
  JSArray [showJSON C.qlangOpRegexp, showJSON field, showJSON regexp]
201
showFilter (ContainsFilter field value) =
202
  JSArray [showJSON C.qlangOpContains, showJSON field, showJSON value]
203

    
204
-- | Deserializer for the 'Filter' data type.
205
readFilter :: (JSON a) => JSValue -> Result (Filter a)
206
readFilter JSNull = Ok EmptyFilter
207
readFilter (JSArray (JSString op:args)) =
208
  readFilterArray (fromJSString op) args
209
readFilter v =
210
  Error $ "Cannot deserialise filter: expected array [string, args], got " ++
211
        show (pp_value v)
212

    
213
-- | Helper to deserialise an array corresponding to a single filter
214
-- and return the built filter. Note this looks generic but is (at
215
-- least currently) only used for the NotFilter.
216
readFilterArg :: (JSON a) =>
217
                 (Filter a -> Filter a) -- ^ Constructor
218
              -> [JSValue]              -- ^ Single argument
219
              -> Result (Filter a)
220
readFilterArg constr [flt] = constr <$> readJSON flt
221
readFilterArg _ v = Error $ "Cannot deserialise field, expected [filter]" ++
222
                            " but got " ++ show (pp_value (showJSON v))
223

    
224
-- | Helper to deserialise an array corresponding to a single field
225
-- and return the built filter.
226
readFilterField :: (JSON a) =>
227
                   (a -> Filter a)   -- ^ Constructor
228
                -> [JSValue]         -- ^ Single argument
229
                -> Result (Filter a)
230
readFilterField constr [field] = constr <$> readJSON field
231
readFilterField _ v = Error $ "Cannot deserialise field, expected" ++
232
                              " [fieldname] but got " ++
233
                              show (pp_value (showJSON v))
234

    
235
-- | Helper to deserialise an array corresponding to a field and
236
-- value, returning the built filter.
237
readFilterFieldValue :: (JSON a, JSON b) =>
238
                        (a -> b -> Filter a) -- ^ Constructor
239
                     -> [JSValue]            -- ^ Arguments array
240
                     -> Result (Filter a)
241
readFilterFieldValue constr [field, value] =
242
  constr <$> readJSON field <*> readJSON value
243
readFilterFieldValue _ v =
244
  Error $ "Cannot deserialise field/value pair, expected [fieldname, value]" ++
245
          " but got " ++ show (pp_value (showJSON v))
246

    
247
-- | Inner deserialiser for 'Filter'.
248
readFilterArray :: (JSON a) => String -> [JSValue] -> Result (Filter a)
249
readFilterArray op args
250
  | op == C.qlangOpAnd      = AndFilter <$> mapM readJSON args
251
  | op == C.qlangOpOr       = OrFilter  <$> mapM readJSON args
252
  | op == C.qlangOpNot      = readFilterArg        NotFilter args
253
  | op == C.qlangOpTrue     = readFilterField      TrueFilter args
254
  | op == C.qlangOpEqual    = readFilterFieldValue EQFilter args
255
  | op == C.qlangOpLt       = readFilterFieldValue LTFilter args
256
  | op == C.qlangOpGt       = readFilterFieldValue GTFilter args
257
  | op == C.qlangOpLe       = readFilterFieldValue LEFilter args
258
  | op == C.qlangOpGe       = readFilterFieldValue GEFilter args
259
  | op == C.qlangOpRegexp   = readFilterFieldValue RegexpFilter args
260
  | op == C.qlangOpContains = readFilterFieldValue ContainsFilter args
261
  | otherwise = Error $ "Unknown filter operand '" ++ op ++ "'"
262

    
263
instance (JSON a) => JSON (Filter a) where
264
  showJSON = showFilter
265
  readJSON = readFilter
266

    
267
-- Traversable implementation for 'Filter'.
268
traverseFlt :: (Applicative f) => (a -> f b) -> Filter a -> f (Filter b)
269
traverseFlt _ EmptyFilter       = pure EmptyFilter
270
traverseFlt f (AndFilter flts)  = AndFilter <$> traverse (traverseFlt f) flts
271
traverseFlt f (OrFilter  flts)  = OrFilter  <$> traverse (traverseFlt f) flts
272
traverseFlt f (NotFilter flt)   = NotFilter <$> traverseFlt f flt
273
traverseFlt f (TrueFilter a)    = TrueFilter <$> f a
274
traverseFlt f (EQFilter a fval) = EQFilter <$> f a <*> pure fval
275
traverseFlt f (LTFilter a fval) = LTFilter <$> f a <*> pure fval
276
traverseFlt f (GTFilter a fval) = GTFilter <$> f a <*> pure fval
277
traverseFlt f (LEFilter a fval) = LEFilter <$> f a <*> pure fval
278
traverseFlt f (GEFilter a fval) = GEFilter <$> f a <*> pure fval
279
traverseFlt f (RegexpFilter a re)     = RegexpFilter <$> f a <*> pure re
280
traverseFlt f (ContainsFilter a fval) = ContainsFilter <$> f a <*> pure fval
281

    
282
instance Traversable Filter where
283
  traverse = traverseFlt
284

    
285
instance Functor Filter where
286
  fmap = fmapDefault
287

    
288
instance Foldable Filter where
289
  foldMap = foldMapDefault
290

    
291
-- | Field name to filter on.
292
type FilterField = String
293

    
294
-- | Value to compare the field value to, for filtering purposes.
295
data FilterValue = QuotedString String
296
                 | NumericValue Integer
297
                   deriving (Show, Eq)
298

    
299
-- | Serialiser for 'FilterValue'. The Python code just sends this to
300
-- JSON as-is, so we'll do the same.
301
showFilterValue :: FilterValue -> JSValue
302
showFilterValue (QuotedString str) = showJSON str
303
showFilterValue (NumericValue val) = showJSON val
304

    
305
-- | Decoder for 'FilterValue'. We have to see what it contains, since
306
-- the context doesn't give us hints on what to expect.
307
readFilterValue :: JSValue -> Result FilterValue
308
readFilterValue (JSString a) = Ok . QuotedString $ fromJSString a
309
readFilterValue (JSRational _ x) =
310
  if denominator x /= 1
311
    then Error $ "Cannot deserialise numeric filter value," ++
312
                 " expecting integral but got a fractional value: " ++
313
                 show x
314
    else Ok . NumericValue $ numerator x
315
readFilterValue v = Error $ "Cannot deserialise filter value, expecting" ++
316
                            " string or integer, got " ++ show (pp_value v)
317

    
318
instance JSON FilterValue where
319
  showJSON = showFilterValue
320
  readJSON = readFilterValue
321

    
322
-- | Regexp to apply to the filter value, for filtering purposes. It
323
-- holds both the string format, and the \"compiled\" format, so that
324
-- we don't re-compile the regex at each match attempt.
325
data FilterRegex = FilterRegex
326
  { stringRegex   :: String      -- ^ The string version of the regex
327
  , compiledRegex :: RegexType   -- ^ The compiled regex
328
  }
329

    
330
-- | Builder for 'FilterRegex'. We always attempt to compile the
331
-- regular expression on the initialisation of the data structure;
332
-- this might fail, if the RE is not well-formed.
333
mkRegex :: (Monad m) => String -> m FilterRegex
334
#ifndef NO_REGEX_PCRE
335
mkRegex str = do
336
  compiled <- case PCRE.getVersion of
337
                Nothing -> fail $ "regex-pcre library compiled without" ++
338
                                  " libpcre, regex functionality not available"
339
                _ -> PCRE.makeRegexM str
340
  return $ FilterRegex str compiled
341
#else
342
mkRegex _ =
343
  fail $ "regex-pcre not found at compile time," ++
344
         " regex functionality not available"
345
#endif
346

    
347
-- | 'Show' instance: we show the constructor plus the string version
348
-- of the regex.
349
instance Show FilterRegex where
350
  show (FilterRegex re _) = "mkRegex " ++ show re
351

    
352
-- | 'Eq' instance: we only compare the string versions of the regexes.
353
instance Eq FilterRegex where
354
  (FilterRegex re1 _) == (FilterRegex re2 _) = re1 == re2
355

    
356
-- | 'JSON' instance: like for show and read instances, we work only
357
-- with the string component.
358
instance JSON FilterRegex where
359
  showJSON (FilterRegex re _) = showJSON re
360
  readJSON s = do
361
    re <- readJSON s
362
    mkRegex re
363

    
364
-- | Name of a field.
365
type FieldName = String
366
-- | Title of a field, when represented in tabular format.
367
type FieldTitle = String
368
-- | Human redable description of a field.
369
type FieldDoc = String
370

    
371
-- | Definition of a field.
372
$(buildObject "FieldDefinition" "fdef"
373
  [ simpleField "name"  [t| FieldName  |] -- FIXME: the name has restrictions
374
  , simpleField "title" [t| FieldTitle |]
375
  , simpleField "kind"  [t| FieldType  |]
376
  , simpleField "doc"   [t| FieldDoc   |]
377
  ])
378

    
379
--- | Single field entry result.
380
data ResultEntry = ResultEntry
381
  { rentryStatus :: ResultStatus      -- ^ The result status
382
  , rentryValue  :: Maybe ResultValue -- ^ The (optional) result value
383
  } deriving (Show, Eq)
384

    
385
instance JSON ResultEntry where
386
  showJSON (ResultEntry rs rv) =
387
    showJSON (showJSON rs, maybe JSNull showJSON rv)
388
  readJSON v = do
389
    (rs, rv) <- readJSON v
390
    rv' <- case rv of
391
             JSNull -> return Nothing
392
             x -> Just <$> readJSON x
393
    return $ ResultEntry rs rv'
394

    
395
-- | The type of one result row.
396
type ResultRow = [ ResultEntry ]
397

    
398
-- | Value of a field, in json encoding.
399
-- (its type will be depending on ResultStatus and FieldType)
400
type ResultValue = JSValue
401

    
402
-- * Main Qlang queries and responses.
403

    
404
-- | Query2 query.
405
data Query = Query ItemType Fields (Filter FilterField)
406

    
407
-- | Query2 result.
408
$(buildObject "QueryResult" "qres"
409
  [ simpleField "fields" [t| [ FieldDefinition ] |]
410
  , simpleField "data"   [t| [ ResultRow       ] |]
411
  ])
412

    
413
-- | Query2 Fields query.
414
-- (to get supported fields names, descriptions, and types)
415
data QueryFields = QueryFields ItemType Fields
416

    
417
-- | Query2 Fields result.
418
$(buildObject "QueryFieldsResult" "qfieldres"
419
  [ simpleField "fields" [t| [FieldDefinition ] |]
420
  ])