Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Query / Language.hs @ 7ae97c33

History | View | Annotate | Download (14.1 kB)

1 7ae97c33 Iustin Pop
{-# LANGUAGE TemplateHaskell, CPP #-}
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 4cab6703 Iustin Pop
module Ganeti.Query.Language
29 b647b6d7 Iustin Pop
    ( Filter(..)
30 05ac718f Iustin Pop
    , FilterField
31 e8a25d62 Iustin Pop
    , FilterValue(..)
32 01606931 Iustin Pop
    , FilterRegex -- note: we don't export the constructor, must use helpers
33 01606931 Iustin Pop
    , mkRegex
34 01606931 Iustin Pop
    , stringRegex
35 01606931 Iustin Pop
    , compiledRegex
36 4cbe9bda Iustin Pop
    , Fields
37 b647b6d7 Iustin Pop
    , Query(..)
38 b647b6d7 Iustin Pop
    , QueryResult(..)
39 b647b6d7 Iustin Pop
    , QueryFields(..)
40 b647b6d7 Iustin Pop
    , QueryFieldsResult(..)
41 046fe3f5 Iustin Pop
    , FieldName
42 046fe3f5 Iustin Pop
    , FieldTitle
43 4cbe9bda Iustin Pop
    , FieldType(..)
44 046fe3f5 Iustin Pop
    , FieldDoc
45 b647b6d7 Iustin Pop
    , FieldDefinition(..)
46 b647b6d7 Iustin Pop
    , ResultEntry(..)
47 4cbe9bda Iustin Pop
    , ResultStatus(..)
48 046fe3f5 Iustin Pop
    , ResultValue
49 8a9ee1e9 Iustin Pop
    , ItemType(..)
50 62377cf5 Iustin Pop
    , checkRS
51 ac13f473 Guido Trotter
    ) where
52 ac13f473 Guido Trotter
53 e8a25d62 Iustin Pop
import Control.Applicative
54 05ac718f Iustin Pop
import Data.Foldable
55 05ac718f Iustin Pop
import Data.Traversable (Traversable, traverse, fmapDefault, foldMapDefault)
56 e8a25d62 Iustin Pop
import Data.Ratio (numerator, denominator)
57 e8a25d62 Iustin Pop
import Text.JSON.Pretty (pp_value)
58 ac13f473 Guido Trotter
import Text.JSON.Types
59 ac13f473 Guido Trotter
import Text.JSON
60 7ae97c33 Iustin Pop
#ifndef NO_REGEX_PCRE
61 01606931 Iustin Pop
import qualified Text.Regex.PCRE as PCRE
62 7ae97c33 Iustin Pop
#endif
63 ac13f473 Guido Trotter
64 ac13f473 Guido Trotter
import qualified Ganeti.Constants as C
65 ac13f473 Guido Trotter
import Ganeti.THH
66 f3baf5ef Iustin Pop
import Ganeti.JSON
67 ac13f473 Guido Trotter
68 ac13f473 Guido Trotter
-- * THH declarations, that require ordering.
69 ac13f473 Guido Trotter
70 ac13f473 Guido Trotter
-- | Status of a query field.
71 ac13f473 Guido Trotter
$(declareIADT "ResultStatus"
72 ac13f473 Guido Trotter
  [ ("RSNormal",  'C.rsNormal )
73 ac13f473 Guido Trotter
  , ("RSUnknown", 'C.rsUnknown )
74 ac13f473 Guido Trotter
  , ("RSNoData",  'C.rsNodata )
75 ac13f473 Guido Trotter
  , ("RSUnavail", 'C.rsUnavail )
76 ac13f473 Guido Trotter
  , ("RSOffline", 'C.rsOffline )
77 ac13f473 Guido Trotter
  ])
78 ac13f473 Guido Trotter
$(makeJSONInstance ''ResultStatus)
79 ac13f473 Guido Trotter
80 62377cf5 Iustin Pop
-- | Check that ResultStatus is success or fail with descriptive
81 62377cf5 Iustin Pop
-- message.
82 62377cf5 Iustin Pop
checkRS :: (Monad m) => ResultStatus -> a -> m a
83 62377cf5 Iustin Pop
checkRS RSNormal val = return val
84 62377cf5 Iustin Pop
checkRS RSUnknown  _ = fail "Unknown field"
85 62377cf5 Iustin Pop
checkRS RSNoData   _ = fail "No data for a field"
86 62377cf5 Iustin Pop
checkRS RSUnavail  _ = fail "Ganeti reports unavailable data"
87 62377cf5 Iustin Pop
checkRS RSOffline  _ = fail "Ganeti reports resource as offline"
88 62377cf5 Iustin Pop
89 ac13f473 Guido Trotter
-- | Type of a query field.
90 ac13f473 Guido Trotter
$(declareSADT "FieldType"
91 ac13f473 Guido Trotter
  [ ("QFTUnknown",   'C.qftUnknown )
92 ac13f473 Guido Trotter
  , ("QFTText",      'C.qftText )
93 ac13f473 Guido Trotter
  , ("QFTBool",      'C.qftBool )
94 ac13f473 Guido Trotter
  , ("QFTNumber",    'C.qftNumber )
95 ac13f473 Guido Trotter
  , ("QFTUnit",      'C.qftUnit )
96 ac13f473 Guido Trotter
  , ("QFTTimestamp", 'C.qftTimestamp )
97 ac13f473 Guido Trotter
  , ("QFTOther",     'C.qftOther )
98 ac13f473 Guido Trotter
  ])
99 ac13f473 Guido Trotter
$(makeJSONInstance ''FieldType)
100 ac13f473 Guido Trotter
101 dc6a0f82 Iustin Pop
-- | Supported items on which Qlang works.
102 ac13f473 Guido Trotter
$(declareSADT "ItemType"
103 ac13f473 Guido Trotter
  [ ("QRCluster",  'C.qrCluster )
104 ac13f473 Guido Trotter
  , ("QRInstance", 'C.qrInstance )
105 ac13f473 Guido Trotter
  , ("QRNode",     'C.qrNode )
106 ac13f473 Guido Trotter
  , ("QRLock",     'C.qrLock )
107 ac13f473 Guido Trotter
  , ("QRGroup",    'C.qrGroup )
108 ac13f473 Guido Trotter
  , ("QROs",       'C.qrOs )
109 ac13f473 Guido Trotter
  , ("QRJob",      'C.qrJob )
110 ac13f473 Guido Trotter
  , ("QRExport",   'C.qrExport )
111 ac13f473 Guido Trotter
  ])
112 ac13f473 Guido Trotter
$(makeJSONInstance ''ItemType)
113 ac13f473 Guido Trotter
114 ac13f473 Guido Trotter
-- * Sub data types for query2 queries and responses.
115 ac13f473 Guido Trotter
116 7ae97c33 Iustin Pop
-- | Internal type of a regex expression (not exported).
117 7ae97c33 Iustin Pop
#ifndef NO_REGEX_PCRE
118 7ae97c33 Iustin Pop
type RegexType = PCRE.Regex
119 7ae97c33 Iustin Pop
#else
120 7ae97c33 Iustin Pop
type RegexType = ()
121 7ae97c33 Iustin Pop
#endif
122 7ae97c33 Iustin Pop
123 ac13f473 Guido Trotter
-- | List of requested fields.
124 ac13f473 Guido Trotter
type Fields = [ String ]
125 ac13f473 Guido Trotter
126 05ac718f Iustin Pop
-- | Query2 filter expression. It's a parameteric type since we can
127 05ac718f Iustin Pop
-- filter different \"things\"; e.g. field names, or actual field
128 05ac718f Iustin Pop
-- getters, etc.
129 05ac718f Iustin Pop
data Filter a
130 05ac718f Iustin Pop
    = EmptyFilter                   -- ^ No filter at all
131 05ac718f Iustin Pop
    | AndFilter      [ Filter a ]   -- ^ & [<expression>, ...]
132 05ac718f Iustin Pop
    | OrFilter       [ Filter a ]   -- ^ | [<expression>, ...]
133 05ac718f Iustin Pop
    | NotFilter      (Filter a)     -- ^ ! <expression>
134 05ac718f Iustin Pop
    | TrueFilter     a              -- ^ ? <field>
135 05ac718f Iustin Pop
    | EQFilter       a FilterValue  -- ^ (=|!=) <field> <value>
136 05ac718f Iustin Pop
    | LTFilter       a FilterValue  -- ^ < <field> <value>
137 05ac718f Iustin Pop
    | GTFilter       a FilterValue  -- ^ > <field> <value>
138 05ac718f Iustin Pop
    | LEFilter       a FilterValue  -- ^ <= <field> <value>
139 05ac718f Iustin Pop
    | GEFilter       a FilterValue  -- ^ >= <field> <value>
140 01606931 Iustin Pop
    | RegexpFilter   a FilterRegex  -- ^ =~ <field> <regexp>
141 05ac718f Iustin Pop
    | ContainsFilter a FilterValue  -- ^ =[] <list-field> <value>
142 e8a25d62 Iustin Pop
      deriving (Show, Read, Eq)
143 e8a25d62 Iustin Pop
144 e8a25d62 Iustin Pop
-- | Serialiser for the 'Filter' data type.
145 05ac718f Iustin Pop
showFilter :: (JSON a) => Filter a -> JSValue
146 e8a25d62 Iustin Pop
showFilter (EmptyFilter)          = JSNull
147 e8a25d62 Iustin Pop
showFilter (AndFilter exprs)      =
148 5b11f8db Iustin Pop
  JSArray $ showJSON C.qlangOpAnd : map showJSON exprs
149 e8a25d62 Iustin Pop
showFilter (OrFilter  exprs)      =
150 5b11f8db Iustin Pop
  JSArray $ showJSON C.qlangOpOr : map showJSON exprs
151 e8a25d62 Iustin Pop
showFilter (NotFilter flt)        =
152 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpNot, showJSON flt]
153 e8a25d62 Iustin Pop
showFilter (TrueFilter field)     =
154 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpTrue, showJSON field]
155 e8a25d62 Iustin Pop
showFilter (EQFilter field value) =
156 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpEqual, showJSON field, showJSON value]
157 e8a25d62 Iustin Pop
showFilter (LTFilter field value) =
158 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpLt, showJSON field, showJSON value]
159 e8a25d62 Iustin Pop
showFilter (GTFilter field value) =
160 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpGt, showJSON field, showJSON value]
161 e8a25d62 Iustin Pop
showFilter (LEFilter field value) =
162 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpLe, showJSON field, showJSON value]
163 e8a25d62 Iustin Pop
showFilter (GEFilter field value) =
164 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpGe, showJSON field, showJSON value]
165 e8a25d62 Iustin Pop
showFilter (RegexpFilter field regexp) =
166 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpRegexp, showJSON field, showJSON regexp]
167 e8a25d62 Iustin Pop
showFilter (ContainsFilter field value) =
168 e8a25d62 Iustin Pop
  JSArray [showJSON C.qlangOpContains, showJSON field, showJSON value]
169 e8a25d62 Iustin Pop
170 e8a25d62 Iustin Pop
-- | Deserializer for the 'Filter' data type.
171 05ac718f Iustin Pop
readFilter :: (JSON a) => JSValue -> Result (Filter a)
172 e8a25d62 Iustin Pop
readFilter JSNull = Ok EmptyFilter
173 e8a25d62 Iustin Pop
readFilter (JSArray (JSString op:args)) =
174 e8a25d62 Iustin Pop
  readFilterArray (fromJSString op) args
175 e8a25d62 Iustin Pop
readFilter v =
176 e8a25d62 Iustin Pop
  Error $ "Cannot deserialise filter: expected array [string, args], got " ++
177 e8a25d62 Iustin Pop
        show (pp_value v)
178 e8a25d62 Iustin Pop
179 e8a25d62 Iustin Pop
-- | Helper to deserialise an array corresponding to a single filter
180 e8a25d62 Iustin Pop
-- and return the built filter. Note this looks generic but is (at
181 e8a25d62 Iustin Pop
-- least currently) only used for the NotFilter.
182 05ac718f Iustin Pop
readFilterArg :: (JSON a) =>
183 05ac718f Iustin Pop
                 (Filter a -> Filter a) -- ^ Constructor
184 05ac718f Iustin Pop
              -> [JSValue]              -- ^ Single argument
185 05ac718f Iustin Pop
              -> Result (Filter a)
186 e8a25d62 Iustin Pop
readFilterArg constr [flt] = constr <$> readJSON flt
187 7ae97c33 Iustin Pop
readFilterArg _ v = Error $ "Cannot deserialise field, expected [filter]" ++
188 7ae97c33 Iustin Pop
                            " but got " ++ show (pp_value (showJSON v))
189 e8a25d62 Iustin Pop
190 e8a25d62 Iustin Pop
-- | Helper to deserialise an array corresponding to a single field
191 e8a25d62 Iustin Pop
-- and return the built filter.
192 05ac718f Iustin Pop
readFilterField :: (JSON a) =>
193 05ac718f Iustin Pop
                   (a -> Filter a)   -- ^ Constructor
194 05ac718f Iustin Pop
                -> [JSValue]         -- ^ Single argument
195 05ac718f Iustin Pop
                -> Result (Filter a)
196 e8a25d62 Iustin Pop
readFilterField constr [field] = constr <$> readJSON field
197 7ae97c33 Iustin Pop
readFilterField _ v = Error $ "Cannot deserialise field, expected" ++
198 7ae97c33 Iustin Pop
                              " [fieldname] but got " ++
199 7ae97c33 Iustin Pop
                              show (pp_value (showJSON v))
200 e8a25d62 Iustin Pop
201 e8a25d62 Iustin Pop
-- | Helper to deserialise an array corresponding to a field and
202 e8a25d62 Iustin Pop
-- value, returning the built filter.
203 05ac718f Iustin Pop
readFilterFieldValue :: (JSON a, JSON b) =>
204 05ac718f Iustin Pop
                        (a -> b -> Filter a) -- ^ Constructor
205 05ac718f Iustin Pop
                     -> [JSValue]            -- ^ Arguments array
206 05ac718f Iustin Pop
                     -> Result (Filter a)
207 e8a25d62 Iustin Pop
readFilterFieldValue constr [field, value] =
208 e8a25d62 Iustin Pop
  constr <$> readJSON field <*> readJSON value
209 e8a25d62 Iustin Pop
readFilterFieldValue _ v =
210 7ae97c33 Iustin Pop
  Error $ "Cannot deserialise field/value pair, expected [fieldname, value]" ++
211 7ae97c33 Iustin Pop
          " but got " ++ show (pp_value (showJSON v))
212 e8a25d62 Iustin Pop
213 e8a25d62 Iustin Pop
-- | Inner deserialiser for 'Filter'.
214 05ac718f Iustin Pop
readFilterArray :: (JSON a) => String -> [JSValue] -> Result (Filter a)
215 e8a25d62 Iustin Pop
readFilterArray op args
216 e8a25d62 Iustin Pop
  | op == C.qlangOpAnd      = AndFilter <$> mapM readJSON args
217 e8a25d62 Iustin Pop
  | op == C.qlangOpOr       = OrFilter  <$> mapM readJSON args
218 e8a25d62 Iustin Pop
  | op == C.qlangOpNot      = readFilterArg        NotFilter args
219 e8a25d62 Iustin Pop
  | op == C.qlangOpTrue     = readFilterField      TrueFilter args
220 e8a25d62 Iustin Pop
  | op == C.qlangOpEqual    = readFilterFieldValue EQFilter args
221 e8a25d62 Iustin Pop
  | op == C.qlangOpLt       = readFilterFieldValue LTFilter args
222 e8a25d62 Iustin Pop
  | op == C.qlangOpGt       = readFilterFieldValue GTFilter args
223 e8a25d62 Iustin Pop
  | op == C.qlangOpLe       = readFilterFieldValue LEFilter args
224 e8a25d62 Iustin Pop
  | op == C.qlangOpGe       = readFilterFieldValue GEFilter args
225 e8a25d62 Iustin Pop
  | op == C.qlangOpRegexp   = readFilterFieldValue RegexpFilter args
226 e8a25d62 Iustin Pop
  | op == C.qlangOpContains = readFilterFieldValue ContainsFilter args
227 e8a25d62 Iustin Pop
  | otherwise = Error $ "Unknown filter operand '" ++ op ++ "'"
228 e8a25d62 Iustin Pop
229 05ac718f Iustin Pop
instance (JSON a) => JSON (Filter a) where
230 e8a25d62 Iustin Pop
  showJSON = showFilter
231 e8a25d62 Iustin Pop
  readJSON = readFilter
232 ac13f473 Guido Trotter
233 05ac718f Iustin Pop
-- Traversable implementation for 'Filter'.
234 05ac718f Iustin Pop
traverseFlt :: (Applicative f) => (a -> f b) -> Filter a -> f (Filter b)
235 05ac718f Iustin Pop
traverseFlt _ EmptyFilter       = pure EmptyFilter
236 5b11f8db Iustin Pop
traverseFlt f (AndFilter flts)  = AndFilter <$> traverse (traverseFlt f) flts
237 5b11f8db Iustin Pop
traverseFlt f (OrFilter  flts)  = OrFilter  <$> traverse (traverseFlt f) flts
238 5b11f8db Iustin Pop
traverseFlt f (NotFilter flt)   = NotFilter <$> traverseFlt f flt
239 05ac718f Iustin Pop
traverseFlt f (TrueFilter a)    = TrueFilter <$> f a
240 05ac718f Iustin Pop
traverseFlt f (EQFilter a fval) = EQFilter <$> f a <*> pure fval
241 05ac718f Iustin Pop
traverseFlt f (LTFilter a fval) = LTFilter <$> f a <*> pure fval
242 05ac718f Iustin Pop
traverseFlt f (GTFilter a fval) = GTFilter <$> f a <*> pure fval
243 05ac718f Iustin Pop
traverseFlt f (LEFilter a fval) = LEFilter <$> f a <*> pure fval
244 05ac718f Iustin Pop
traverseFlt f (GEFilter a fval) = GEFilter <$> f a <*> pure fval
245 05ac718f Iustin Pop
traverseFlt f (RegexpFilter a re)     = RegexpFilter <$> f a <*> pure re
246 05ac718f Iustin Pop
traverseFlt f (ContainsFilter a fval) = ContainsFilter <$> f a <*> pure fval
247 05ac718f Iustin Pop
248 05ac718f Iustin Pop
instance Traversable Filter where
249 05ac718f Iustin Pop
  traverse = traverseFlt
250 05ac718f Iustin Pop
251 05ac718f Iustin Pop
instance Functor Filter where
252 05ac718f Iustin Pop
  fmap = fmapDefault
253 05ac718f Iustin Pop
254 05ac718f Iustin Pop
instance Foldable Filter where
255 05ac718f Iustin Pop
  foldMap = foldMapDefault
256 05ac718f Iustin Pop
257 ac13f473 Guido Trotter
-- | Field name to filter on.
258 ac13f473 Guido Trotter
type FilterField = String
259 ac13f473 Guido Trotter
260 ac13f473 Guido Trotter
-- | Value to compare the field value to, for filtering purposes.
261 e8a25d62 Iustin Pop
data FilterValue = QuotedString String
262 e8a25d62 Iustin Pop
                 | NumericValue Integer
263 e8a25d62 Iustin Pop
                   deriving (Read, Show, Eq)
264 e8a25d62 Iustin Pop
265 e8a25d62 Iustin Pop
-- | Serialiser for 'FilterValue'. The Python code just sends this to
266 e8a25d62 Iustin Pop
-- JSON as-is, so we'll do the same.
267 e8a25d62 Iustin Pop
showFilterValue :: FilterValue -> JSValue
268 e8a25d62 Iustin Pop
showFilterValue (QuotedString str) = showJSON str
269 e8a25d62 Iustin Pop
showFilterValue (NumericValue val) = showJSON val
270 e8a25d62 Iustin Pop
271 e8a25d62 Iustin Pop
-- | Decoder for 'FilterValue'. We have to see what it contains, since
272 e8a25d62 Iustin Pop
-- the context doesn't give us hints on what to expect.
273 e8a25d62 Iustin Pop
readFilterValue :: JSValue -> Result FilterValue
274 e8a25d62 Iustin Pop
readFilterValue (JSString a) = Ok . QuotedString $ fromJSString a
275 e8a25d62 Iustin Pop
readFilterValue (JSRational _ x) =
276 e8a25d62 Iustin Pop
  if denominator x /= 1
277 7ae97c33 Iustin Pop
    then Error $ "Cannot deserialise numeric filter value," ++
278 7ae97c33 Iustin Pop
                 " expecting integral but got a fractional value: " ++
279 7ae97c33 Iustin Pop
                 show x
280 e8a25d62 Iustin Pop
    else Ok . NumericValue $ numerator x
281 7ae97c33 Iustin Pop
readFilterValue v = Error $ "Cannot deserialise filter value, expecting" ++
282 7ae97c33 Iustin Pop
                            " string or integer, got " ++ show (pp_value v)
283 e8a25d62 Iustin Pop
284 e8a25d62 Iustin Pop
instance JSON FilterValue where
285 e8a25d62 Iustin Pop
  showJSON = showFilterValue
286 e8a25d62 Iustin Pop
  readJSON = readFilterValue
287 ac13f473 Guido Trotter
288 01606931 Iustin Pop
-- | Regexp to apply to the filter value, for filtering purposes. It
289 01606931 Iustin Pop
-- holds both the string format, and the \"compiled\" format, so that
290 01606931 Iustin Pop
-- we don't re-compile the regex at each match attempt.
291 01606931 Iustin Pop
data FilterRegex = FilterRegex
292 01606931 Iustin Pop
  { stringRegex   :: String      -- ^ The string version of the regex
293 7ae97c33 Iustin Pop
  , compiledRegex :: RegexType   -- ^ The compiled regex
294 01606931 Iustin Pop
  }
295 01606931 Iustin Pop
296 01606931 Iustin Pop
-- | Builder for 'FilterRegex'. We always attempt to compile the
297 01606931 Iustin Pop
-- regular expression on the initialisation of the data structure;
298 01606931 Iustin Pop
-- this might fail, if the RE is not well-formed.
299 01606931 Iustin Pop
mkRegex :: (Monad m) => String -> m FilterRegex
300 7ae97c33 Iustin Pop
#ifndef NO_REGEX_PCRE
301 01606931 Iustin Pop
mkRegex str = do
302 01606931 Iustin Pop
  compiled <- case PCRE.getVersion of
303 7ae97c33 Iustin Pop
                Nothing -> fail $ "regex-pcre library compiled without" ++
304 7ae97c33 Iustin Pop
                                  " libpcre, regex functionality not available"
305 01606931 Iustin Pop
                _ -> PCRE.makeRegexM str
306 01606931 Iustin Pop
  return $ FilterRegex str compiled
307 7ae97c33 Iustin Pop
#else
308 7ae97c33 Iustin Pop
mkRegex _ =
309 7ae97c33 Iustin Pop
  fail $ "regex-pcre not found at compile time," ++
310 7ae97c33 Iustin Pop
         " regex functionality not available"
311 7ae97c33 Iustin Pop
#endif
312 01606931 Iustin Pop
313 01606931 Iustin Pop
-- | 'Show' instance: we show the constructor plus the string version
314 01606931 Iustin Pop
-- of the regex.
315 01606931 Iustin Pop
instance Show FilterRegex where
316 01606931 Iustin Pop
  show (FilterRegex re _) = "mkRegex " ++ show re
317 01606931 Iustin Pop
318 01606931 Iustin Pop
-- | 'Read' instance: we manually read \"mkRegex\" followed by a
319 01606931 Iustin Pop
-- string, and build the 'FilterRegex' using that.
320 01606931 Iustin Pop
instance Read FilterRegex where
321 01606931 Iustin Pop
  readsPrec _ str = do
322 01606931 Iustin Pop
    ("mkRegex", s') <- lex str
323 01606931 Iustin Pop
    (re, s'') <- reads s'
324 01606931 Iustin Pop
    filterre <- mkRegex re
325 01606931 Iustin Pop
    return (filterre, s'')
326 01606931 Iustin Pop
327 01606931 Iustin Pop
-- | 'Eq' instance: we only compare the string versions of the regexes.
328 01606931 Iustin Pop
instance Eq FilterRegex where
329 01606931 Iustin Pop
  (FilterRegex re1 _) == (FilterRegex re2 _) = re1 == re2
330 01606931 Iustin Pop
331 01606931 Iustin Pop
-- | 'JSON' instance: like for show and read instances, we work only
332 01606931 Iustin Pop
-- with the string component.
333 01606931 Iustin Pop
instance JSON FilterRegex where
334 01606931 Iustin Pop
  showJSON (FilterRegex re _) = showJSON re
335 01606931 Iustin Pop
  readJSON s = do
336 01606931 Iustin Pop
    re <- readJSON s
337 01606931 Iustin Pop
    mkRegex re
338 ac13f473 Guido Trotter
339 ac13f473 Guido Trotter
-- | Name of a field.
340 ac13f473 Guido Trotter
type FieldName = String
341 ac13f473 Guido Trotter
-- | Title of a field, when represented in tabular format.
342 ac13f473 Guido Trotter
type FieldTitle = String
343 ac13f473 Guido Trotter
-- | Human redable description of a field.
344 ac13f473 Guido Trotter
type FieldDoc = String
345 ac13f473 Guido Trotter
346 4cbe9bda Iustin Pop
-- | Definition of a field.
347 4cbe9bda Iustin Pop
$(buildObject "FieldDefinition" "fdef"
348 4cbe9bda Iustin Pop
  [ simpleField "name"  [t| FieldName  |] -- FIXME: the name has restrictions
349 4cbe9bda Iustin Pop
  , simpleField "title" [t| FieldTitle |]
350 4cbe9bda Iustin Pop
  , simpleField "kind"  [t| FieldType  |]
351 4cbe9bda Iustin Pop
  , simpleField "doc"   [t| FieldDoc   |]
352 4cbe9bda Iustin Pop
  ])
353 4cbe9bda Iustin Pop
354 ac13f473 Guido Trotter
--- | Single field entry result.
355 b9bdc10e Iustin Pop
data ResultEntry = ResultEntry
356 b9bdc10e Iustin Pop
  { rentryStatus :: ResultStatus      -- ^ The result status
357 b9bdc10e Iustin Pop
  , rentryValue  :: Maybe ResultValue -- ^ The (optional) result value
358 b9bdc10e Iustin Pop
  } deriving (Show, Read, Eq)
359 4cbe9bda Iustin Pop
360 4cbe9bda Iustin Pop
instance JSON ResultEntry where
361 4cbe9bda Iustin Pop
  showJSON (ResultEntry rs rv) =
362 4cbe9bda Iustin Pop
    showJSON (showJSON rs, maybe JSNull showJSON rv)
363 4cbe9bda Iustin Pop
  readJSON v = do
364 4cbe9bda Iustin Pop
    (rs, rv) <- readJSON v
365 4cbe9bda Iustin Pop
    rv' <- case rv of
366 4cbe9bda Iustin Pop
             JSNull -> return Nothing
367 3ce788db Iustin Pop
             x -> Just <$> readJSON x
368 4cbe9bda Iustin Pop
    return $ ResultEntry rs rv'
369 4cbe9bda Iustin Pop
370 4cbe9bda Iustin Pop
-- | The type of one result row.
371 4cbe9bda Iustin Pop
type ResultRow = [ ResultEntry ]
372 ac13f473 Guido Trotter
373 ac13f473 Guido Trotter
-- | Value of a field, in json encoding.
374 ac13f473 Guido Trotter
-- (its type will be depending on ResultStatus and FieldType)
375 ac13f473 Guido Trotter
type ResultValue = JSValue
376 4cbe9bda Iustin Pop
377 4cbe9bda Iustin Pop
-- * Main Qlang queries and responses.
378 4cbe9bda Iustin Pop
379 4cbe9bda Iustin Pop
-- | Query2 query.
380 05ac718f Iustin Pop
data Query = Query ItemType Fields (Filter FilterField)
381 4cbe9bda Iustin Pop
382 4cbe9bda Iustin Pop
-- | Query2 result.
383 4cbe9bda Iustin Pop
$(buildObject "QueryResult" "qres"
384 4cbe9bda Iustin Pop
  [ simpleField "fields" [t| [ FieldDefinition ] |]
385 4cbe9bda Iustin Pop
  , simpleField "data"   [t| [ ResultRow       ] |]
386 4cbe9bda Iustin Pop
  ])
387 4cbe9bda Iustin Pop
388 4cbe9bda Iustin Pop
-- | Query2 Fields query.
389 4cbe9bda Iustin Pop
-- (to get supported fields names, descriptions, and types)
390 4cbe9bda Iustin Pop
data QueryFields = QueryFields ItemType Fields
391 4cbe9bda Iustin Pop
392 4cbe9bda Iustin Pop
-- | Query2 Fields result.
393 518023a9 Iustin Pop
$(buildObject "QueryFieldsResult" "qfieldres"
394 518023a9 Iustin Pop
  [ simpleField "fields" [t| [FieldDefinition ] |]
395 518023a9 Iustin Pop
  ])