Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Language.hs @ 3ce788db

History | View | Annotate | Download (13.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
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
    , checkRS
51
    ) where
52

    
53
import Control.Applicative
54
import Data.Foldable
55
import Data.Traversable (Traversable, traverse, fmapDefault, foldMapDefault)
56
import Data.Ratio (numerator, denominator)
57
import Text.JSON.Pretty (pp_value)
58
import Text.JSON.Types
59
import Text.JSON
60
import qualified Text.Regex.PCRE as PCRE
61

    
62
import qualified Ganeti.Constants as C
63
import Ganeti.THH
64
import Ganeti.JSON
65

    
66
-- * THH declarations, that require ordering.
67

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

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

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

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

    
112
-- * Sub data types for query2 queries and responses.
113

    
114
-- | List of requested fields.
115
type Fields = [ String ]
116

    
117
-- | Query2 filter expression. It's a parameteric type since we can
118
-- filter different \"things\"; e.g. field names, or actual field
119
-- getters, etc.
120
data Filter a
121
    = EmptyFilter                   -- ^ No filter at all
122
    | AndFilter      [ Filter a ]   -- ^ & [<expression>, ...]
123
    | OrFilter       [ Filter a ]   -- ^ | [<expression>, ...]
124
    | NotFilter      (Filter a)     -- ^ ! <expression>
125
    | TrueFilter     a              -- ^ ? <field>
126
    | EQFilter       a FilterValue  -- ^ (=|!=) <field> <value>
127
    | LTFilter       a FilterValue  -- ^ < <field> <value>
128
    | GTFilter       a FilterValue  -- ^ > <field> <value>
129
    | LEFilter       a FilterValue  -- ^ <= <field> <value>
130
    | GEFilter       a FilterValue  -- ^ >= <field> <value>
131
    | RegexpFilter   a FilterRegex  -- ^ =~ <field> <regexp>
132
    | ContainsFilter a FilterValue  -- ^ =[] <list-field> <value>
133
      deriving (Show, Read, Eq)
134

    
135
-- | Serialiser for the 'Filter' data type.
136
showFilter :: (JSON a) => Filter a -> JSValue
137
showFilter (EmptyFilter)          = JSNull
138
showFilter (AndFilter exprs)      =
139
  JSArray $ (showJSON C.qlangOpAnd):(map showJSON exprs)
140
showFilter (OrFilter  exprs)      =
141
  JSArray $ (showJSON C.qlangOpOr):(map showJSON exprs)
142
showFilter (NotFilter flt)        =
143
  JSArray [showJSON C.qlangOpNot, showJSON flt]
144
showFilter (TrueFilter field)     =
145
  JSArray [showJSON C.qlangOpTrue, showJSON field]
146
showFilter (EQFilter field value) =
147
  JSArray [showJSON C.qlangOpEqual, showJSON field, showJSON value]
148
showFilter (LTFilter field value) =
149
  JSArray [showJSON C.qlangOpLt, showJSON field, showJSON value]
150
showFilter (GTFilter field value) =
151
  JSArray [showJSON C.qlangOpGt, showJSON field, showJSON value]
152
showFilter (LEFilter field value) =
153
  JSArray [showJSON C.qlangOpLe, showJSON field, showJSON value]
154
showFilter (GEFilter field value) =
155
  JSArray [showJSON C.qlangOpGe, showJSON field, showJSON value]
156
showFilter (RegexpFilter field regexp) =
157
  JSArray [showJSON C.qlangOpRegexp, showJSON field, showJSON regexp]
158
showFilter (ContainsFilter field value) =
159
  JSArray [showJSON C.qlangOpContains, showJSON field, showJSON value]
160

    
161
-- | Deserializer for the 'Filter' data type.
162
readFilter :: (JSON a) => JSValue -> Result (Filter a)
163
readFilter JSNull = Ok EmptyFilter
164
readFilter (JSArray (JSString op:args)) =
165
  readFilterArray (fromJSString op) args
166
readFilter v =
167
  Error $ "Cannot deserialise filter: expected array [string, args], got " ++
168
        show (pp_value v)
169

    
170
-- | Helper to deserialise an array corresponding to a single filter
171
-- and return the built filter. Note this looks generic but is (at
172
-- least currently) only used for the NotFilter.
173
readFilterArg :: (JSON a) =>
174
                 (Filter a -> Filter a) -- ^ Constructor
175
              -> [JSValue]              -- ^ Single argument
176
              -> Result (Filter a)
177
readFilterArg constr [flt] = constr <$> readJSON flt
178
readFilterArg _ v = Error $ "Cannot deserialise field, expected [filter]\
179
                            \ but got " ++ show (pp_value (showJSON v))
180

    
181
-- | Helper to deserialise an array corresponding to a single field
182
-- and return the built filter.
183
readFilterField :: (JSON a) =>
184
                   (a -> Filter a)   -- ^ Constructor
185
                -> [JSValue]         -- ^ Single argument
186
                -> Result (Filter a)
187
readFilterField constr [field] = constr <$> readJSON field
188
readFilterField _ v = Error $ "Cannot deserialise field, expected [fieldname]\
189
                              \ but got " ++ show (pp_value (showJSON v))
190

    
191
-- | Helper to deserialise an array corresponding to a field and
192
-- value, returning the built filter.
193
readFilterFieldValue :: (JSON a, JSON b) =>
194
                        (a -> b -> Filter a) -- ^ Constructor
195
                     -> [JSValue]            -- ^ Arguments array
196
                     -> Result (Filter a)
197
readFilterFieldValue constr [field, value] =
198
  constr <$> readJSON field <*> readJSON value
199
readFilterFieldValue _ v =
200
  Error $ "Cannot deserialise field/value pair, expected [fieldname, value]\
201
          \ but got " ++ show (pp_value (showJSON v))
202

    
203
-- | Inner deserialiser for 'Filter'.
204
readFilterArray :: (JSON a) => String -> [JSValue] -> Result (Filter a)
205
readFilterArray op args
206
  | op == C.qlangOpAnd      = AndFilter <$> mapM readJSON args
207
  | op == C.qlangOpOr       = OrFilter  <$> mapM readJSON args
208
  | op == C.qlangOpNot      = readFilterArg        NotFilter args
209
  | op == C.qlangOpTrue     = readFilterField      TrueFilter args
210
  | op == C.qlangOpEqual    = readFilterFieldValue EQFilter args
211
  | op == C.qlangOpLt       = readFilterFieldValue LTFilter args
212
  | op == C.qlangOpGt       = readFilterFieldValue GTFilter args
213
  | op == C.qlangOpLe       = readFilterFieldValue LEFilter args
214
  | op == C.qlangOpGe       = readFilterFieldValue GEFilter args
215
  | op == C.qlangOpRegexp   = readFilterFieldValue RegexpFilter args
216
  | op == C.qlangOpContains = readFilterFieldValue ContainsFilter args
217
  | otherwise = Error $ "Unknown filter operand '" ++ op ++ "'"
218

    
219
instance (JSON a) => JSON (Filter a) where
220
  showJSON = showFilter
221
  readJSON = readFilter
222

    
223
-- Traversable implementation for 'Filter'.
224
traverseFlt :: (Applicative f) => (a -> f b) -> Filter a -> f (Filter b)
225
traverseFlt _ EmptyFilter       = pure EmptyFilter
226
traverseFlt f (AndFilter flts)  = AndFilter <$> (traverse (traverseFlt f) flts)
227
traverseFlt f (OrFilter  flts)  = OrFilter  <$> (traverse (traverseFlt f) flts)
228
traverseFlt f (NotFilter flt)   = NotFilter <$> (traverseFlt f flt)
229
traverseFlt f (TrueFilter a)    = TrueFilter <$> f a
230
traverseFlt f (EQFilter a fval) = EQFilter <$> f a <*> pure fval
231
traverseFlt f (LTFilter a fval) = LTFilter <$> f a <*> pure fval
232
traverseFlt f (GTFilter a fval) = GTFilter <$> f a <*> pure fval
233
traverseFlt f (LEFilter a fval) = LEFilter <$> f a <*> pure fval
234
traverseFlt f (GEFilter a fval) = GEFilter <$> f a <*> pure fval
235
traverseFlt f (RegexpFilter a re)     = RegexpFilter <$> f a <*> pure re
236
traverseFlt f (ContainsFilter a fval) = ContainsFilter <$> f a <*> pure fval
237

    
238
instance Traversable Filter where
239
  traverse = traverseFlt
240

    
241
instance Functor Filter where
242
  fmap = fmapDefault
243

    
244
instance Foldable Filter where
245
  foldMap = foldMapDefault
246

    
247
-- | Field name to filter on.
248
type FilterField = String
249

    
250
-- | Value to compare the field value to, for filtering purposes.
251
data FilterValue = QuotedString String
252
                 | NumericValue Integer
253
                   deriving (Read, Show, Eq)
254

    
255
-- | Serialiser for 'FilterValue'. The Python code just sends this to
256
-- JSON as-is, so we'll do the same.
257
showFilterValue :: FilterValue -> JSValue
258
showFilterValue (QuotedString str) = showJSON str
259
showFilterValue (NumericValue val) = showJSON val
260

    
261
-- | Decoder for 'FilterValue'. We have to see what it contains, since
262
-- the context doesn't give us hints on what to expect.
263
readFilterValue :: JSValue -> Result FilterValue
264
readFilterValue (JSString a) = Ok . QuotedString $ fromJSString a
265
readFilterValue (JSRational _ x) =
266
  if denominator x /= 1
267
    then Error $ "Cannot deserialise numeric filter value,\
268
                 \ expecting integral but\
269
                 \ got a fractional value: " ++ show x
270
    else Ok . NumericValue $ numerator x
271
readFilterValue v = Error $ "Cannot deserialise filter value, expecting\
272
                            \ string or integer, got " ++ show (pp_value v)
273

    
274
instance JSON FilterValue where
275
  showJSON = showFilterValue
276
  readJSON = readFilterValue
277

    
278
-- | Regexp to apply to the filter value, for filtering purposes. It
279
-- holds both the string format, and the \"compiled\" format, so that
280
-- we don't re-compile the regex at each match attempt.
281
data FilterRegex = FilterRegex
282
  { stringRegex   :: String      -- ^ The string version of the regex
283
  , compiledRegex :: PCRE.Regex  -- ^ The compiled regex
284
  }
285

    
286
-- | Builder for 'FilterRegex'. We always attempt to compile the
287
-- regular expression on the initialisation of the data structure;
288
-- this might fail, if the RE is not well-formed.
289
mkRegex :: (Monad m) => String -> m FilterRegex
290
mkRegex str = do
291
  compiled <- case PCRE.getVersion of
292
                Nothing -> fail "regex-pcre library compiled without\
293
                                \ libpcre, regex functionality not available"
294
                _ -> PCRE.makeRegexM str
295
  return $ FilterRegex str compiled
296

    
297
-- | 'Show' instance: we show the constructor plus the string version
298
-- of the regex.
299
instance Show FilterRegex where
300
  show (FilterRegex re _) = "mkRegex " ++ show re
301

    
302
-- | 'Read' instance: we manually read \"mkRegex\" followed by a
303
-- string, and build the 'FilterRegex' using that.
304
instance Read FilterRegex where
305
  readsPrec _ str = do
306
    ("mkRegex", s') <- lex str
307
    (re, s'') <- reads s'
308
    filterre <- mkRegex re
309
    return (filterre, s'')
310

    
311
-- | 'Eq' instance: we only compare the string versions of the regexes.
312
instance Eq FilterRegex where
313
  (FilterRegex re1 _) == (FilterRegex re2 _) = re1 == re2
314

    
315
-- | 'JSON' instance: like for show and read instances, we work only
316
-- with the string component.
317
instance JSON FilterRegex where
318
  showJSON (FilterRegex re _) = showJSON re
319
  readJSON s = do
320
    re <- readJSON s
321
    mkRegex re
322

    
323
-- | Name of a field.
324
type FieldName = String
325
-- | Title of a field, when represented in tabular format.
326
type FieldTitle = String
327
-- | Human redable description of a field.
328
type FieldDoc = String
329

    
330
-- | Definition of a field.
331
$(buildObject "FieldDefinition" "fdef"
332
  [ simpleField "name"  [t| FieldName  |] -- FIXME: the name has restrictions
333
  , simpleField "title" [t| FieldTitle |]
334
  , simpleField "kind"  [t| FieldType  |]
335
  , simpleField "doc"   [t| FieldDoc   |]
336
  ])
337

    
338
--- | Single field entry result.
339
data ResultEntry = ResultEntry
340
  { rentryStatus :: ResultStatus      -- ^ The result status
341
  , rentryValue  :: Maybe ResultValue -- ^ The (optional) result value
342
  } deriving (Show, Read, Eq)
343

    
344
instance JSON ResultEntry where
345
  showJSON (ResultEntry rs rv) =
346
    showJSON (showJSON rs, maybe JSNull showJSON rv)
347
  readJSON v = do
348
    (rs, rv) <- readJSON v
349
    rv' <- case rv of
350
             JSNull -> return Nothing
351
             x -> Just <$> readJSON x
352
    return $ ResultEntry rs rv'
353

    
354
-- | The type of one result row.
355
type ResultRow = [ ResultEntry ]
356

    
357
-- | Value of a field, in json encoding.
358
-- (its type will be depending on ResultStatus and FieldType)
359
type ResultValue = JSValue
360

    
361
-- * Main Qlang queries and responses.
362

    
363
-- | Query2 query.
364
data Query = Query ItemType Fields (Filter FilterField)
365

    
366
-- | Query2 result.
367
$(buildObject "QueryResult" "qres"
368
  [ simpleField "fields" [t| [ FieldDefinition ] |]
369
  , simpleField "data"   [t| [ ResultRow       ] |]
370
  ])
371

    
372
-- | Query2 Fields query.
373
-- (to get supported fields names, descriptions, and types)
374
data QueryFields = QueryFields ItemType Fields
375

    
376
-- | Query2 Fields result.
377
$(buildObject "QueryFieldsResult" "qfieldres"
378
  [ simpleField "fields" [t| [FieldDefinition ] |]
379
  ])