Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Language.hs @ 139c0683

History | View | Annotate | Download (14.9 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
    , QueryTypeLuxi(..)
52
    , checkRS
53
    ) where
54

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
281
instance Traversable Filter where
282
  traverse = traverseFlt
283

    
284
instance Functor Filter where
285
  fmap = fmapDefault
286

    
287
instance Foldable Filter where
288
  foldMap = foldMapDefault
289

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
401
-- * Main Qlang queries and responses.
402

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

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

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

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