Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query2.hs @ b647b6d7

History | View | Annotate | Download (4.1 kB)

1 ac13f473 Guido Trotter
{-# LANGUAGE TemplateHaskell #-}
2 ac13f473 Guido Trotter
3 ac13f473 Guido Trotter
{-| Implementation of the Ganeti Query2 language.
4 ac13f473 Guido Trotter
5 ac13f473 Guido Trotter
 -}
6 ac13f473 Guido Trotter
7 ac13f473 Guido Trotter
{-
8 ac13f473 Guido Trotter
9 ac13f473 Guido Trotter
Copyright (C) 2012 Google Inc.
10 ac13f473 Guido Trotter
11 ac13f473 Guido Trotter
This program is free software; you can redistribute it and/or modify
12 ac13f473 Guido Trotter
it under the terms of the GNU General Public License as published by
13 ac13f473 Guido Trotter
the Free Software Foundation; either version 2 of the License, or
14 ac13f473 Guido Trotter
(at your option) any later version.
15 ac13f473 Guido Trotter
16 ac13f473 Guido Trotter
This program is distributed in the hope that it will be useful, but
17 ac13f473 Guido Trotter
WITHOUT ANY WARRANTY; without even the implied warranty of
18 ac13f473 Guido Trotter
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 ac13f473 Guido Trotter
General Public License for more details.
20 ac13f473 Guido Trotter
21 ac13f473 Guido Trotter
You should have received a copy of the GNU General Public License
22 ac13f473 Guido Trotter
along with this program; if not, write to the Free Software
23 ac13f473 Guido Trotter
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 ac13f473 Guido Trotter
02110-1301, USA.
25 ac13f473 Guido Trotter
26 ac13f473 Guido Trotter
-}
27 ac13f473 Guido Trotter
28 ac13f473 Guido Trotter
module Ganeti.Query2
29 b647b6d7 Iustin Pop
    ( Filter(..)
30 b647b6d7 Iustin Pop
    , Query(..)
31 b647b6d7 Iustin Pop
    , QueryResult(..)
32 b647b6d7 Iustin Pop
    , QueryFields(..)
33 b647b6d7 Iustin Pop
    , QueryFieldsResult(..)
34 b647b6d7 Iustin Pop
    , FieldDefinition(..)
35 b647b6d7 Iustin Pop
    , ResultEntry(..)
36 ac13f473 Guido Trotter
    ) where
37 ac13f473 Guido Trotter
38 ac13f473 Guido Trotter
39 ac13f473 Guido Trotter
import Text.JSON.Types
40 ac13f473 Guido Trotter
import Text.JSON
41 ac13f473 Guido Trotter
42 ac13f473 Guido Trotter
import qualified Ganeti.Constants as C
43 ac13f473 Guido Trotter
import Ganeti.THH
44 ac13f473 Guido Trotter
45 ac13f473 Guido Trotter
-- * THH declarations, that require ordering.
46 ac13f473 Guido Trotter
47 ac13f473 Guido Trotter
-- | Status of a query field.
48 ac13f473 Guido Trotter
$(declareIADT "ResultStatus"
49 ac13f473 Guido Trotter
  [ ("RSNormal",  'C.rsNormal )
50 ac13f473 Guido Trotter
  , ("RSUnknown", 'C.rsUnknown )
51 ac13f473 Guido Trotter
  , ("RSNoData",  'C.rsNodata )
52 ac13f473 Guido Trotter
  , ("RSUnavail", 'C.rsUnavail )
53 ac13f473 Guido Trotter
  , ("RSOffline", 'C.rsOffline )
54 ac13f473 Guido Trotter
  ])
55 ac13f473 Guido Trotter
$(makeJSONInstance ''ResultStatus)
56 ac13f473 Guido Trotter
57 ac13f473 Guido Trotter
-- | Type of a query field.
58 ac13f473 Guido Trotter
$(declareSADT "FieldType"
59 ac13f473 Guido Trotter
  [ ("QFTUnknown",   'C.qftUnknown )
60 ac13f473 Guido Trotter
  , ("QFTText",      'C.qftText )
61 ac13f473 Guido Trotter
  , ("QFTBool",      'C.qftBool )
62 ac13f473 Guido Trotter
  , ("QFTNumber",    'C.qftNumber )
63 ac13f473 Guido Trotter
  , ("QFTUnit",      'C.qftUnit )
64 ac13f473 Guido Trotter
  , ("QFTTimestamp", 'C.qftTimestamp )
65 ac13f473 Guido Trotter
  , ("QFTOther",     'C.qftOther )
66 ac13f473 Guido Trotter
  ])
67 ac13f473 Guido Trotter
$(makeJSONInstance ''FieldType)
68 ac13f473 Guido Trotter
69 ac13f473 Guido Trotter
-- | Supported items on which Query2 works.
70 ac13f473 Guido Trotter
$(declareSADT "ItemType"
71 ac13f473 Guido Trotter
  [ ("QRCluster",  'C.qrCluster )
72 ac13f473 Guido Trotter
  , ("QRInstance", 'C.qrInstance )
73 ac13f473 Guido Trotter
  , ("QRNode",     'C.qrNode )
74 ac13f473 Guido Trotter
  , ("QRLock",     'C.qrLock )
75 ac13f473 Guido Trotter
  , ("QRGroup",    'C.qrGroup )
76 ac13f473 Guido Trotter
  , ("QROs",       'C.qrOs )
77 ac13f473 Guido Trotter
  , ("QRJob",      'C.qrJob )
78 ac13f473 Guido Trotter
  , ("QRExport",   'C.qrExport )
79 ac13f473 Guido Trotter
  ])
80 ac13f473 Guido Trotter
$(makeJSONInstance ''ItemType)
81 ac13f473 Guido Trotter
82 ac13f473 Guido Trotter
-- * Main Query2 queries and responses.
83 ac13f473 Guido Trotter
84 ac13f473 Guido Trotter
-- | Query2 query.
85 ac13f473 Guido Trotter
data Query = Query ItemType Fields (Maybe Filter)
86 ac13f473 Guido Trotter
87 ac13f473 Guido Trotter
-- | Query2 result.
88 ac13f473 Guido Trotter
data QueryResult = QueryResult [ FieldDefinition ] [ ResultEntry ]
89 ac13f473 Guido Trotter
90 ac13f473 Guido Trotter
-- | Query2 Fields query.
91 ac13f473 Guido Trotter
-- (to get supported fields names, descriptions, and types)
92 ac13f473 Guido Trotter
data QueryFields = QueryFields ItemType Fields
93 ac13f473 Guido Trotter
94 ac13f473 Guido Trotter
-- | Query2 Fields result.
95 ac13f473 Guido Trotter
data QueryFieldsResult = QueryFieldsResult [ FieldDefinition ]
96 ac13f473 Guido Trotter
97 ac13f473 Guido Trotter
-- * Sub data types for query2 queries and responses.
98 ac13f473 Guido Trotter
99 ac13f473 Guido Trotter
-- | List of requested fields.
100 ac13f473 Guido Trotter
type Fields = [ String ]
101 ac13f473 Guido Trotter
102 ac13f473 Guido Trotter
-- | Query2 filter expression.
103 ac13f473 Guido Trotter
data Filter
104 ac13f473 Guido Trotter
    = AndFilter [ Filter ] -- ^ & [<expression>, ...]
105 ac13f473 Guido Trotter
    | OrFilter [ Filter ] -- ^ | [<expression>, ...]
106 ac13f473 Guido Trotter
    | NotFilter Filter -- ^ ! <expression>
107 ac13f473 Guido Trotter
    | TrueFilter FilterField -- ^ ? <field>
108 ac13f473 Guido Trotter
    | EqualFilter FilterField FilterValue -- ^ (=|!=) <field> <value>
109 c664f05e Guido Trotter
    | LessThanFilter FilterField FilterValue -- ^ < <field> <value>
110 c664f05e Guido Trotter
    | GreaterThanFilter FilterField FilterValue -- ^ > <field> <value>
111 c664f05e Guido Trotter
    | LEThanFilter FilterField FilterValue -- ^ <= <field> <value>
112 c664f05e Guido Trotter
    | GEThanFilter FilterField FilterValue -- ^ >= <field> <value>
113 ac13f473 Guido Trotter
    | RegexpFilter FilterField FilterRegexp -- ^ =~ <field> <regexp>
114 ac13f473 Guido Trotter
    | ContainsFilter FilterField FilterValue -- ^ =[] <list-field> <value>
115 ac13f473 Guido Trotter
116 ac13f473 Guido Trotter
-- | Field name to filter on.
117 ac13f473 Guido Trotter
type FilterField = String
118 ac13f473 Guido Trotter
119 ac13f473 Guido Trotter
-- | Value to compare the field value to, for filtering purposes.
120 ac13f473 Guido Trotter
type FilterValue = String
121 ac13f473 Guido Trotter
122 ac13f473 Guido Trotter
-- | Regexp to apply to the filter value, for filteriong purposes.
123 ac13f473 Guido Trotter
type FilterRegexp = String
124 ac13f473 Guido Trotter
125 ac13f473 Guido Trotter
-- | Definition of a field.
126 ac13f473 Guido Trotter
data FieldDefinition = FieldDefinition FieldName FieldTitle FieldType FieldDoc
127 ac13f473 Guido Trotter
128 ac13f473 Guido Trotter
-- | Name of a field.
129 ac13f473 Guido Trotter
type FieldName = String
130 ac13f473 Guido Trotter
-- | Title of a field, when represented in tabular format.
131 ac13f473 Guido Trotter
type FieldTitle = String
132 ac13f473 Guido Trotter
-- | Human redable description of a field.
133 ac13f473 Guido Trotter
type FieldDoc = String
134 ac13f473 Guido Trotter
135 ac13f473 Guido Trotter
--- | Single field entry result.
136 ac13f473 Guido Trotter
data ResultEntry = ResultEntry ResultStatus (Maybe ResultValue)
137 ac13f473 Guido Trotter
138 ac13f473 Guido Trotter
-- | Value of a field, in json encoding.
139 ac13f473 Guido Trotter
-- (its type will be depending on ResultStatus and FieldType)
140 ac13f473 Guido Trotter
type ResultValue = JSValue