Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Language.hs @ 13b17073

History | View | Annotate | Download (15.2 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 Control.DeepSeq
58
import Data.Foldable
59
import Data.Traversable (Traversable, traverse, fmapDefault, foldMapDefault)
60
import Data.Ratio (numerator, denominator)
61
import Text.JSON.Pretty (pp_value)
62
import Text.JSON.Types
63
import Text.JSON
64
#ifndef NO_REGEX_PCRE
65
import qualified Text.Regex.PCRE as PCRE
66
#endif
67

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

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

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

    
83
-- | No-op 'NFData' instance for 'ResultStatus', since it's a single
84
-- constructor data-type.
85
instance NFData ResultStatus
86

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

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

    
108
-- | Supported items on which Qlang works.
109
$(declareSADT "QueryTypeOp"
110
  [ ("QRCluster",  'C.qrCluster )
111
  , ("QRInstance", 'C.qrInstance )
112
  , ("QRNode",     'C.qrNode )
113
  , ("QRGroup",    'C.qrGroup )
114
  , ("QROs",       'C.qrOs )
115
  , ("QRExport",   'C.qrExport )
116
  ])
117
$(makeJSONInstance ''QueryTypeOp)
118

    
119
-- | Supported items on which Qlang works.
120
$(declareSADT "QueryTypeLuxi"
121
  [ ("QRLock",     'C.qrLock )
122
  , ("QRJob",      'C.qrJob )
123
  ])
124
$(makeJSONInstance ''QueryTypeLuxi)
125

    
126
-- | Overall query type.
127
data ItemType = ItemTypeLuxi QueryTypeLuxi
128
              | ItemTypeOpCode QueryTypeOp
129
                deriving (Show, Eq)
130

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

    
146
-- | Custom JSON instance for 'ItemType' since its encoding is not
147
-- consistent with the data type itself.
148
instance JSON ItemType where
149
  showJSON (ItemTypeLuxi x)  = showJSON x
150
  showJSON (ItemTypeOpCode y) = showJSON y
151
  readJSON = decodeItemType
152

    
153
-- * Sub data types for query2 queries and responses.
154

    
155
-- | Internal type of a regex expression (not exported).
156
#ifndef NO_REGEX_PCRE
157
type RegexType = PCRE.Regex
158
#else
159
type RegexType = ()
160
#endif
161

    
162
-- | List of requested fields.
163
type Fields = [ String ]
164

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

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

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

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

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

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

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

    
268
instance (JSON a) => JSON (Filter a) where
269
  showJSON = showFilter
270
  readJSON = readFilter
271

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

    
287
instance Traversable Filter where
288
  traverse = traverseFlt
289

    
290
instance Functor Filter where
291
  fmap = fmapDefault
292

    
293
instance Foldable Filter where
294
  foldMap = foldMapDefault
295

    
296
-- | Field name to filter on.
297
type FilterField = String
298

    
299
-- | Value to compare the field value to, for filtering purposes.
300
data FilterValue = QuotedString String
301
                 | NumericValue Integer
302
                   deriving (Show, Eq)
303

    
304
-- | Serialiser for 'FilterValue'. The Python code just sends this to
305
-- JSON as-is, so we'll do the same.
306
showFilterValue :: FilterValue -> JSValue
307
showFilterValue (QuotedString str) = showJSON str
308
showFilterValue (NumericValue val) = showJSON val
309

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

    
323
instance JSON FilterValue where
324
  showJSON = showFilterValue
325
  readJSON = readFilterValue
326

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

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

    
352
-- | 'Show' instance: we show the constructor plus the string version
353
-- of the regex.
354
instance Show FilterRegex where
355
  show (FilterRegex re _) = "mkRegex " ++ show re
356

    
357
-- | 'Eq' instance: we only compare the string versions of the regexes.
358
instance Eq FilterRegex where
359
  (FilterRegex re1 _) == (FilterRegex re2 _) = re1 == re2
360

    
361
-- | 'JSON' instance: like for show and read instances, we work only
362
-- with the string component.
363
instance JSON FilterRegex where
364
  showJSON (FilterRegex re _) = showJSON re
365
  readJSON s = readJSON s >>= mkRegex
366

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

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

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

    
388
instance NFData ResultEntry where
389
  rnf (ResultEntry rs rv) = rnf rs `seq` rnf rv
390

    
391
instance JSON ResultEntry where
392
  showJSON (ResultEntry rs rv) =
393
    showJSON (showJSON rs, maybe JSNull showJSON rv)
394
  readJSON v = do
395
    (rs, rv) <- readJSON v
396
    rv' <- case rv of
397
             JSNull -> return Nothing
398
             x -> Just <$> readJSON x
399
    return $ ResultEntry rs rv'
400

    
401
-- | The type of one result row.
402
type ResultRow = [ ResultEntry ]
403

    
404
-- | Value of a field, in json encoding.
405
-- (its type will be depending on ResultStatus and FieldType)
406
type ResultValue = JSValue
407

    
408
-- * Main Qlang queries and responses.
409

    
410
-- | Query2 query.
411
data Query = Query ItemType Fields (Filter FilterField)
412

    
413
-- | Query2 result.
414
$(buildObject "QueryResult" "qres"
415
  [ simpleField "fields" [t| [ FieldDefinition ] |]
416
  , simpleField "data"   [t| [ ResultRow       ] |]
417
  ])
418

    
419
-- | Query2 Fields query.
420
-- (to get supported fields names, descriptions, and types)
421
data QueryFields = QueryFields ItemType Fields
422

    
423
-- | Query2 Fields result.
424
$(buildObject "QueryFieldsResult" "qfieldres"
425
  [ simpleField "fields" [t| [FieldDefinition ] |]
426
  ])