Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 32a569fe

History | View | Annotate | Download (38.8 kB)

1
{-# LANGUAGE 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
                  , genOpID
36
                  , genAllConstr
37
                  , genAllOpIDs
38
                  , genOpCode
39
                  , genStrOfOp
40
                  , genStrOfKey
41
                  , genLuxiOp
42
                  , Field
43
                  , simpleField
44
                  , defaultField
45
                  , optionalField
46
                  , optionalNullSerField
47
                  , renameField
48
                  , customField
49
                  , timeStampFields
50
                  , uuidFields
51
                  , serialFields
52
                  , tagsFields
53
                  , TagSet
54
                  , buildObject
55
                  , buildObjectSerialisation
56
                  , buildParam
57
                  , DictObject(..)
58
                  , genException
59
                  , excErrMsg
60
                  ) where
61

    
62
import Control.Monad (liftM)
63
import Data.Char
64
import Data.List
65
import Data.Maybe (fromMaybe)
66
import qualified Data.Set as Set
67
import Language.Haskell.TH
68

    
69
import qualified Text.JSON as JSON
70
import Text.JSON.Pretty (pp_value)
71

    
72
import Ganeti.JSON
73

    
74
-- * Exported types
75

    
76
-- | Class of objects that can be converted to 'JSObject'
77
-- lists-format.
78
class DictObject a where
79
  toDict :: a -> [(String, JSON.JSValue)]
80

    
81
-- | Optional field information.
82
data OptionalType
83
  = NotOptional           -- ^ Field is not optional
84
  | OptionalOmitNull      -- ^ Field is optional, null is not serialised
85
  | OptionalSerializeNull -- ^ Field is optional, null is serialised
86
  deriving (Show, Eq)
87

    
88
-- | Serialised field data type.
89
data Field = Field { fieldName        :: String
90
                   , fieldType        :: Q Type
91
                   , fieldRead        :: Maybe (Q Exp)
92
                   , fieldShow        :: Maybe (Q Exp)
93
                   , fieldDefault     :: Maybe (Q Exp)
94
                   , fieldConstr      :: Maybe String
95
                   , fieldIsOptional  :: OptionalType
96
                   }
97

    
98
-- | Generates a simple field.
99
simpleField :: String -> Q Type -> Field
100
simpleField fname ftype =
101
  Field { fieldName        = fname
102
        , fieldType        = ftype
103
        , fieldRead        = Nothing
104
        , fieldShow        = Nothing
105
        , fieldDefault     = Nothing
106
        , fieldConstr      = Nothing
107
        , fieldIsOptional  = NotOptional
108
        }
109

    
110
-- | Sets the renamed constructor field.
111
renameField :: String -> Field -> Field
112
renameField constrName field = field { fieldConstr = Just constrName }
113

    
114
-- | Sets the default value on a field (makes it optional with a
115
-- default value).
116
defaultField :: Q Exp -> Field -> Field
117
defaultField defval field = field { fieldDefault = Just defval }
118

    
119
-- | Marks a field optional (turning its base type into a Maybe).
120
optionalField :: Field -> Field
121
optionalField field = field { fieldIsOptional = OptionalOmitNull }
122

    
123
-- | Marks a field optional (turning its base type into a Maybe), but
124
-- with 'Nothing' serialised explicitly as /null/.
125
optionalNullSerField :: Field -> Field
126
optionalNullSerField field = field { fieldIsOptional = OptionalSerializeNull }
127

    
128
-- | Sets custom functions on a field.
129
customField :: Name    -- ^ The name of the read function
130
            -> Name    -- ^ The name of the show function
131
            -> Field   -- ^ The original field
132
            -> Field   -- ^ Updated field
133
customField readfn showfn field =
134
  field { fieldRead = Just (varE readfn), fieldShow = Just (varE showfn) }
135

    
136
-- | Computes the record name for a given field, based on either the
137
-- string value in the JSON serialisation or the custom named if any
138
-- exists.
139
fieldRecordName :: Field -> String
140
fieldRecordName (Field { fieldName = name, fieldConstr = alias }) =
141
  fromMaybe (camelCase name) alias
142

    
143
-- | Computes the preferred variable name to use for the value of this
144
-- field. If the field has a specific constructor name, then we use a
145
-- first-letter-lowercased version of that; otherwise, we simply use
146
-- the field name. See also 'fieldRecordName'.
147
fieldVariable :: Field -> String
148
fieldVariable f =
149
  case (fieldConstr f) of
150
    Just name -> ensureLower name
151
    _ -> map (\c -> if c == '-' then '_' else c) $ fieldName f
152

    
153
-- | Compute the actual field type (taking into account possible
154
-- optional status).
155
actualFieldType :: Field -> Q Type
156
actualFieldType f | fieldIsOptional f /= NotOptional = [t| Maybe $t |]
157
                  | otherwise = t
158
                  where t = fieldType f
159

    
160
-- | Checks that a given field is not optional (for object types or
161
-- fields which should not allow this case).
162
checkNonOptDef :: (Monad m) => Field -> m ()
163
checkNonOptDef (Field { fieldIsOptional = OptionalOmitNull
164
                      , fieldName = name }) =
165
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
166
checkNonOptDef (Field { fieldIsOptional = OptionalSerializeNull
167
                      , fieldName = name }) =
168
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
169
checkNonOptDef (Field { fieldDefault = (Just _), fieldName = name }) =
170
  fail $ "Default field " ++ name ++ " used in parameter declaration"
171
checkNonOptDef _ = return ()
172

    
173
-- | Produces the expression that will de-serialise a given
174
-- field. Since some custom parsing functions might need to use the
175
-- entire object, we do take and pass the object to any custom read
176
-- functions.
177
loadFn :: Field   -- ^ The field definition
178
       -> Q Exp   -- ^ The value of the field as existing in the JSON message
179
       -> Q Exp   -- ^ The entire object in JSON object format
180
       -> Q Exp   -- ^ Resulting expression
181
loadFn (Field { fieldRead = Just readfn }) expr o = [| $expr >>= $readfn $o |]
182
loadFn _ expr _ = expr
183

    
184
-- * Common field declarations
185

    
186
-- | Timestamp fields description.
187
timeStampFields :: [Field]
188
timeStampFields =
189
    [ defaultField [| 0::Double |] $ simpleField "ctime" [t| Double |]
190
    , defaultField [| 0::Double |] $ simpleField "mtime" [t| Double |]
191
    ]
192

    
193
-- | Serial number fields description.
194
serialFields :: [Field]
195
serialFields =
196
    [ renameField  "Serial" $ simpleField "serial_no" [t| Int |] ]
197

    
198
-- | UUID fields description.
199
uuidFields :: [Field]
200
uuidFields = [ simpleField "uuid" [t| String |] ]
201

    
202
-- | Tag set type alias.
203
type TagSet = Set.Set String
204

    
205
-- | Tag field description.
206
tagsFields :: [Field]
207
tagsFields = [ defaultField [| Set.empty |] $
208
               simpleField "tags" [t| TagSet |] ]
209

    
210
-- * Internal types
211

    
212
-- | A simple field, in constrast to the customisable 'Field' type.
213
type SimpleField = (String, Q Type)
214

    
215
-- | A definition for a single constructor for a simple object.
216
type SimpleConstructor = (String, [SimpleField])
217

    
218
-- | A definition for ADTs with simple fields.
219
type SimpleObject = [SimpleConstructor]
220

    
221
-- * Helper functions
222

    
223
-- | Ensure first letter is lowercase.
224
--
225
-- Used to convert type name to function prefix, e.g. in @data Aa ->
226
-- aaToRaw@.
227
ensureLower :: String -> String
228
ensureLower [] = []
229
ensureLower (x:xs) = toLower x:xs
230

    
231
-- | Ensure first letter is uppercase.
232
--
233
-- Used to convert constructor name to component
234
ensureUpper :: String -> String
235
ensureUpper [] = []
236
ensureUpper (x:xs) = toUpper x:xs
237

    
238
-- | Helper for quoted expressions.
239
varNameE :: String -> Q Exp
240
varNameE = varE . mkName
241

    
242
-- | showJSON as an expression, for reuse.
243
showJSONE :: Q Exp
244
showJSONE = varE 'JSON.showJSON
245

    
246
-- | makeObj as an expression, for reuse.
247
makeObjE :: Q Exp
248
makeObjE = varE 'JSON.makeObj
249

    
250
-- | fromObj (Ganeti specific) as an expression, for reuse.
251
fromObjE :: Q Exp
252
fromObjE = varE 'fromObj
253

    
254
-- | ToRaw function name.
255
toRawName :: String -> Name
256
toRawName = mkName . (++ "ToRaw") . ensureLower
257

    
258
-- | FromRaw function name.
259
fromRawName :: String -> Name
260
fromRawName = mkName . (++ "FromRaw") . ensureLower
261

    
262
-- | Converts a name to it's varE\/litE representations.
263
reprE :: Either String Name -> Q Exp
264
reprE = either stringE varE
265

    
266
-- | Smarter function application.
267
--
268
-- This does simply f x, except that if is 'id', it will skip it, in
269
-- order to generate more readable code when using -ddump-splices.
270
appFn :: Exp -> Exp -> Exp
271
appFn f x | f == VarE 'id = x
272
          | otherwise = AppE f x
273

    
274
-- | Builds a field for a normal constructor.
275
buildConsField :: Q Type -> StrictTypeQ
276
buildConsField ftype = do
277
  ftype' <- ftype
278
  return (NotStrict, ftype')
279

    
280
-- | Builds a constructor based on a simple definition (not field-based).
281
buildSimpleCons :: Name -> SimpleObject -> Q Dec
282
buildSimpleCons tname cons = do
283
  decl_d <- mapM (\(cname, fields) -> do
284
                    fields' <- mapM (buildConsField . snd) fields
285
                    return $ NormalC (mkName cname) fields') cons
286
  return $ DataD [] tname [] decl_d [''Show, ''Read, ''Eq]
287

    
288
-- | Generate the save function for a given type.
289
genSaveSimpleObj :: Name                            -- ^ Object type
290
                 -> String                          -- ^ Function name
291
                 -> SimpleObject                    -- ^ Object definition
292
                 -> (SimpleConstructor -> Q Clause) -- ^ Constructor save fn
293
                 -> Q (Dec, Dec)
294
genSaveSimpleObj tname sname opdefs fn = do
295
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
296
      fname = mkName sname
297
  cclauses <- mapM fn opdefs
298
  return $ (SigD fname sigt, FunD fname cclauses)
299

    
300
-- * Template code for simple raw type-equivalent ADTs
301

    
302
-- | Generates a data type declaration.
303
--
304
-- The type will have a fixed list of instances.
305
strADTDecl :: Name -> [String] -> Dec
306
strADTDecl name constructors =
307
  DataD [] name []
308
          (map (flip NormalC [] . mkName) constructors)
309
          [''Show, ''Read, ''Eq, ''Enum, ''Bounded, ''Ord]
310

    
311
-- | Generates a toRaw function.
312
--
313
-- This generates a simple function of the form:
314
--
315
-- @
316
-- nameToRaw :: Name -> /traw/
317
-- nameToRaw Cons1 = var1
318
-- nameToRaw Cons2 = \"value2\"
319
-- @
320
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
321
genToRaw traw fname tname constructors = do
322
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw)
323
  -- the body clauses, matching on the constructor and returning the
324
  -- raw value
325
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
326
                             (normalB (reprE v)) []) constructors
327
  return [SigD fname sigt, FunD fname clauses]
328

    
329
-- | Generates a fromRaw function.
330
--
331
-- The function generated is monadic and can fail parsing the
332
-- raw value. It is of the form:
333
--
334
-- @
335
-- nameFromRaw :: (Monad m) => /traw/ -> m Name
336
-- nameFromRaw s | s == var1       = Cons1
337
--               | s == \"value2\" = Cons2
338
--               | otherwise = fail /.../
339
-- @
340
genFromRaw :: Name -> Name -> Name -> [(String, Name)] -> Q [Dec]
341
genFromRaw traw fname tname constructors = do
342
  -- signature of form (Monad m) => String -> m $name
343
  sigt <- [t| (Monad m) => $(conT traw) -> m $(conT tname) |]
344
  -- clauses for a guarded pattern
345
  let varp = mkName "s"
346
      varpe = varE varp
347
  clauses <- mapM (\(c, v) -> do
348
                     -- the clause match condition
349
                     g <- normalG [| $varpe == $(varE v) |]
350
                     -- the clause result
351
                     r <- [| return $(conE (mkName c)) |]
352
                     return (g, r)) constructors
353
  -- the otherwise clause (fallback)
354
  oth_clause <- do
355
    g <- normalG [| otherwise |]
356
    r <- [|fail ("Invalid string value for type " ++
357
                 $(litE (stringL (nameBase tname))) ++ ": " ++ show $varpe) |]
358
    return (g, r)
359
  let fun = FunD fname [Clause [VarP varp]
360
                        (GuardedB (clauses++[oth_clause])) []]
361
  return [SigD fname sigt, fun]
362

    
363
-- | Generates a data type from a given raw format.
364
--
365
-- The format is expected to multiline. The first line contains the
366
-- type name, and the rest of the lines must contain two words: the
367
-- constructor name and then the string representation of the
368
-- respective constructor.
369
--
370
-- The function will generate the data type declaration, and then two
371
-- functions:
372
--
373
-- * /name/ToRaw, which converts the type to a raw type
374
--
375
-- * /name/FromRaw, which (monadically) converts from a raw type to the type
376
--
377
-- Note that this is basically just a custom show\/read instance,
378
-- nothing else.
379
declareADT :: Name -> String -> [(String, Name)] -> Q [Dec]
380
declareADT traw sname cons = do
381
  let name = mkName sname
382
      ddecl = strADTDecl name (map fst cons)
383
      -- process cons in the format expected by genToRaw
384
      cons' = map (\(a, b) -> (a, Right b)) cons
385
  toraw <- genToRaw traw (toRawName sname) name cons'
386
  fromraw <- genFromRaw traw (fromRawName sname) name cons
387
  return $ ddecl:toraw ++ fromraw
388

    
389
declareIADT :: String -> [(String, Name)] -> Q [Dec]
390
declareIADT = declareADT ''Int
391

    
392
declareSADT :: String -> [(String, Name)] -> Q [Dec]
393
declareSADT = declareADT ''String
394

    
395
-- | Creates the showJSON member of a JSON instance declaration.
396
--
397
-- This will create what is the equivalent of:
398
--
399
-- @
400
-- showJSON = showJSON . /name/ToRaw
401
-- @
402
--
403
-- in an instance JSON /name/ declaration
404
genShowJSON :: String -> Q Dec
405
genShowJSON name = do
406
  body <- [| JSON.showJSON . $(varE (toRawName name)) |]
407
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
408

    
409
-- | Creates the readJSON member of a JSON instance declaration.
410
--
411
-- This will create what is the equivalent of:
412
--
413
-- @
414
-- readJSON s = case readJSON s of
415
--                Ok s' -> /name/FromRaw s'
416
--                Error e -> Error /description/
417
-- @
418
--
419
-- in an instance JSON /name/ declaration
420
genReadJSON :: String -> Q Dec
421
genReadJSON name = do
422
  let s = mkName "s"
423
  body <- [| case JSON.readJSON $(varE s) of
424
               JSON.Ok s' -> $(varE (fromRawName name)) s'
425
               JSON.Error e ->
426
                   JSON.Error $ "Can't parse raw value for type " ++
427
                           $(stringE name) ++ ": " ++ e ++ " from " ++
428
                           show $(varE s)
429
           |]
430
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
431

    
432
-- | Generates a JSON instance for a given type.
433
--
434
-- This assumes that the /name/ToRaw and /name/FromRaw functions
435
-- have been defined as by the 'declareSADT' function.
436
makeJSONInstance :: Name -> Q [Dec]
437
makeJSONInstance name = do
438
  let base = nameBase name
439
  showJ <- genShowJSON base
440
  readJ <- genReadJSON base
441
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]]
442

    
443
-- * Template code for opcodes
444

    
445
-- | Transforms a CamelCase string into an_underscore_based_one.
446
deCamelCase :: String -> String
447
deCamelCase =
448
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
449

    
450
-- | Transform an underscore_name into a CamelCase one.
451
camelCase :: String -> String
452
camelCase = concatMap (ensureUpper . drop 1) .
453
            groupBy (\_ b -> b /= '_' && b /= '-') . ('_':)
454

    
455
-- | Computes the name of a given constructor.
456
constructorName :: Con -> Q Name
457
constructorName (NormalC name _) = return name
458
constructorName (RecC name _)    = return name
459
constructorName x                = fail $ "Unhandled constructor " ++ show x
460

    
461
-- | Extract all constructor names from a given type.
462
reifyConsNames :: Name -> Q [String]
463
reifyConsNames name = do
464
  reify_result <- reify name
465
  case reify_result of
466
    TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons
467
    o -> fail $ "Unhandled name passed to reifyConsNames, expected\
468
                \ type constructor but got '" ++ show o ++ "'"
469

    
470
-- | Builds the generic constructor-to-string function.
471
--
472
-- This generates a simple function of the following form:
473
--
474
-- @
475
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne")
476
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo")
477
-- @
478
--
479
-- This builds a custom list of name\/string pairs and then uses
480
-- 'genToRaw' to actually generate the function.
481
genConstrToStr :: (String -> String) -> Name -> String -> Q [Dec]
482
genConstrToStr trans_fun name fname = do
483
  cnames <- reifyConsNames name
484
  let svalues = map (Left . trans_fun) cnames
485
  genToRaw ''String (mkName fname) name $ zip cnames svalues
486

    
487
-- | Constructor-to-string for OpCode.
488
genOpID :: Name -> String -> Q [Dec]
489
genOpID = genConstrToStr deCamelCase
490

    
491
-- | Builds a list with all defined constructor names for a type.
492
--
493
-- @
494
-- vstr :: String
495
-- vstr = [...]
496
-- @
497
--
498
-- Where the actual values of the string are the constructor names
499
-- mapped via @trans_fun@.
500
genAllConstr :: (String -> String) -> Name -> String -> Q [Dec]
501
genAllConstr trans_fun name vstr = do
502
  cnames <- reifyConsNames name
503
  let svalues = sort $ map trans_fun cnames
504
      vname = mkName vstr
505
      sig = SigD vname (AppT ListT (ConT ''String))
506
      body = NormalB (ListE (map (LitE . StringL) svalues))
507
  return $ [sig, ValD (VarP vname) body []]
508

    
509
-- | Generates a list of all defined opcode IDs.
510
genAllOpIDs :: Name -> String -> Q [Dec]
511
genAllOpIDs = genAllConstr deCamelCase
512

    
513
-- | OpCode parameter (field) type.
514
type OpParam = (String, Q Type, Q Exp)
515

    
516
-- | Generates the OpCode data type.
517
--
518
-- This takes an opcode logical definition, and builds both the
519
-- datatype and the JSON serialisation out of it. We can't use a
520
-- generic serialisation since we need to be compatible with Ganeti's
521
-- own, so we have a few quirks to work around.
522
genOpCode :: String                -- ^ Type name to use
523
          -> [(String, [Field])]   -- ^ Constructor name and parameters
524
          -> Q [Dec]
525
genOpCode name cons = do
526
  let tname = mkName name
527
  decl_d <- mapM (\(cname, fields) -> do
528
                    -- we only need the type of the field, without Q
529
                    fields' <- mapM actualFieldType fields
530
                    let fields'' = zip (repeat NotStrict) fields'
531
                    return $ NormalC (mkName cname) fields'')
532
            cons
533
  let declD = DataD [] tname [] decl_d [''Show, ''Read, ''Eq]
534

    
535
  (savesig, savefn) <- genSaveOpCode tname "saveOpCode" cons
536
                         (uncurry saveConstructor)
537
  (loadsig, loadfn) <- genLoadOpCode cons
538
  return [declD, loadsig, loadfn, savesig, savefn]
539

    
540
-- | Generates the \"save\" clause for an entire opcode constructor.
541
--
542
-- This matches the opcode with variables named the same as the
543
-- constructor fields (just so that the spliced in code looks nicer),
544
-- and passes those name plus the parameter definition to 'saveObjectField'.
545
saveConstructor :: String    -- ^ The constructor name
546
                -> [Field]   -- ^ The parameter definitions for this
547
                             -- constructor
548
                -> Q Clause  -- ^ Resulting clause
549
saveConstructor sname fields = do
550
  let cname = mkName sname
551
  fnames <- mapM (newName . fieldVariable) fields
552
  let pat = conP cname (map varP fnames)
553
  let felems = map (uncurry saveObjectField) (zip fnames fields)
554
      -- now build the OP_ID serialisation
555
      opid = [| [( $(stringE "OP_ID"),
556
                   JSON.showJSON $(stringE . deCamelCase $ sname) )] |]
557
      flist = listE (opid:felems)
558
      -- and finally convert all this to a json object
559
      flist' = [| $makeObjE (concat $flist) |]
560
  clause [pat] (normalB flist') []
561

    
562
-- | Generates the main save opcode function.
563
--
564
-- This builds a per-constructor match clause that contains the
565
-- respective constructor-serialisation code.
566
genSaveOpCode :: Name                            -- ^ Object ype
567
              -> String                          -- ^ Function name
568
              -> [(String, [Field])]             -- ^ Object definition
569
              -> ((String, [Field]) -> Q Clause) -- ^ Constructor save fn
570
              -> Q (Dec, Dec)
571
genSaveOpCode tname sname opdefs fn = do
572
  cclauses <- mapM fn opdefs
573
  let fname = mkName sname
574
      sigt = AppT  (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
575
  return $ (SigD fname sigt, FunD fname cclauses)
576

    
577
-- | Generates load code for a single constructor of the opcode data type.
578
loadConstructor :: String -> [Field] -> Q Exp
579
loadConstructor sname fields = do
580
  let name = mkName sname
581
  fbinds <- mapM loadObjectField fields
582
  let (fnames, fstmts) = unzip fbinds
583
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
584
      fstmts' = fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
585
  return $ DoE fstmts'
586

    
587
-- | Generates the loadOpCode function.
588
genLoadOpCode :: [(String, [Field])] -> Q (Dec, Dec)
589
genLoadOpCode opdefs = do
590
  let fname = mkName "loadOpCode"
591
      arg1 = mkName "v"
592
      objname = mkName "o"
593
      opid = mkName "op_id"
594
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
595
                                 (JSON.readJSON $(varE arg1)) |]
596
  st2 <- bindS (varP opid) [| $fromObjE $(varE objname) $(stringE "OP_ID") |]
597
  -- the match results (per-constructor blocks)
598
  mexps <- mapM (uncurry loadConstructor) opdefs
599
  fails <- [| fail $ "Unknown opcode " ++ $(varE opid) |]
600
  let mpats = map (\(me, c) ->
601
                       let mp = LitP . StringL . deCamelCase . fst $ c
602
                       in Match mp (NormalB me) []
603
                  ) $ zip mexps opdefs
604
      defmatch = Match WildP (NormalB fails) []
605
      cst = NoBindS $ CaseE (VarE opid) $ mpats++[defmatch]
606
      body = DoE [st1, st2, cst]
607
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT (mkName "OpCode")) |]
608
  return $ (SigD fname sigt, FunD fname [Clause [VarP arg1] (NormalB body) []])
609

    
610
-- * Template code for luxi
611

    
612
-- | Constructor-to-string for LuxiOp.
613
genStrOfOp :: Name -> String -> Q [Dec]
614
genStrOfOp = genConstrToStr id
615

    
616
-- | Constructor-to-string for MsgKeys.
617
genStrOfKey :: Name -> String -> Q [Dec]
618
genStrOfKey = genConstrToStr ensureLower
619

    
620
-- | Generates the LuxiOp data type.
621
--
622
-- This takes a Luxi operation definition and builds both the
623
-- datatype and the function trnasforming the arguments to JSON.
624
-- We can't use anything less generic, because the way different
625
-- operations are serialized differs on both parameter- and top-level.
626
--
627
-- There are two things to be defined for each parameter:
628
--
629
-- * name
630
--
631
-- * type
632
--
633
genLuxiOp :: String -> [(String, [Field])] -> Q [Dec]
634
genLuxiOp name cons = do
635
  let tname = mkName name
636
  decl_d <- mapM (\(cname, fields) -> do
637
                    -- we only need the type of the field, without Q
638
                    fields' <- mapM actualFieldType fields
639
                    let fields'' = zip (repeat NotStrict) fields'
640
                    return $ NormalC (mkName cname) fields'')
641
            cons
642
  let declD = DataD [] (mkName name) [] decl_d [''Show, ''Read, ''Eq]
643
  (savesig, savefn) <- genSaveOpCode tname "opToArgs"
644
                         cons saveLuxiConstructor
645
  req_defs <- declareSADT "LuxiReq" .
646
              map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $
647
                  cons
648
  return $ [declD, savesig, savefn] ++ req_defs
649

    
650
-- | Generates the \"save\" expression for a single luxi parameter.
651
saveLuxiField :: Name -> SimpleField -> Q Exp
652
saveLuxiField fvar (_, qt) =
653
    [| JSON.showJSON $(varE fvar) |]
654

    
655
-- | Generates the \"save\" clause for entire LuxiOp constructor.
656
saveLuxiConstructor :: (String, [Field]) -> Q Clause
657
saveLuxiConstructor (sname, fields) = do
658
  let cname = mkName sname
659
  fnames <- mapM (newName . fieldVariable) fields
660
  let pat = conP cname (map varP fnames)
661
  let felems = map (uncurry saveObjectField) (zip fnames fields)
662
      flist = if null felems
663
                then [| JSON.showJSON () |]
664
                else [| JSON.showJSON (map snd $ concat $(listE felems)) |]
665
  clause [pat] (normalB flist) []
666

    
667
-- * "Objects" functionality
668

    
669
-- | Extract the field's declaration from a Field structure.
670
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
671
fieldTypeInfo field_pfx fd = do
672
  t <- actualFieldType fd
673
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
674
  return (n, NotStrict, t)
675

    
676
-- | Build an object declaration.
677
buildObject :: String -> String -> [Field] -> Q [Dec]
678
buildObject sname field_pfx fields = do
679
  let name = mkName sname
680
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
681
  let decl_d = RecC name fields_d
682
  let declD = DataD [] name [] [decl_d] [''Show, ''Read, ''Eq]
683
  ser_decls <- buildObjectSerialisation sname fields
684
  return $ declD:ser_decls
685

    
686
-- | Generates an object definition: data type and its JSON instance.
687
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
688
buildObjectSerialisation sname fields = do
689
  let name = mkName sname
690
  savedecls <- genSaveObject saveObjectField sname fields
691
  (loadsig, loadfn) <- genLoadObject loadObjectField sname fields
692
  shjson <- objectShowJSON sname
693
  rdjson <- objectReadJSON sname
694
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
695
                 [rdjson, shjson]
696
  return $ savedecls ++ [loadsig, loadfn, instdecl]
697

    
698
-- | The toDict function name for a given type.
699
toDictName :: String -> Name
700
toDictName sname = mkName ("toDict" ++ sname)
701

    
702
-- | Generates the save object functionality.
703
genSaveObject :: (Name -> Field -> Q Exp)
704
              -> String -> [Field] -> Q [Dec]
705
genSaveObject save_fn sname fields = do
706
  let name = mkName sname
707
  fnames <- mapM (newName . fieldVariable) fields
708
  let pat = conP name (map varP fnames)
709
  let tdname = toDictName sname
710
  tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |]
711

    
712
  let felems = map (uncurry save_fn) (zip fnames fields)
713
      flist = listE felems
714
      -- and finally convert all this to a json object
715
      tdlist = [| concat $flist |]
716
      iname = mkName "i"
717
  tclause <- clause [pat] (normalB tdlist) []
718
  cclause <- [| $makeObjE . $(varE tdname) |]
719
  let fname = mkName ("save" ++ sname)
720
  sigt <- [t| $(conT name) -> JSON.JSValue |]
721
  return [SigD tdname tdsigt, FunD tdname [tclause],
722
          SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
723

    
724
-- | Generates the code for saving an object's field, handling the
725
-- various types of fields that we have.
726
saveObjectField :: Name -> Field -> Q Exp
727
saveObjectField fvar field =
728
  case fieldIsOptional field of
729
    OptionalOmitNull -> [| case $(varE fvar) of
730
                             Nothing -> []
731
                             Just v  -> [( $nameE, JSON.showJSON v )]
732
                         |]
733
    OptionalSerializeNull -> [| case $(varE fvar) of
734
                                  Nothing -> [( $nameE, JSON.JSNull )]
735
                                  Just v  -> [( $nameE, JSON.showJSON v )]
736
                              |]
737
    NotOptional ->
738
      case fieldShow field of
739
        -- Note: the order of actual:extra is important, since for
740
        -- some serialisation types (e.g. Luxi), we use tuples
741
        -- (positional info) rather than object (name info)
742
        Nothing -> [| [( $nameE, JSON.showJSON $fvarE)] |]
743
        Just fn -> [| let (actual, extra) = $fn $fvarE
744
                      in ($nameE, JSON.showJSON actual):extra
745
                    |]
746
  where nameE = stringE (fieldName field)
747
        fvarE = varE fvar
748

    
749
-- | Generates the showJSON clause for a given object name.
750
objectShowJSON :: String -> Q Dec
751
objectShowJSON name = do
752
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
753
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
754

    
755
-- | Generates the load object functionality.
756
genLoadObject :: (Field -> Q (Name, Stmt))
757
              -> String -> [Field] -> Q (Dec, Dec)
758
genLoadObject load_fn sname fields = do
759
  let name = mkName sname
760
      funname = mkName $ "load" ++ sname
761
      arg1 = mkName "v"
762
      objname = mkName "o"
763
      opid = mkName "op_id"
764
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
765
                                 (JSON.readJSON $(varE arg1)) |]
766
  fbinds <- mapM load_fn fields
767
  let (fnames, fstmts) = unzip fbinds
768
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
769
      fstmts' = st1:fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
770
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT name) |]
771
  return $ (SigD funname sigt,
772
            FunD funname [Clause [VarP arg1] (NormalB (DoE fstmts')) []])
773

    
774
-- | Generates code for loading an object's field.
775
loadObjectField :: Field -> Q (Name, Stmt)
776
loadObjectField field = do
777
  let name = fieldVariable field
778
  fvar <- newName name
779
  -- these are used in all patterns below
780
  let objvar = varNameE "o"
781
      objfield = stringE (fieldName field)
782
      loadexp =
783
        if fieldIsOptional field /= NotOptional
784
          -- we treat both optional types the same, since
785
          -- 'maybeFromObj' can deal with both missing and null values
786
          -- appropriately (the same)
787
          then [| $(varE 'maybeFromObj) $objvar $objfield |]
788
          else case fieldDefault field of
789
                 Just defv ->
790
                   [| $(varE 'fromObjWithDefault) $objvar
791
                      $objfield $defv |]
792
                 Nothing -> [| $fromObjE $objvar $objfield |]
793
  bexp <- loadFn field loadexp objvar
794

    
795
  return (fvar, BindS (VarP fvar) bexp)
796

    
797
-- | Builds the readJSON instance for a given object name.
798
objectReadJSON :: String -> Q Dec
799
objectReadJSON name = do
800
  let s = mkName "s"
801
  body <- [| case JSON.readJSON $(varE s) of
802
               JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s'
803
               JSON.Error e ->
804
                 JSON.Error $ "Can't parse value for type " ++
805
                       $(stringE name) ++ ": " ++ e
806
           |]
807
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
808

    
809
-- * Inheritable parameter tables implementation
810

    
811
-- | Compute parameter type names.
812
paramTypeNames :: String -> (String, String)
813
paramTypeNames root = ("Filled"  ++ root ++ "Params",
814
                       "Partial" ++ root ++ "Params")
815

    
816
-- | Compute information about the type of a parameter field.
817
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
818
paramFieldTypeInfo field_pfx fd = do
819
  t <- actualFieldType fd
820
  let n = mkName . (++ "P") . (field_pfx ++) .
821
          fieldRecordName $ fd
822
  return (n, NotStrict, AppT (ConT ''Maybe) t)
823

    
824
-- | Build a parameter declaration.
825
--
826
-- This function builds two different data structures: a /filled/ one,
827
-- in which all fields are required, and a /partial/ one, in which all
828
-- fields are optional. Due to the current record syntax issues, the
829
-- fields need to be named differrently for the two structures, so the
830
-- partial ones get a /P/ suffix.
831
buildParam :: String -> String -> [Field] -> Q [Dec]
832
buildParam sname field_pfx fields = do
833
  let (sname_f, sname_p) = paramTypeNames sname
834
      name_f = mkName sname_f
835
      name_p = mkName sname_p
836
  fields_f <- mapM (fieldTypeInfo field_pfx) fields
837
  fields_p <- mapM (paramFieldTypeInfo field_pfx) fields
838
  let decl_f = RecC name_f fields_f
839
      decl_p = RecC name_p fields_p
840
  let declF = DataD [] name_f [] [decl_f] [''Show, ''Read, ''Eq]
841
      declP = DataD [] name_p [] [decl_p] [''Show, ''Read, ''Eq]
842
  ser_decls_f <- buildObjectSerialisation sname_f fields
843
  ser_decls_p <- buildPParamSerialisation sname_p fields
844
  fill_decls <- fillParam sname field_pfx fields
845
  return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls ++
846
           buildParamAllFields sname fields ++
847
           buildDictObjectInst name_f sname_f
848

    
849
-- | Builds a list of all fields of a parameter.
850
buildParamAllFields :: String -> [Field] -> [Dec]
851
buildParamAllFields sname fields =
852
  let vname = mkName ("all" ++ sname ++ "ParamFields")
853
      sig = SigD vname (AppT ListT (ConT ''String))
854
      val = ListE $ map (LitE . StringL . fieldName) fields
855
  in [sig, ValD (VarP vname) (NormalB val) []]
856

    
857
-- | Builds the 'DictObject' instance for a filled parameter.
858
buildDictObjectInst :: Name -> String -> [Dec]
859
buildDictObjectInst name sname =
860
  [InstanceD [] (AppT (ConT ''DictObject) (ConT name))
861
   [ValD (VarP 'toDict) (NormalB (VarE (toDictName sname))) []]]
862

    
863
-- | Generates the serialisation for a partial parameter.
864
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
865
buildPParamSerialisation sname fields = do
866
  let name = mkName sname
867
  savedecls <- genSaveObject savePParamField sname fields
868
  (loadsig, loadfn) <- genLoadObject loadPParamField sname fields
869
  shjson <- objectShowJSON sname
870
  rdjson <- objectReadJSON sname
871
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
872
                 [rdjson, shjson]
873
  return $ savedecls ++ [loadsig, loadfn, instdecl]
874

    
875
-- | Generates code to save an optional parameter field.
876
savePParamField :: Name -> Field -> Q Exp
877
savePParamField fvar field = do
878
  checkNonOptDef field
879
  let actualVal = mkName "v"
880
  normalexpr <- saveObjectField actualVal field
881
  -- we have to construct the block here manually, because we can't
882
  -- splice-in-splice
883
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
884
                                       (NormalB (ConE '[])) []
885
                             , Match (ConP 'Just [VarP actualVal])
886
                                       (NormalB normalexpr) []
887
                             ]
888

    
889
-- | Generates code to load an optional parameter field.
890
loadPParamField :: Field -> Q (Name, Stmt)
891
loadPParamField field = do
892
  checkNonOptDef field
893
  let name = fieldName field
894
  fvar <- newName name
895
  -- these are used in all patterns below
896
  let objvar = varNameE "o"
897
      objfield = stringE name
898
      loadexp = [| $(varE 'maybeFromObj) $objvar $objfield |]
899
  bexp <- loadFn field loadexp objvar
900
  return (fvar, BindS (VarP fvar) bexp)
901

    
902
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
903
buildFromMaybe :: String -> Q Dec
904
buildFromMaybe fname =
905
  valD (varP (mkName $ "n_" ++ fname))
906
         (normalB [| $(varE 'fromMaybe)
907
                        $(varNameE $ "f_" ++ fname)
908
                        $(varNameE $ "p_" ++ fname) |]) []
909

    
910
-- | Builds a function that executes the filling of partial parameter
911
-- from a full copy (similar to Python's fillDict).
912
fillParam :: String -> String -> [Field] -> Q [Dec]
913
fillParam sname field_pfx fields = do
914
  let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields
915
      (sname_f, sname_p) = paramTypeNames sname
916
      oname_f = "fobj"
917
      oname_p = "pobj"
918
      name_f = mkName sname_f
919
      name_p = mkName sname_p
920
      fun_name = mkName $ "fill" ++ sname ++ "Params"
921
      le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames))
922
                (NormalB . VarE . mkName $ oname_f) []
923
      le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames))
924
                (NormalB . VarE . mkName $ oname_p) []
925
      obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f)
926
                $ map (mkName . ("n_" ++)) fnames
927
  le_new <- mapM buildFromMaybe fnames
928
  funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |]
929
  let sig = SigD fun_name funt
930
      fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)]
931
                (NormalB $ LetE (le_full:le_part:le_new) obj_new) []
932
      fun = FunD fun_name [fclause]
933
  return [sig, fun]
934

    
935
-- * Template code for exceptions
936

    
937
-- | Exception simple error message field.
938
excErrMsg :: (String, Q Type)
939
excErrMsg = ("errMsg", [t| String |])
940

    
941
-- | Builds an exception type definition.
942
genException :: String                  -- ^ Name of new type
943
             -> SimpleObject -- ^ Constructor name and parameters
944
             -> Q [Dec]
945
genException name cons = do
946
  let tname = mkName name
947
  declD <- buildSimpleCons tname cons
948
  (savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $
949
                         uncurry saveExcCons
950
  (loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons
951
  return [declD, loadsig, loadfn, savesig, savefn]
952

    
953
-- | Generates the \"save\" clause for an entire exception constructor.
954
--
955
-- This matches the exception with variables named the same as the
956
-- constructor fields (just so that the spliced in code looks nicer),
957
-- and calls showJSON on it.
958
saveExcCons :: String        -- ^ The constructor name
959
            -> [SimpleField] -- ^ The parameter definitions for this
960
                             -- constructor
961
            -> Q Clause      -- ^ Resulting clause
962
saveExcCons sname fields = do
963
  let cname = mkName sname
964
  fnames <- mapM (newName . fst) fields
965
  let pat = conP cname (map varP fnames)
966
      felems = if null fnames
967
                 then conE '() -- otherwise, empty list has no type
968
                 else listE $ map (\f -> [| JSON.showJSON $(varE f) |]) fnames
969
  let tup = tupE [ litE (stringL sname), felems ]
970
  clause [pat] (normalB [| JSON.showJSON $tup |]) []
971

    
972
-- | Generates load code for a single constructor of an exception.
973
--
974
-- Generates the code (if there's only one argument, we will use a
975
-- list, not a tuple:
976
--
977
-- @
978
-- do
979
--  (x1, x2, ...) <- readJSON args
980
--  return $ Cons x1 x2 ...
981
-- @
982
loadExcConstructor :: Name -> String -> [SimpleField] -> Q Exp
983
loadExcConstructor inname sname fields = do
984
  let name = mkName sname
985
  f_names <- mapM (newName . fst) fields
986
  let read_args = AppE (VarE 'JSON.readJSON) (VarE inname)
987
  let binds = case f_names of
988
                [x] -> BindS (ListP [VarP x])
989
                _   -> BindS (TupP (map VarP f_names))
990
      cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) f_names
991
  return $ DoE [binds read_args, NoBindS (AppE (VarE 'return) cval)]
992

    
993
{-| Generates the loadException function.
994

    
995
This generates a quite complicated function, along the lines of:
996

    
997
@
998
loadFn (JSArray [JSString name, args]) = case name of
999
   "A1" -> do
1000
     (x1, x2, ...) <- readJSON args
1001
     return $ A1 x1 x2 ...
1002
   "a2" -> ...
1003
   s -> fail $ "Unknown exception" ++ s
1004
loadFn v = fail $ "Expected array but got " ++ show v
1005
@
1006
-}
1007
genLoadExc :: Name -> String -> SimpleObject -> Q (Dec, Dec)
1008
genLoadExc tname sname opdefs = do
1009
  let fname = mkName sname
1010
  exc_name <- newName "name"
1011
  exc_args <- newName "args"
1012
  exc_else <- newName "s"
1013
  arg_else <- newName "v"
1014
  fails <- [| fail $ "Unknown exception '" ++ $(varE exc_else) ++ "'" |]
1015
  -- default match for unknown exception name
1016
  let defmatch = Match (VarP exc_else) (NormalB fails) []
1017
  -- the match results (per-constructor blocks)
1018
  str_matches <-
1019
    mapM (\(s, params) -> do
1020
            body_exp <- loadExcConstructor exc_args s params
1021
            return $ Match (LitP (StringL s)) (NormalB body_exp) [])
1022
    opdefs
1023
  -- the first function clause; we can't use [| |] due to TH
1024
  -- limitations, so we have to build the AST by hand
1025
  let clause1 = Clause [ConP 'JSON.JSArray
1026
                               [ListP [ConP 'JSON.JSString [VarP exc_name],
1027
                                            VarP exc_args]]]
1028
                (NormalB (CaseE (AppE (VarE 'JSON.fromJSString)
1029
                                        (VarE exc_name))
1030
                          (str_matches ++ [defmatch]))) []
1031
  -- the fail expression for the second function clause
1032
  fail_type <- [| fail $ "Invalid exception: expected '(string, [args])' " ++
1033
                  "      but got " ++ show (pp_value $(varE arg_else)) ++ "'"
1034
                |]
1035
  -- the second function clause
1036
  let clause2 = Clause [VarP arg_else] (NormalB fail_type) []
1037
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT tname) |]
1038
  return $ (SigD fname sigt, FunD fname [clause1, clause2])