root / src / Ganeti / THH.hs @ ce1b0c05
History | View | Annotate | Download (46 kB)
1 |
{-# LANGUAGE ExistentialQuantification, TemplateHaskell #-} |
---|---|
2 |
|
3 |
{-| TemplateHaskell helper for Ganeti Haskell code. |
4 |
|
5 |
As TemplateHaskell require that splices be defined in a separate |
6 |
module, we combine all the TemplateHaskell functionality that HTools |
7 |
needs in this module (except the one for unittests). |
8 |
|
9 |
-} |
10 |
|
11 |
{- |
12 |
|
13 |
Copyright (C) 2011, 2012 Google Inc. |
14 |
|
15 |
This program is free software; you can redistribute it and/or modify |
16 |
it under the terms of the GNU General Public License as published by |
17 |
the Free Software Foundation; either version 2 of the License, or |
18 |
(at your option) any later version. |
19 |
|
20 |
This program is distributed in the hope that it will be useful, but |
21 |
WITHOUT ANY WARRANTY; without even the implied warranty of |
22 |
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
23 |
General Public License for more details. |
24 |
|
25 |
You should have received a copy of the GNU General Public License |
26 |
along with this program; if not, write to the Free Software |
27 |
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
28 |
02110-1301, USA. |
29 |
|
30 |
-} |
31 |
|
32 |
module Ganeti.THH ( declareSADT |
33 |
, declareIADT |
34 |
, makeJSONInstance |
35 |
, deCamelCase |
36 |
, genOpID |
37 |
, genAllConstr |
38 |
, genAllOpIDs |
39 |
, PyValue(..) |
40 |
, PyValueEx(..) |
41 |
, OpCodeDescriptor |
42 |
, genOpCode |
43 |
, genStrOfOp |
44 |
, genStrOfKey |
45 |
, genLuxiOp |
46 |
, Field (..) |
47 |
, simpleField |
48 |
, withDoc |
49 |
, defaultField |
50 |
, optionalField |
51 |
, optionalNullSerField |
52 |
, renameField |
53 |
, customField |
54 |
, timeStampFields |
55 |
, uuidFields |
56 |
, serialFields |
57 |
, tagsFields |
58 |
, TagSet |
59 |
, buildObject |
60 |
, buildObjectSerialisation |
61 |
, buildParam |
62 |
, DictObject(..) |
63 |
, genException |
64 |
, excErrMsg |
65 |
) where |
66 |
|
67 |
import Control.Monad (liftM) |
68 |
import Data.Char |
69 |
import Data.List |
70 |
import qualified Data.Set as Set |
71 |
import Language.Haskell.TH |
72 |
|
73 |
import qualified Text.JSON as JSON |
74 |
import Text.JSON.Pretty (pp_value) |
75 |
|
76 |
import Ganeti.JSON |
77 |
|
78 |
import Data.Maybe |
79 |
import Data.Functor ((<$>)) |
80 |
|
81 |
-- * Exported types |
82 |
|
83 |
-- | Class of objects that can be converted to 'JSObject' |
84 |
-- lists-format. |
85 |
class DictObject a where |
86 |
toDict :: a -> [(String, JSON.JSValue)] |
87 |
|
88 |
-- | Optional field information. |
89 |
data OptionalType |
90 |
= NotOptional -- ^ Field is not optional |
91 |
| OptionalOmitNull -- ^ Field is optional, null is not serialised |
92 |
| OptionalSerializeNull -- ^ Field is optional, null is serialised |
93 |
deriving (Show, Eq) |
94 |
|
95 |
-- | Serialised field data type. |
96 |
data Field = Field { fieldName :: String |
97 |
, fieldType :: Q Type |
98 |
, fieldRead :: Maybe (Q Exp) |
99 |
, fieldShow :: Maybe (Q Exp) |
100 |
, fieldExtraKeys :: [String] |
101 |
, fieldDefault :: Maybe (Q Exp) |
102 |
, fieldConstr :: Maybe String |
103 |
, fieldIsOptional :: OptionalType |
104 |
, fieldDoc :: String |
105 |
} |
106 |
|
107 |
-- | Generates a simple field. |
108 |
simpleField :: String -> Q Type -> Field |
109 |
simpleField fname ftype = |
110 |
Field { fieldName = fname |
111 |
, fieldType = ftype |
112 |
, fieldRead = Nothing |
113 |
, fieldShow = Nothing |
114 |
, fieldExtraKeys = [] |
115 |
, fieldDefault = Nothing |
116 |
, fieldConstr = Nothing |
117 |
, fieldIsOptional = NotOptional |
118 |
, fieldDoc = "" |
119 |
} |
120 |
|
121 |
withDoc :: String -> Field -> Field |
122 |
withDoc doc field = |
123 |
field { fieldDoc = doc } |
124 |
|
125 |
-- | Sets the renamed constructor field. |
126 |
renameField :: String -> Field -> Field |
127 |
renameField constrName field = field { fieldConstr = Just constrName } |
128 |
|
129 |
-- | Sets the default value on a field (makes it optional with a |
130 |
-- default value). |
131 |
defaultField :: Q Exp -> Field -> Field |
132 |
defaultField defval field = field { fieldDefault = Just defval } |
133 |
|
134 |
-- | Marks a field optional (turning its base type into a Maybe). |
135 |
optionalField :: Field -> Field |
136 |
optionalField field = field { fieldIsOptional = OptionalOmitNull } |
137 |
|
138 |
-- | Marks a field optional (turning its base type into a Maybe), but |
139 |
-- with 'Nothing' serialised explicitly as /null/. |
140 |
optionalNullSerField :: Field -> Field |
141 |
optionalNullSerField field = field { fieldIsOptional = OptionalSerializeNull } |
142 |
|
143 |
-- | Sets custom functions on a field. |
144 |
customField :: Name -- ^ The name of the read function |
145 |
-> Name -- ^ The name of the show function |
146 |
-> [String] -- ^ The name of extra field keys |
147 |
-> Field -- ^ The original field |
148 |
-> Field -- ^ Updated field |
149 |
customField readfn showfn extra field = |
150 |
field { fieldRead = Just (varE readfn), fieldShow = Just (varE showfn) |
151 |
, fieldExtraKeys = extra } |
152 |
|
153 |
-- | Computes the record name for a given field, based on either the |
154 |
-- string value in the JSON serialisation or the custom named if any |
155 |
-- exists. |
156 |
fieldRecordName :: Field -> String |
157 |
fieldRecordName (Field { fieldName = name, fieldConstr = alias }) = |
158 |
fromMaybe (camelCase name) alias |
159 |
|
160 |
-- | Computes the preferred variable name to use for the value of this |
161 |
-- field. If the field has a specific constructor name, then we use a |
162 |
-- first-letter-lowercased version of that; otherwise, we simply use |
163 |
-- the field name. See also 'fieldRecordName'. |
164 |
fieldVariable :: Field -> String |
165 |
fieldVariable f = |
166 |
case (fieldConstr f) of |
167 |
Just name -> ensureLower name |
168 |
_ -> map (\c -> if c == '-' then '_' else c) $ fieldName f |
169 |
|
170 |
-- | Compute the actual field type (taking into account possible |
171 |
-- optional status). |
172 |
actualFieldType :: Field -> Q Type |
173 |
actualFieldType f | fieldIsOptional f /= NotOptional = [t| Maybe $t |] |
174 |
| otherwise = t |
175 |
where t = fieldType f |
176 |
|
177 |
-- | Checks that a given field is not optional (for object types or |
178 |
-- fields which should not allow this case). |
179 |
checkNonOptDef :: (Monad m) => Field -> m () |
180 |
checkNonOptDef (Field { fieldIsOptional = OptionalOmitNull |
181 |
, fieldName = name }) = |
182 |
fail $ "Optional field " ++ name ++ " used in parameter declaration" |
183 |
checkNonOptDef (Field { fieldIsOptional = OptionalSerializeNull |
184 |
, fieldName = name }) = |
185 |
fail $ "Optional field " ++ name ++ " used in parameter declaration" |
186 |
checkNonOptDef (Field { fieldDefault = (Just _), fieldName = name }) = |
187 |
fail $ "Default field " ++ name ++ " used in parameter declaration" |
188 |
checkNonOptDef _ = return () |
189 |
|
190 |
-- | Produces the expression that will de-serialise a given |
191 |
-- field. Since some custom parsing functions might need to use the |
192 |
-- entire object, we do take and pass the object to any custom read |
193 |
-- functions. |
194 |
loadFn :: Field -- ^ The field definition |
195 |
-> Q Exp -- ^ The value of the field as existing in the JSON message |
196 |
-> Q Exp -- ^ The entire object in JSON object format |
197 |
-> Q Exp -- ^ Resulting expression |
198 |
loadFn (Field { fieldRead = Just readfn }) expr o = [| $expr >>= $readfn $o |] |
199 |
loadFn _ expr _ = expr |
200 |
|
201 |
-- * Common field declarations |
202 |
|
203 |
-- | Timestamp fields description. |
204 |
timeStampFields :: [Field] |
205 |
timeStampFields = |
206 |
[ defaultField [| 0::Double |] $ simpleField "ctime" [t| Double |] |
207 |
, defaultField [| 0::Double |] $ simpleField "mtime" [t| Double |] |
208 |
] |
209 |
|
210 |
-- | Serial number fields description. |
211 |
serialFields :: [Field] |
212 |
serialFields = |
213 |
[ renameField "Serial" $ simpleField "serial_no" [t| Int |] ] |
214 |
|
215 |
-- | UUID fields description. |
216 |
uuidFields :: [Field] |
217 |
uuidFields = [ simpleField "uuid" [t| String |] ] |
218 |
|
219 |
-- | Tag set type alias. |
220 |
type TagSet = Set.Set String |
221 |
|
222 |
-- | Tag field description. |
223 |
tagsFields :: [Field] |
224 |
tagsFields = [ defaultField [| Set.empty |] $ |
225 |
simpleField "tags" [t| TagSet |] ] |
226 |
|
227 |
-- * Internal types |
228 |
|
229 |
-- | A simple field, in constrast to the customisable 'Field' type. |
230 |
type SimpleField = (String, Q Type) |
231 |
|
232 |
-- | A definition for a single constructor for a simple object. |
233 |
type SimpleConstructor = (String, [SimpleField]) |
234 |
|
235 |
-- | A definition for ADTs with simple fields. |
236 |
type SimpleObject = [SimpleConstructor] |
237 |
|
238 |
-- | A type alias for an opcode constructor of a regular object. |
239 |
type OpCodeConstructor = (String, Q Type, String, [Field], String) |
240 |
|
241 |
-- | A type alias for a Luxi constructor of a regular object. |
242 |
type LuxiConstructor = (String, [Field]) |
243 |
|
244 |
-- * Helper functions |
245 |
|
246 |
-- | Ensure first letter is lowercase. |
247 |
-- |
248 |
-- Used to convert type name to function prefix, e.g. in @data Aa -> |
249 |
-- aaToRaw@. |
250 |
ensureLower :: String -> String |
251 |
ensureLower [] = [] |
252 |
ensureLower (x:xs) = toLower x:xs |
253 |
|
254 |
-- | Ensure first letter is uppercase. |
255 |
-- |
256 |
-- Used to convert constructor name to component |
257 |
ensureUpper :: String -> String |
258 |
ensureUpper [] = [] |
259 |
ensureUpper (x:xs) = toUpper x:xs |
260 |
|
261 |
-- | Helper for quoted expressions. |
262 |
varNameE :: String -> Q Exp |
263 |
varNameE = varE . mkName |
264 |
|
265 |
-- | showJSON as an expression, for reuse. |
266 |
showJSONE :: Q Exp |
267 |
showJSONE = varE 'JSON.showJSON |
268 |
|
269 |
-- | makeObj as an expression, for reuse. |
270 |
makeObjE :: Q Exp |
271 |
makeObjE = varE 'JSON.makeObj |
272 |
|
273 |
-- | fromObj (Ganeti specific) as an expression, for reuse. |
274 |
fromObjE :: Q Exp |
275 |
fromObjE = varE 'fromObj |
276 |
|
277 |
-- | ToRaw function name. |
278 |
toRawName :: String -> Name |
279 |
toRawName = mkName . (++ "ToRaw") . ensureLower |
280 |
|
281 |
-- | FromRaw function name. |
282 |
fromRawName :: String -> Name |
283 |
fromRawName = mkName . (++ "FromRaw") . ensureLower |
284 |
|
285 |
-- | Converts a name to it's varE\/litE representations. |
286 |
reprE :: Either String Name -> Q Exp |
287 |
reprE = either stringE varE |
288 |
|
289 |
-- | Smarter function application. |
290 |
-- |
291 |
-- This does simply f x, except that if is 'id', it will skip it, in |
292 |
-- order to generate more readable code when using -ddump-splices. |
293 |
appFn :: Exp -> Exp -> Exp |
294 |
appFn f x | f == VarE 'id = x |
295 |
| otherwise = AppE f x |
296 |
|
297 |
-- | Builds a field for a normal constructor. |
298 |
buildConsField :: Q Type -> StrictTypeQ |
299 |
buildConsField ftype = do |
300 |
ftype' <- ftype |
301 |
return (NotStrict, ftype') |
302 |
|
303 |
-- | Builds a constructor based on a simple definition (not field-based). |
304 |
buildSimpleCons :: Name -> SimpleObject -> Q Dec |
305 |
buildSimpleCons tname cons = do |
306 |
decl_d <- mapM (\(cname, fields) -> do |
307 |
fields' <- mapM (buildConsField . snd) fields |
308 |
return $ NormalC (mkName cname) fields') cons |
309 |
return $ DataD [] tname [] decl_d [''Show, ''Eq] |
310 |
|
311 |
-- | Generate the save function for a given type. |
312 |
genSaveSimpleObj :: Name -- ^ Object type |
313 |
-> String -- ^ Function name |
314 |
-> SimpleObject -- ^ Object definition |
315 |
-> (SimpleConstructor -> Q Clause) -- ^ Constructor save fn |
316 |
-> Q (Dec, Dec) |
317 |
genSaveSimpleObj tname sname opdefs fn = do |
318 |
let sigt = AppT (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue) |
319 |
fname = mkName sname |
320 |
cclauses <- mapM fn opdefs |
321 |
return $ (SigD fname sigt, FunD fname cclauses) |
322 |
|
323 |
-- * Template code for simple raw type-equivalent ADTs |
324 |
|
325 |
-- | Generates a data type declaration. |
326 |
-- |
327 |
-- The type will have a fixed list of instances. |
328 |
strADTDecl :: Name -> [String] -> Dec |
329 |
strADTDecl name constructors = |
330 |
DataD [] name [] |
331 |
(map (flip NormalC [] . mkName) constructors) |
332 |
[''Show, ''Eq, ''Enum, ''Bounded, ''Ord] |
333 |
|
334 |
-- | Generates a toRaw function. |
335 |
-- |
336 |
-- This generates a simple function of the form: |
337 |
-- |
338 |
-- @ |
339 |
-- nameToRaw :: Name -> /traw/ |
340 |
-- nameToRaw Cons1 = var1 |
341 |
-- nameToRaw Cons2 = \"value2\" |
342 |
-- @ |
343 |
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec] |
344 |
genToRaw traw fname tname constructors = do |
345 |
let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw) |
346 |
-- the body clauses, matching on the constructor and returning the |
347 |
-- raw value |
348 |
clauses <- mapM (\(c, v) -> clause [recP (mkName c) []] |
349 |
(normalB (reprE v)) []) constructors |
350 |
return [SigD fname sigt, FunD fname clauses] |
351 |
|
352 |
-- | Generates a fromRaw function. |
353 |
-- |
354 |
-- The function generated is monadic and can fail parsing the |
355 |
-- raw value. It is of the form: |
356 |
-- |
357 |
-- @ |
358 |
-- nameFromRaw :: (Monad m) => /traw/ -> m Name |
359 |
-- nameFromRaw s | s == var1 = Cons1 |
360 |
-- | s == \"value2\" = Cons2 |
361 |
-- | otherwise = fail /.../ |
362 |
-- @ |
363 |
genFromRaw :: Name -> Name -> Name -> [(String, Name)] -> Q [Dec] |
364 |
genFromRaw traw fname tname constructors = do |
365 |
-- signature of form (Monad m) => String -> m $name |
366 |
sigt <- [t| (Monad m) => $(conT traw) -> m $(conT tname) |] |
367 |
-- clauses for a guarded pattern |
368 |
let varp = mkName "s" |
369 |
varpe = varE varp |
370 |
clauses <- mapM (\(c, v) -> do |
371 |
-- the clause match condition |
372 |
g <- normalG [| $varpe == $(varE v) |] |
373 |
-- the clause result |
374 |
r <- [| return $(conE (mkName c)) |] |
375 |
return (g, r)) constructors |
376 |
-- the otherwise clause (fallback) |
377 |
oth_clause <- do |
378 |
g <- normalG [| otherwise |] |
379 |
r <- [|fail ("Invalid string value for type " ++ |
380 |
$(litE (stringL (nameBase tname))) ++ ": " ++ show $varpe) |] |
381 |
return (g, r) |
382 |
let fun = FunD fname [Clause [VarP varp] |
383 |
(GuardedB (clauses++[oth_clause])) []] |
384 |
return [SigD fname sigt, fun] |
385 |
|
386 |
-- | Generates a data type from a given raw format. |
387 |
-- |
388 |
-- The format is expected to multiline. The first line contains the |
389 |
-- type name, and the rest of the lines must contain two words: the |
390 |
-- constructor name and then the string representation of the |
391 |
-- respective constructor. |
392 |
-- |
393 |
-- The function will generate the data type declaration, and then two |
394 |
-- functions: |
395 |
-- |
396 |
-- * /name/ToRaw, which converts the type to a raw type |
397 |
-- |
398 |
-- * /name/FromRaw, which (monadically) converts from a raw type to the type |
399 |
-- |
400 |
-- Note that this is basically just a custom show\/read instance, |
401 |
-- nothing else. |
402 |
declareADT :: Name -> String -> [(String, Name)] -> Q [Dec] |
403 |
declareADT traw sname cons = do |
404 |
let name = mkName sname |
405 |
ddecl = strADTDecl name (map fst cons) |
406 |
-- process cons in the format expected by genToRaw |
407 |
cons' = map (\(a, b) -> (a, Right b)) cons |
408 |
toraw <- genToRaw traw (toRawName sname) name cons' |
409 |
fromraw <- genFromRaw traw (fromRawName sname) name cons |
410 |
return $ ddecl:toraw ++ fromraw |
411 |
|
412 |
declareIADT :: String -> [(String, Name)] -> Q [Dec] |
413 |
declareIADT = declareADT ''Int |
414 |
|
415 |
declareSADT :: String -> [(String, Name)] -> Q [Dec] |
416 |
declareSADT = declareADT ''String |
417 |
|
418 |
-- | Creates the showJSON member of a JSON instance declaration. |
419 |
-- |
420 |
-- This will create what is the equivalent of: |
421 |
-- |
422 |
-- @ |
423 |
-- showJSON = showJSON . /name/ToRaw |
424 |
-- @ |
425 |
-- |
426 |
-- in an instance JSON /name/ declaration |
427 |
genShowJSON :: String -> Q Dec |
428 |
genShowJSON name = do |
429 |
body <- [| JSON.showJSON . $(varE (toRawName name)) |] |
430 |
return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []] |
431 |
|
432 |
-- | Creates the readJSON member of a JSON instance declaration. |
433 |
-- |
434 |
-- This will create what is the equivalent of: |
435 |
-- |
436 |
-- @ |
437 |
-- readJSON s = case readJSON s of |
438 |
-- Ok s' -> /name/FromRaw s' |
439 |
-- Error e -> Error /description/ |
440 |
-- @ |
441 |
-- |
442 |
-- in an instance JSON /name/ declaration |
443 |
genReadJSON :: String -> Q Dec |
444 |
genReadJSON name = do |
445 |
let s = mkName "s" |
446 |
body <- [| case JSON.readJSON $(varE s) of |
447 |
JSON.Ok s' -> $(varE (fromRawName name)) s' |
448 |
JSON.Error e -> |
449 |
JSON.Error $ "Can't parse raw value for type " ++ |
450 |
$(stringE name) ++ ": " ++ e ++ " from " ++ |
451 |
show $(varE s) |
452 |
|] |
453 |
return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []] |
454 |
|
455 |
-- | Generates a JSON instance for a given type. |
456 |
-- |
457 |
-- This assumes that the /name/ToRaw and /name/FromRaw functions |
458 |
-- have been defined as by the 'declareSADT' function. |
459 |
makeJSONInstance :: Name -> Q [Dec] |
460 |
makeJSONInstance name = do |
461 |
let base = nameBase name |
462 |
showJ <- genShowJSON base |
463 |
readJ <- genReadJSON base |
464 |
return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]] |
465 |
|
466 |
-- * Template code for opcodes |
467 |
|
468 |
-- | Transforms a CamelCase string into an_underscore_based_one. |
469 |
deCamelCase :: String -> String |
470 |
deCamelCase = |
471 |
intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b) |
472 |
|
473 |
-- | Transform an underscore_name into a CamelCase one. |
474 |
camelCase :: String -> String |
475 |
camelCase = concatMap (ensureUpper . drop 1) . |
476 |
groupBy (\_ b -> b /= '_' && b /= '-') . ('_':) |
477 |
|
478 |
-- | Computes the name of a given constructor. |
479 |
constructorName :: Con -> Q Name |
480 |
constructorName (NormalC name _) = return name |
481 |
constructorName (RecC name _) = return name |
482 |
constructorName x = fail $ "Unhandled constructor " ++ show x |
483 |
|
484 |
-- | Extract all constructor names from a given type. |
485 |
reifyConsNames :: Name -> Q [String] |
486 |
reifyConsNames name = do |
487 |
reify_result <- reify name |
488 |
case reify_result of |
489 |
TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons |
490 |
o -> fail $ "Unhandled name passed to reifyConsNames, expected\ |
491 |
\ type constructor but got '" ++ show o ++ "'" |
492 |
|
493 |
-- | Builds the generic constructor-to-string function. |
494 |
-- |
495 |
-- This generates a simple function of the following form: |
496 |
-- |
497 |
-- @ |
498 |
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne") |
499 |
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo") |
500 |
-- @ |
501 |
-- |
502 |
-- This builds a custom list of name\/string pairs and then uses |
503 |
-- 'genToRaw' to actually generate the function. |
504 |
genConstrToStr :: (String -> String) -> Name -> String -> Q [Dec] |
505 |
genConstrToStr trans_fun name fname = do |
506 |
cnames <- reifyConsNames name |
507 |
let svalues = map (Left . trans_fun) cnames |
508 |
genToRaw ''String (mkName fname) name $ zip cnames svalues |
509 |
|
510 |
-- | Constructor-to-string for OpCode. |
511 |
genOpID :: Name -> String -> Q [Dec] |
512 |
genOpID = genConstrToStr deCamelCase |
513 |
|
514 |
-- | Builds a list with all defined constructor names for a type. |
515 |
-- |
516 |
-- @ |
517 |
-- vstr :: String |
518 |
-- vstr = [...] |
519 |
-- @ |
520 |
-- |
521 |
-- Where the actual values of the string are the constructor names |
522 |
-- mapped via @trans_fun@. |
523 |
genAllConstr :: (String -> String) -> Name -> String -> Q [Dec] |
524 |
genAllConstr trans_fun name vstr = do |
525 |
cnames <- reifyConsNames name |
526 |
let svalues = sort $ map trans_fun cnames |
527 |
vname = mkName vstr |
528 |
sig = SigD vname (AppT ListT (ConT ''String)) |
529 |
body = NormalB (ListE (map (LitE . StringL) svalues)) |
530 |
return $ [sig, ValD (VarP vname) body []] |
531 |
|
532 |
-- | Generates a list of all defined opcode IDs. |
533 |
genAllOpIDs :: Name -> String -> Q [Dec] |
534 |
genAllOpIDs = genAllConstr deCamelCase |
535 |
|
536 |
-- | OpCode parameter (field) type. |
537 |
type OpParam = (String, Q Type, Q Exp) |
538 |
|
539 |
-- * Python code generation |
540 |
|
541 |
-- | Converts Haskell values into Python values |
542 |
-- |
543 |
-- This is necessary for the default values of opcode parameters and |
544 |
-- return values. For example, if a default value or return type is a |
545 |
-- Data.Map, then it must be shown as a Python dictioanry. |
546 |
class Show a => PyValue a where |
547 |
showValue :: a -> String |
548 |
showValue = show |
549 |
|
550 |
-- | Encapsulates Python default values |
551 |
data PyValueEx = forall a. PyValue a => PyValueEx a |
552 |
|
553 |
-- | Transfers opcode data between the opcode description (through |
554 |
-- @genOpCode@) and the Python code generation functions. |
555 |
type OpCodeDescriptor = |
556 |
(String, String, String, [String], |
557 |
[String], [Maybe PyValueEx], [String], String) |
558 |
|
559 |
-- | Strips out the module name |
560 |
-- |
561 |
-- @ |
562 |
-- pyBaseName "Data.Map" = "Map" |
563 |
-- @ |
564 |
pyBaseName :: String -> String |
565 |
pyBaseName str = |
566 |
case span (/= '.') str of |
567 |
(x, []) -> x |
568 |
(_, _:x) -> pyBaseName x |
569 |
|
570 |
-- | Converts a Haskell type name into a Python type name. |
571 |
-- |
572 |
-- @ |
573 |
-- pyTypename "Bool" = "ht.TBool" |
574 |
-- @ |
575 |
pyTypeName :: Show a => a -> String |
576 |
pyTypeName name = |
577 |
"ht.T" ++ (case pyBaseName (show name) of |
578 |
"()" -> "None" |
579 |
"Map" -> "DictOf" |
580 |
"Set" -> "SetOf" |
581 |
"Either" -> "Or" |
582 |
"GenericContainer" -> "DictOf" |
583 |
"JSValue" -> "Any" |
584 |
"JSObject" -> "Object" |
585 |
str -> str) |
586 |
|
587 |
-- | Converts a Haskell type into a Python type. |
588 |
-- |
589 |
-- @ |
590 |
-- pyType [Int] = "ht.TListOf(ht.TInt)" |
591 |
-- @ |
592 |
pyType :: Type -> Q String |
593 |
pyType (AppT typ1 typ2) = |
594 |
do t <- pyCall typ1 typ2 |
595 |
return $ t ++ ")" |
596 |
|
597 |
pyType (ConT name) = return (pyTypeName name) |
598 |
pyType ListT = return "ht.TListOf" |
599 |
pyType (TupleT 0) = return "ht.TNone" |
600 |
pyType (TupleT _) = return "ht.TTupleOf" |
601 |
pyType typ = error $ "unhandled case for type " ++ show typ |
602 |
|
603 |
-- | Converts a Haskell type application into a Python type. |
604 |
-- |
605 |
-- @ |
606 |
-- Maybe Int = "ht.TMaybe(ht.TInt)" |
607 |
-- @ |
608 |
pyCall :: Type -> Type -> Q String |
609 |
pyCall (AppT typ1 typ2) arg = |
610 |
do t <- pyCall typ1 typ2 |
611 |
targ <- pyType arg |
612 |
return $ t ++ ", " ++ targ |
613 |
|
614 |
pyCall typ1 typ2 = |
615 |
do t1 <- pyType typ1 |
616 |
t2 <- pyType typ2 |
617 |
return $ t1 ++ "(" ++ t2 |
618 |
|
619 |
-- | @pyType opt typ@ converts Haskell type @typ@ into a Python type, |
620 |
-- where @opt@ determines if the converted type is optional (i.e., |
621 |
-- Maybe). |
622 |
-- |
623 |
-- @ |
624 |
-- pyType False [Int] = "ht.TListOf(ht.TInt)" (mandatory) |
625 |
-- pyType True [Int] = "ht.TMaybe(ht.TListOf(ht.TInt))" (optional) |
626 |
-- @ |
627 |
pyOptionalType :: Bool -> Type -> Q String |
628 |
pyOptionalType opt typ |
629 |
| opt = do t <- pyType typ |
630 |
return $ "ht.TMaybe(" ++ t ++ ")" |
631 |
| otherwise = pyType typ |
632 |
|
633 |
-- | Optionally encapsulates default values in @PyValueEx@. |
634 |
-- |
635 |
-- @maybeApp exp typ@ returns a quoted expression that encapsulates |
636 |
-- the default value @exp@ of an opcode parameter cast to @typ@ in a |
637 |
-- @PyValueEx@, if @exp@ is @Just@. Otherwise, it returns a quoted |
638 |
-- expression with @Nothing@. |
639 |
maybeApp :: Maybe (Q Exp) -> Q Type -> Q Exp |
640 |
maybeApp Nothing _ = |
641 |
[| Nothing |] |
642 |
|
643 |
maybeApp (Just expr) typ = |
644 |
[| Just ($(conE (mkName "PyValueEx")) ($expr :: $typ)) |] |
645 |
|
646 |
|
647 |
-- | Generates a Python type according to whether the field is |
648 |
-- optional |
649 |
genPyType :: OptionalType -> Q Type -> Q ExpQ |
650 |
genPyType opt typ = |
651 |
do t <- typ |
652 |
stringE <$> pyOptionalType (opt /= NotOptional) t |
653 |
|
654 |
-- | Generates Python types from opcode parameters. |
655 |
genPyTypes :: [Field] -> Q ExpQ |
656 |
genPyTypes fs = |
657 |
listE <$> mapM (\f -> genPyType (fieldIsOptional f) (fieldType f)) fs |
658 |
|
659 |
-- | Generates Python default values from opcode parameters. |
660 |
genPyDefaults :: [Field] -> ExpQ |
661 |
genPyDefaults fs = |
662 |
listE $ map (\f -> maybeApp (fieldDefault f) (fieldType f)) fs |
663 |
|
664 |
-- | Generates a Haskell function call to "showPyClass" with the |
665 |
-- necessary information on how to build the Python class string. |
666 |
pyClass :: OpCodeConstructor -> ExpQ |
667 |
pyClass (consName, consType, consDoc, consFields, consDscField) = |
668 |
do let pyClassVar = varNameE "showPyClass" |
669 |
consName' = stringE consName |
670 |
consType' <- genPyType NotOptional consType |
671 |
let consDoc' = stringE consDoc |
672 |
consFieldNames = listE $ map (stringE . fieldName) consFields |
673 |
consFieldDocs = listE $ map (stringE . fieldDoc) consFields |
674 |
consFieldTypes <- genPyTypes consFields |
675 |
let consFieldDefaults = genPyDefaults consFields |
676 |
[| ($consName', |
677 |
$consType', |
678 |
$consDoc', |
679 |
$consFieldNames, |
680 |
$consFieldTypes, |
681 |
$consFieldDefaults, |
682 |
$consFieldDocs, |
683 |
consDscField) |] |
684 |
|
685 |
-- | Generates a function called "pyClasses" that holds the list of |
686 |
-- all the opcode descriptors necessary for generating the Python |
687 |
-- opcodes. |
688 |
pyClasses :: [OpCodeConstructor] -> Q [Dec] |
689 |
pyClasses cons = |
690 |
do let name = mkName "pyClasses" |
691 |
sig = SigD name (AppT ListT (ConT ''OpCodeDescriptor)) |
692 |
fn <- FunD name <$> (:[]) <$> declClause cons |
693 |
return [sig, fn] |
694 |
where declClause c = |
695 |
clause [] (normalB (ListE <$> mapM pyClass c)) [] |
696 |
|
697 |
-- | Converts from an opcode constructor to a Luxi constructor. |
698 |
opcodeConsToLuxiCons :: (a, b, c, d, e) -> (a, d) |
699 |
opcodeConsToLuxiCons (x, _, _, y, _) = (x, y) |
700 |
|
701 |
-- | Generates the OpCode data type. |
702 |
-- |
703 |
-- This takes an opcode logical definition, and builds both the |
704 |
-- datatype and the JSON serialisation out of it. We can't use a |
705 |
-- generic serialisation since we need to be compatible with Ganeti's |
706 |
-- own, so we have a few quirks to work around. |
707 |
genOpCode :: String -- ^ Type name to use |
708 |
-> [OpCodeConstructor] -- ^ Constructor name and parameters |
709 |
-> Q [Dec] |
710 |
genOpCode name cons = do |
711 |
let tname = mkName name |
712 |
decl_d <- mapM (\(cname, _, _, fields, _) -> do |
713 |
-- we only need the type of the field, without Q |
714 |
fields' <- mapM (fieldTypeInfo "op") fields |
715 |
return $ RecC (mkName cname) fields') |
716 |
cons |
717 |
let declD = DataD [] tname [] decl_d [''Show, ''Eq] |
718 |
let (allfsig, allffn) = genAllOpFields "allOpFields" cons |
719 |
save_decs <- genSaveOpCode tname "saveOpCode" "toDictOpCode" |
720 |
(map opcodeConsToLuxiCons cons) saveConstructor True |
721 |
(loadsig, loadfn) <- genLoadOpCode cons |
722 |
pyDecls <- pyClasses cons |
723 |
return $ [declD, allfsig, allffn, loadsig, loadfn] ++ save_decs ++ pyDecls |
724 |
|
725 |
-- | Generates the function pattern returning the list of fields for a |
726 |
-- given constructor. |
727 |
genOpConsFields :: OpCodeConstructor -> Clause |
728 |
genOpConsFields (cname, _, _, fields, _) = |
729 |
let op_id = deCamelCase cname |
730 |
fvals = map (LitE . StringL) . sort . nub $ |
731 |
concatMap (\f -> fieldName f:fieldExtraKeys f) fields |
732 |
in Clause [LitP (StringL op_id)] (NormalB $ ListE fvals) [] |
733 |
|
734 |
-- | Generates a list of all fields of an opcode constructor. |
735 |
genAllOpFields :: String -- ^ Function name |
736 |
-> [OpCodeConstructor] -- ^ Object definition |
737 |
-> (Dec, Dec) |
738 |
genAllOpFields sname opdefs = |
739 |
let cclauses = map genOpConsFields opdefs |
740 |
other = Clause [WildP] (NormalB (ListE [])) [] |
741 |
fname = mkName sname |
742 |
sigt = AppT (AppT ArrowT (ConT ''String)) (AppT ListT (ConT ''String)) |
743 |
in (SigD fname sigt, FunD fname (cclauses++[other])) |
744 |
|
745 |
-- | Generates the \"save\" clause for an entire opcode constructor. |
746 |
-- |
747 |
-- This matches the opcode with variables named the same as the |
748 |
-- constructor fields (just so that the spliced in code looks nicer), |
749 |
-- and passes those name plus the parameter definition to 'saveObjectField'. |
750 |
saveConstructor :: LuxiConstructor -- ^ The constructor |
751 |
-> Q Clause -- ^ Resulting clause |
752 |
saveConstructor (sname, fields) = do |
753 |
let cname = mkName sname |
754 |
fnames <- mapM (newName . fieldVariable) fields |
755 |
let pat = conP cname (map varP fnames) |
756 |
let felems = map (uncurry saveObjectField) (zip fnames fields) |
757 |
-- now build the OP_ID serialisation |
758 |
opid = [| [( $(stringE "OP_ID"), |
759 |
JSON.showJSON $(stringE . deCamelCase $ sname) )] |] |
760 |
flist = listE (opid:felems) |
761 |
-- and finally convert all this to a json object |
762 |
flist' = [| concat $flist |] |
763 |
clause [pat] (normalB flist') [] |
764 |
|
765 |
-- | Generates the main save opcode function. |
766 |
-- |
767 |
-- This builds a per-constructor match clause that contains the |
768 |
-- respective constructor-serialisation code. |
769 |
genSaveOpCode :: Name -- ^ Object ype |
770 |
-> String -- ^ To 'JSValue' function name |
771 |
-> String -- ^ To 'JSObject' function name |
772 |
-> [LuxiConstructor] -- ^ Object definition |
773 |
-> (LuxiConstructor -> Q Clause) -- ^ Constructor save fn |
774 |
-> Bool -- ^ Whether to generate |
775 |
-- obj or just a |
776 |
-- list\/tuple of values |
777 |
-> Q [Dec] |
778 |
genSaveOpCode tname jvalstr tdstr opdefs fn gen_object = do |
779 |
tdclauses <- mapM fn opdefs |
780 |
let typecon = ConT tname |
781 |
jvalname = mkName jvalstr |
782 |
jvalsig = AppT (AppT ArrowT typecon) (ConT ''JSON.JSValue) |
783 |
tdname = mkName tdstr |
784 |
tdsig <- [t| $(return typecon) -> [(String, JSON.JSValue)] |] |
785 |
jvalclause <- if gen_object |
786 |
then [| $makeObjE . $(varE tdname) |] |
787 |
else [| JSON.showJSON . map snd . $(varE tdname) |] |
788 |
return [ SigD tdname tdsig |
789 |
, FunD tdname tdclauses |
790 |
, SigD jvalname jvalsig |
791 |
, ValD (VarP jvalname) (NormalB jvalclause) []] |
792 |
|
793 |
-- | Generates load code for a single constructor of the opcode data type. |
794 |
loadConstructor :: OpCodeConstructor -> Q Exp |
795 |
loadConstructor (sname, _, _, fields, _) = do |
796 |
let name = mkName sname |
797 |
fbinds <- mapM loadObjectField fields |
798 |
let (fnames, fstmts) = unzip fbinds |
799 |
let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames |
800 |
fstmts' = fstmts ++ [NoBindS (AppE (VarE 'return) cval)] |
801 |
return $ DoE fstmts' |
802 |
|
803 |
-- | Generates the loadOpCode function. |
804 |
genLoadOpCode :: [OpCodeConstructor] -> Q (Dec, Dec) |
805 |
genLoadOpCode opdefs = do |
806 |
let fname = mkName "loadOpCode" |
807 |
arg1 = mkName "v" |
808 |
objname = mkName "o" |
809 |
opid = mkName "op_id" |
810 |
st1 <- bindS (varP objname) [| liftM JSON.fromJSObject |
811 |
(JSON.readJSON $(varE arg1)) |] |
812 |
st2 <- bindS (varP opid) [| $fromObjE $(varE objname) $(stringE "OP_ID") |] |
813 |
-- the match results (per-constructor blocks) |
814 |
mexps <- mapM loadConstructor opdefs |
815 |
fails <- [| fail $ "Unknown opcode " ++ $(varE opid) |] |
816 |
let mpats = map (\(me, (consName, _, _, _, _)) -> |
817 |
let mp = LitP . StringL . deCamelCase $ consName |
818 |
in Match mp (NormalB me) [] |
819 |
) $ zip mexps opdefs |
820 |
defmatch = Match WildP (NormalB fails) [] |
821 |
cst = NoBindS $ CaseE (VarE opid) $ mpats++[defmatch] |
822 |
body = DoE [st1, st2, cst] |
823 |
sigt <- [t| JSON.JSValue -> JSON.Result $(conT (mkName "OpCode")) |] |
824 |
return $ (SigD fname sigt, FunD fname [Clause [VarP arg1] (NormalB body) []]) |
825 |
|
826 |
-- * Template code for luxi |
827 |
|
828 |
-- | Constructor-to-string for LuxiOp. |
829 |
genStrOfOp :: Name -> String -> Q [Dec] |
830 |
genStrOfOp = genConstrToStr id |
831 |
|
832 |
-- | Constructor-to-string for MsgKeys. |
833 |
genStrOfKey :: Name -> String -> Q [Dec] |
834 |
genStrOfKey = genConstrToStr ensureLower |
835 |
|
836 |
-- | Generates the LuxiOp data type. |
837 |
-- |
838 |
-- This takes a Luxi operation definition and builds both the |
839 |
-- datatype and the function transforming the arguments to JSON. |
840 |
-- We can't use anything less generic, because the way different |
841 |
-- operations are serialized differs on both parameter- and top-level. |
842 |
-- |
843 |
-- There are two things to be defined for each parameter: |
844 |
-- |
845 |
-- * name |
846 |
-- |
847 |
-- * type |
848 |
-- |
849 |
genLuxiOp :: String -> [LuxiConstructor] -> Q [Dec] |
850 |
genLuxiOp name cons = do |
851 |
let tname = mkName name |
852 |
decl_d <- mapM (\(cname, fields) -> do |
853 |
-- we only need the type of the field, without Q |
854 |
fields' <- mapM actualFieldType fields |
855 |
let fields'' = zip (repeat NotStrict) fields' |
856 |
return $ NormalC (mkName cname) fields'') |
857 |
cons |
858 |
let declD = DataD [] (mkName name) [] decl_d [''Show, ''Eq] |
859 |
save_decs <- genSaveOpCode tname "opToArgs" "opToDict" |
860 |
cons saveLuxiConstructor False |
861 |
req_defs <- declareSADT "LuxiReq" . |
862 |
map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $ |
863 |
cons |
864 |
return $ declD:save_decs ++ req_defs |
865 |
|
866 |
-- | Generates the \"save\" clause for entire LuxiOp constructor. |
867 |
saveLuxiConstructor :: LuxiConstructor -> Q Clause |
868 |
saveLuxiConstructor (sname, fields) = do |
869 |
let cname = mkName sname |
870 |
fnames <- mapM (newName . fieldVariable) fields |
871 |
let pat = conP cname (map varP fnames) |
872 |
let felems = map (uncurry saveObjectField) (zip fnames fields) |
873 |
flist = [| concat $(listE felems) |] |
874 |
clause [pat] (normalB flist) [] |
875 |
|
876 |
-- * "Objects" functionality |
877 |
|
878 |
-- | Extract the field's declaration from a Field structure. |
879 |
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type) |
880 |
fieldTypeInfo field_pfx fd = do |
881 |
t <- actualFieldType fd |
882 |
let n = mkName . (field_pfx ++) . fieldRecordName $ fd |
883 |
return (n, NotStrict, t) |
884 |
|
885 |
-- | Build an object declaration. |
886 |
buildObject :: String -> String -> [Field] -> Q [Dec] |
887 |
buildObject sname field_pfx fields = do |
888 |
let name = mkName sname |
889 |
fields_d <- mapM (fieldTypeInfo field_pfx) fields |
890 |
let decl_d = RecC name fields_d |
891 |
let declD = DataD [] name [] [decl_d] [''Show, ''Eq] |
892 |
ser_decls <- buildObjectSerialisation sname fields |
893 |
return $ declD:ser_decls |
894 |
|
895 |
-- | Generates an object definition: data type and its JSON instance. |
896 |
buildObjectSerialisation :: String -> [Field] -> Q [Dec] |
897 |
buildObjectSerialisation sname fields = do |
898 |
let name = mkName sname |
899 |
savedecls <- genSaveObject saveObjectField sname fields |
900 |
(loadsig, loadfn) <- genLoadObject loadObjectField sname fields |
901 |
shjson <- objectShowJSON sname |
902 |
rdjson <- objectReadJSON sname |
903 |
let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) |
904 |
[rdjson, shjson] |
905 |
return $ savedecls ++ [loadsig, loadfn, instdecl] |
906 |
|
907 |
-- | The toDict function name for a given type. |
908 |
toDictName :: String -> Name |
909 |
toDictName sname = mkName ("toDict" ++ sname) |
910 |
|
911 |
-- | Generates the save object functionality. |
912 |
genSaveObject :: (Name -> Field -> Q Exp) |
913 |
-> String -> [Field] -> Q [Dec] |
914 |
genSaveObject save_fn sname fields = do |
915 |
let name = mkName sname |
916 |
fnames <- mapM (newName . fieldVariable) fields |
917 |
let pat = conP name (map varP fnames) |
918 |
let tdname = toDictName sname |
919 |
tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |] |
920 |
|
921 |
let felems = map (uncurry save_fn) (zip fnames fields) |
922 |
flist = listE felems |
923 |
-- and finally convert all this to a json object |
924 |
tdlist = [| concat $flist |] |
925 |
iname = mkName "i" |
926 |
tclause <- clause [pat] (normalB tdlist) [] |
927 |
cclause <- [| $makeObjE . $(varE tdname) |] |
928 |
let fname = mkName ("save" ++ sname) |
929 |
sigt <- [t| $(conT name) -> JSON.JSValue |] |
930 |
return [SigD tdname tdsigt, FunD tdname [tclause], |
931 |
SigD fname sigt, ValD (VarP fname) (NormalB cclause) []] |
932 |
|
933 |
-- | Generates the code for saving an object's field, handling the |
934 |
-- various types of fields that we have. |
935 |
saveObjectField :: Name -> Field -> Q Exp |
936 |
saveObjectField fvar field = |
937 |
case fieldIsOptional field of |
938 |
OptionalOmitNull -> [| case $(varE fvar) of |
939 |
Nothing -> [] |
940 |
Just v -> [( $nameE, JSON.showJSON v )] |
941 |
|] |
942 |
OptionalSerializeNull -> [| case $(varE fvar) of |
943 |
Nothing -> [( $nameE, JSON.JSNull )] |
944 |
Just v -> [( $nameE, JSON.showJSON v )] |
945 |
|] |
946 |
NotOptional -> |
947 |
case fieldShow field of |
948 |
-- Note: the order of actual:extra is important, since for |
949 |
-- some serialisation types (e.g. Luxi), we use tuples |
950 |
-- (positional info) rather than object (name info) |
951 |
Nothing -> [| [( $nameE, JSON.showJSON $fvarE)] |] |
952 |
Just fn -> [| let (actual, extra) = $fn $fvarE |
953 |
in ($nameE, JSON.showJSON actual):extra |
954 |
|] |
955 |
where nameE = stringE (fieldName field) |
956 |
fvarE = varE fvar |
957 |
|
958 |
-- | Generates the showJSON clause for a given object name. |
959 |
objectShowJSON :: String -> Q Dec |
960 |
objectShowJSON name = do |
961 |
body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |] |
962 |
return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []] |
963 |
|
964 |
-- | Generates the load object functionality. |
965 |
genLoadObject :: (Field -> Q (Name, Stmt)) |
966 |
-> String -> [Field] -> Q (Dec, Dec) |
967 |
genLoadObject load_fn sname fields = do |
968 |
let name = mkName sname |
969 |
funname = mkName $ "load" ++ sname |
970 |
arg1 = mkName $ if null fields then "_" else "v" |
971 |
objname = mkName "o" |
972 |
opid = mkName "op_id" |
973 |
st1 <- bindS (varP objname) [| liftM JSON.fromJSObject |
974 |
(JSON.readJSON $(varE arg1)) |] |
975 |
fbinds <- mapM load_fn fields |
976 |
let (fnames, fstmts) = unzip fbinds |
977 |
let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames |
978 |
retstmt = [NoBindS (AppE (VarE 'return) cval)] |
979 |
-- FIXME: should we require an empty dict for an empty type? |
980 |
-- this allows any JSValue right now |
981 |
fstmts' = if null fields |
982 |
then retstmt |
983 |
else st1:fstmts ++ retstmt |
984 |
sigt <- [t| JSON.JSValue -> JSON.Result $(conT name) |] |
985 |
return $ (SigD funname sigt, |
986 |
FunD funname [Clause [VarP arg1] (NormalB (DoE fstmts')) []]) |
987 |
|
988 |
-- | Generates code for loading an object's field. |
989 |
loadObjectField :: Field -> Q (Name, Stmt) |
990 |
loadObjectField field = do |
991 |
let name = fieldVariable field |
992 |
fvar <- newName name |
993 |
-- these are used in all patterns below |
994 |
let objvar = varNameE "o" |
995 |
objfield = stringE (fieldName field) |
996 |
loadexp = |
997 |
if fieldIsOptional field /= NotOptional |
998 |
-- we treat both optional types the same, since |
999 |
-- 'maybeFromObj' can deal with both missing and null values |
1000 |
-- appropriately (the same) |
1001 |
then [| $(varE 'maybeFromObj) $objvar $objfield |] |
1002 |
else case fieldDefault field of |
1003 |
Just defv -> |
1004 |
[| $(varE 'fromObjWithDefault) $objvar |
1005 |
$objfield $defv |] |
1006 |
Nothing -> [| $fromObjE $objvar $objfield |] |
1007 |
bexp <- loadFn field loadexp objvar |
1008 |
|
1009 |
return (fvar, BindS (VarP fvar) bexp) |
1010 |
|
1011 |
-- | Builds the readJSON instance for a given object name. |
1012 |
objectReadJSON :: String -> Q Dec |
1013 |
objectReadJSON name = do |
1014 |
let s = mkName "s" |
1015 |
body <- [| case JSON.readJSON $(varE s) of |
1016 |
JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s' |
1017 |
JSON.Error e -> |
1018 |
JSON.Error $ "Can't parse value for type " ++ |
1019 |
$(stringE name) ++ ": " ++ e |
1020 |
|] |
1021 |
return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []] |
1022 |
|
1023 |
-- * Inheritable parameter tables implementation |
1024 |
|
1025 |
-- | Compute parameter type names. |
1026 |
paramTypeNames :: String -> (String, String) |
1027 |
paramTypeNames root = ("Filled" ++ root ++ "Params", |
1028 |
"Partial" ++ root ++ "Params") |
1029 |
|
1030 |
-- | Compute information about the type of a parameter field. |
1031 |
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type) |
1032 |
paramFieldTypeInfo field_pfx fd = do |
1033 |
t <- actualFieldType fd |
1034 |
let n = mkName . (++ "P") . (field_pfx ++) . |
1035 |
fieldRecordName $ fd |
1036 |
return (n, NotStrict, AppT (ConT ''Maybe) t) |
1037 |
|
1038 |
-- | Build a parameter declaration. |
1039 |
-- |
1040 |
-- This function builds two different data structures: a /filled/ one, |
1041 |
-- in which all fields are required, and a /partial/ one, in which all |
1042 |
-- fields are optional. Due to the current record syntax issues, the |
1043 |
-- fields need to be named differrently for the two structures, so the |
1044 |
-- partial ones get a /P/ suffix. |
1045 |
buildParam :: String -> String -> [Field] -> Q [Dec] |
1046 |
buildParam sname field_pfx fields = do |
1047 |
let (sname_f, sname_p) = paramTypeNames sname |
1048 |
name_f = mkName sname_f |
1049 |
name_p = mkName sname_p |
1050 |
fields_f <- mapM (fieldTypeInfo field_pfx) fields |
1051 |
fields_p <- mapM (paramFieldTypeInfo field_pfx) fields |
1052 |
let decl_f = RecC name_f fields_f |
1053 |
decl_p = RecC name_p fields_p |
1054 |
let declF = DataD [] name_f [] [decl_f] [''Show, ''Eq] |
1055 |
declP = DataD [] name_p [] [decl_p] [''Show, ''Eq] |
1056 |
ser_decls_f <- buildObjectSerialisation sname_f fields |
1057 |
ser_decls_p <- buildPParamSerialisation sname_p fields |
1058 |
fill_decls <- fillParam sname field_pfx fields |
1059 |
return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls ++ |
1060 |
buildParamAllFields sname fields ++ |
1061 |
buildDictObjectInst name_f sname_f |
1062 |
|
1063 |
-- | Builds a list of all fields of a parameter. |
1064 |
buildParamAllFields :: String -> [Field] -> [Dec] |
1065 |
buildParamAllFields sname fields = |
1066 |
let vname = mkName ("all" ++ sname ++ "ParamFields") |
1067 |
sig = SigD vname (AppT ListT (ConT ''String)) |
1068 |
val = ListE $ map (LitE . StringL . fieldName) fields |
1069 |
in [sig, ValD (VarP vname) (NormalB val) []] |
1070 |
|
1071 |
-- | Builds the 'DictObject' instance for a filled parameter. |
1072 |
buildDictObjectInst :: Name -> String -> [Dec] |
1073 |
buildDictObjectInst name sname = |
1074 |
[InstanceD [] (AppT (ConT ''DictObject) (ConT name)) |
1075 |
[ValD (VarP 'toDict) (NormalB (VarE (toDictName sname))) []]] |
1076 |
|
1077 |
-- | Generates the serialisation for a partial parameter. |
1078 |
buildPParamSerialisation :: String -> [Field] -> Q [Dec] |
1079 |
buildPParamSerialisation sname fields = do |
1080 |
let name = mkName sname |
1081 |
savedecls <- genSaveObject savePParamField sname fields |
1082 |
(loadsig, loadfn) <- genLoadObject loadPParamField sname fields |
1083 |
shjson <- objectShowJSON sname |
1084 |
rdjson <- objectReadJSON sname |
1085 |
let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) |
1086 |
[rdjson, shjson] |
1087 |
return $ savedecls ++ [loadsig, loadfn, instdecl] |
1088 |
|
1089 |
-- | Generates code to save an optional parameter field. |
1090 |
savePParamField :: Name -> Field -> Q Exp |
1091 |
savePParamField fvar field = do |
1092 |
checkNonOptDef field |
1093 |
let actualVal = mkName "v" |
1094 |
normalexpr <- saveObjectField actualVal field |
1095 |
-- we have to construct the block here manually, because we can't |
1096 |
-- splice-in-splice |
1097 |
return $ CaseE (VarE fvar) [ Match (ConP 'Nothing []) |
1098 |
(NormalB (ConE '[])) [] |
1099 |
, Match (ConP 'Just [VarP actualVal]) |
1100 |
(NormalB normalexpr) [] |
1101 |
] |
1102 |
|
1103 |
-- | Generates code to load an optional parameter field. |
1104 |
loadPParamField :: Field -> Q (Name, Stmt) |
1105 |
loadPParamField field = do |
1106 |
checkNonOptDef field |
1107 |
let name = fieldName field |
1108 |
fvar <- newName name |
1109 |
-- these are used in all patterns below |
1110 |
let objvar = varNameE "o" |
1111 |
objfield = stringE name |
1112 |
loadexp = [| $(varE 'maybeFromObj) $objvar $objfield |] |
1113 |
bexp <- loadFn field loadexp objvar |
1114 |
return (fvar, BindS (VarP fvar) bexp) |
1115 |
|
1116 |
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@. |
1117 |
buildFromMaybe :: String -> Q Dec |
1118 |
buildFromMaybe fname = |
1119 |
valD (varP (mkName $ "n_" ++ fname)) |
1120 |
(normalB [| $(varE 'fromMaybe) |
1121 |
$(varNameE $ "f_" ++ fname) |
1122 |
$(varNameE $ "p_" ++ fname) |]) [] |
1123 |
|
1124 |
-- | Builds a function that executes the filling of partial parameter |
1125 |
-- from a full copy (similar to Python's fillDict). |
1126 |
fillParam :: String -> String -> [Field] -> Q [Dec] |
1127 |
fillParam sname field_pfx fields = do |
1128 |
let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields |
1129 |
(sname_f, sname_p) = paramTypeNames sname |
1130 |
oname_f = "fobj" |
1131 |
oname_p = "pobj" |
1132 |
name_f = mkName sname_f |
1133 |
name_p = mkName sname_p |
1134 |
fun_name = mkName $ "fill" ++ sname ++ "Params" |
1135 |
le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames)) |
1136 |
(NormalB . VarE . mkName $ oname_f) [] |
1137 |
le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames)) |
1138 |
(NormalB . VarE . mkName $ oname_p) [] |
1139 |
obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f) |
1140 |
$ map (mkName . ("n_" ++)) fnames |
1141 |
le_new <- mapM buildFromMaybe fnames |
1142 |
funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |] |
1143 |
let sig = SigD fun_name funt |
1144 |
fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)] |
1145 |
(NormalB $ LetE (le_full:le_part:le_new) obj_new) [] |
1146 |
fun = FunD fun_name [fclause] |
1147 |
return [sig, fun] |
1148 |
|
1149 |
-- * Template code for exceptions |
1150 |
|
1151 |
-- | Exception simple error message field. |
1152 |
excErrMsg :: (String, Q Type) |
1153 |
excErrMsg = ("errMsg", [t| String |]) |
1154 |
|
1155 |
-- | Builds an exception type definition. |
1156 |
genException :: String -- ^ Name of new type |
1157 |
-> SimpleObject -- ^ Constructor name and parameters |
1158 |
-> Q [Dec] |
1159 |
genException name cons = do |
1160 |
let tname = mkName name |
1161 |
declD <- buildSimpleCons tname cons |
1162 |
(savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $ |
1163 |
uncurry saveExcCons |
1164 |
(loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons |
1165 |
return [declD, loadsig, loadfn, savesig, savefn] |
1166 |
|
1167 |
-- | Generates the \"save\" clause for an entire exception constructor. |
1168 |
-- |
1169 |
-- This matches the exception with variables named the same as the |
1170 |
-- constructor fields (just so that the spliced in code looks nicer), |
1171 |
-- and calls showJSON on it. |
1172 |
saveExcCons :: String -- ^ The constructor name |
1173 |
-> [SimpleField] -- ^ The parameter definitions for this |
1174 |
-- constructor |
1175 |
-> Q Clause -- ^ Resulting clause |
1176 |
saveExcCons sname fields = do |
1177 |
let cname = mkName sname |
1178 |
fnames <- mapM (newName . fst) fields |
1179 |
let pat = conP cname (map varP fnames) |
1180 |
felems = if null fnames |
1181 |
then conE '() -- otherwise, empty list has no type |
1182 |
else listE $ map (\f -> [| JSON.showJSON $(varE f) |]) fnames |
1183 |
let tup = tupE [ litE (stringL sname), felems ] |
1184 |
clause [pat] (normalB [| JSON.showJSON $tup |]) [] |
1185 |
|
1186 |
-- | Generates load code for a single constructor of an exception. |
1187 |
-- |
1188 |
-- Generates the code (if there's only one argument, we will use a |
1189 |
-- list, not a tuple: |
1190 |
-- |
1191 |
-- @ |
1192 |
-- do |
1193 |
-- (x1, x2, ...) <- readJSON args |
1194 |
-- return $ Cons x1 x2 ... |
1195 |
-- @ |
1196 |
loadExcConstructor :: Name -> String -> [SimpleField] -> Q Exp |
1197 |
loadExcConstructor inname sname fields = do |
1198 |
let name = mkName sname |
1199 |
f_names <- mapM (newName . fst) fields |
1200 |
let read_args = AppE (VarE 'JSON.readJSON) (VarE inname) |
1201 |
let binds = case f_names of |
1202 |
[x] -> BindS (ListP [VarP x]) |
1203 |
_ -> BindS (TupP (map VarP f_names)) |
1204 |
cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) f_names |
1205 |
return $ DoE [binds read_args, NoBindS (AppE (VarE 'return) cval)] |
1206 |
|
1207 |
{-| Generates the loadException function. |
1208 |
|
1209 |
This generates a quite complicated function, along the lines of: |
1210 |
|
1211 |
@ |
1212 |
loadFn (JSArray [JSString name, args]) = case name of |
1213 |
"A1" -> do |
1214 |
(x1, x2, ...) <- readJSON args |
1215 |
return $ A1 x1 x2 ... |
1216 |
"a2" -> ... |
1217 |
s -> fail $ "Unknown exception" ++ s |
1218 |
loadFn v = fail $ "Expected array but got " ++ show v |
1219 |
@ |
1220 |
-} |
1221 |
genLoadExc :: Name -> String -> SimpleObject -> Q (Dec, Dec) |
1222 |
genLoadExc tname sname opdefs = do |
1223 |
let fname = mkName sname |
1224 |
exc_name <- newName "name" |
1225 |
exc_args <- newName "args" |
1226 |
exc_else <- newName "s" |
1227 |
arg_else <- newName "v" |
1228 |
fails <- [| fail $ "Unknown exception '" ++ $(varE exc_else) ++ "'" |] |
1229 |
-- default match for unknown exception name |
1230 |
let defmatch = Match (VarP exc_else) (NormalB fails) [] |
1231 |
-- the match results (per-constructor blocks) |
1232 |
str_matches <- |
1233 |
mapM (\(s, params) -> do |
1234 |
body_exp <- loadExcConstructor exc_args s params |
1235 |
return $ Match (LitP (StringL s)) (NormalB body_exp) []) |
1236 |
opdefs |
1237 |
-- the first function clause; we can't use [| |] due to TH |
1238 |
-- limitations, so we have to build the AST by hand |
1239 |
let clause1 = Clause [ConP 'JSON.JSArray |
1240 |
[ListP [ConP 'JSON.JSString [VarP exc_name], |
1241 |
VarP exc_args]]] |
1242 |
(NormalB (CaseE (AppE (VarE 'JSON.fromJSString) |
1243 |
(VarE exc_name)) |
1244 |
(str_matches ++ [defmatch]))) [] |
1245 |
-- the fail expression for the second function clause |
1246 |
fail_type <- [| fail $ "Invalid exception: expected '(string, [args])' " ++ |
1247 |
" but got " ++ show (pp_value $(varE arg_else)) ++ "'" |
1248 |
|] |
1249 |
-- the second function clause |
1250 |
let clause2 = Clause [VarP arg_else] (NormalB fail_type) [] |
1251 |
sigt <- [t| JSON.JSValue -> JSON.Result $(conT tname) |] |
1252 |
return $ (SigD fname sigt, FunD fname [clause1, clause2]) |