Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 37904802

History | View | Annotate | Download (38.7 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
-- * Exported types
73

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
182
-- * Common field declarations
183

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

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

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

    
200
-- | Tag set type alias.
201
type TagSet = Set.Set String
202

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

    
208
-- * Internal types
209

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

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

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

    
219
-- * Helper functions
220

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

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

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

    
240
-- | showJSON as an expression, for reuse.
241
showJSONE :: Q Exp
242
showJSONE = varNameE "showJSON"
243

    
244
-- | ToRaw function name.
245
toRawName :: String -> Name
246
toRawName = mkName . (++ "ToRaw") . ensureLower
247

    
248
-- | FromRaw function name.
249
fromRawName :: String -> Name
250
fromRawName = mkName . (++ "FromRaw") . ensureLower
251

    
252
-- | Converts a name to it's varE\/litE representations.
253
reprE :: Either String Name -> Q Exp
254
reprE = either stringE varE
255

    
256
-- | Smarter function application.
257
--
258
-- This does simply f x, except that if is 'id', it will skip it, in
259
-- order to generate more readable code when using -ddump-splices.
260
appFn :: Exp -> Exp -> Exp
261
appFn f x | f == VarE 'id = x
262
          | otherwise = AppE f x
263

    
264
-- | Builds a field for a normal constructor.
265
buildConsField :: Q Type -> StrictTypeQ
266
buildConsField ftype = do
267
  ftype' <- ftype
268
  return (NotStrict, ftype')
269

    
270
-- | Builds a constructor based on a simple definition (not field-based).
271
buildSimpleCons :: Name -> SimpleObject -> Q Dec
272
buildSimpleCons tname cons = do
273
  decl_d <- mapM (\(cname, fields) -> do
274
                    fields' <- mapM (buildConsField . snd) fields
275
                    return $ NormalC (mkName cname) fields') cons
276
  return $ DataD [] tname [] decl_d [''Show, ''Read, ''Eq]
277

    
278
-- | Generate the save function for a given type.
279
genSaveSimpleObj :: Name                            -- ^ Object type
280
                 -> String                          -- ^ Function name
281
                 -> SimpleObject                    -- ^ Object definition
282
                 -> (SimpleConstructor -> Q Clause) -- ^ Constructor save fn
283
                 -> Q (Dec, Dec)
284
genSaveSimpleObj tname sname opdefs fn = do
285
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
286
      fname = mkName sname
287
  cclauses <- mapM fn opdefs
288
  return $ (SigD fname sigt, FunD fname cclauses)
289

    
290
-- * Template code for simple raw type-equivalent ADTs
291

    
292
-- | Generates a data type declaration.
293
--
294
-- The type will have a fixed list of instances.
295
strADTDecl :: Name -> [String] -> Dec
296
strADTDecl name constructors =
297
  DataD [] name []
298
          (map (flip NormalC [] . mkName) constructors)
299
          [''Show, ''Read, ''Eq, ''Enum, ''Bounded, ''Ord]
300

    
301
-- | Generates a toRaw function.
302
--
303
-- This generates a simple function of the form:
304
--
305
-- @
306
-- nameToRaw :: Name -> /traw/
307
-- nameToRaw Cons1 = var1
308
-- nameToRaw Cons2 = \"value2\"
309
-- @
310
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
311
genToRaw traw fname tname constructors = do
312
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw)
313
  -- the body clauses, matching on the constructor and returning the
314
  -- raw value
315
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
316
                             (normalB (reprE v)) []) constructors
317
  return [SigD fname sigt, FunD fname clauses]
318

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

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

    
379
declareIADT :: String -> [(String, Name)] -> Q [Dec]
380
declareIADT = declareADT ''Int
381

    
382
declareSADT :: String -> [(String, Name)] -> Q [Dec]
383
declareSADT = declareADT ''String
384

    
385
-- | Creates the showJSON member of a JSON instance declaration.
386
--
387
-- This will create what is the equivalent of:
388
--
389
-- @
390
-- showJSON = showJSON . /name/ToRaw
391
-- @
392
--
393
-- in an instance JSON /name/ declaration
394
genShowJSON :: String -> Q Dec
395
genShowJSON name = do
396
  body <- [| JSON.showJSON . $(varE (toRawName name)) |]
397
  return $ FunD (mkName "showJSON") [Clause [] (NormalB body) []]
398

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

    
422
-- | Generates a JSON instance for a given type.
423
--
424
-- This assumes that the /name/ToRaw and /name/FromRaw functions
425
-- have been defined as by the 'declareSADT' function.
426
makeJSONInstance :: Name -> Q [Dec]
427
makeJSONInstance name = do
428
  let base = nameBase name
429
  showJ <- genShowJSON base
430
  readJ <- genReadJSON base
431
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]]
432

    
433
-- * Template code for opcodes
434

    
435
-- | Transforms a CamelCase string into an_underscore_based_one.
436
deCamelCase :: String -> String
437
deCamelCase =
438
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
439

    
440
-- | Transform an underscore_name into a CamelCase one.
441
camelCase :: String -> String
442
camelCase = concatMap (ensureUpper . drop 1) .
443
            groupBy (\_ b -> b /= '_' && b /= '-') . ('_':)
444

    
445
-- | Computes the name of a given constructor.
446
constructorName :: Con -> Q Name
447
constructorName (NormalC name _) = return name
448
constructorName (RecC name _)    = return name
449
constructorName x                = fail $ "Unhandled constructor " ++ show x
450

    
451
-- | Extract all constructor names from a given type.
452
reifyConsNames :: Name -> Q [String]
453
reifyConsNames name = do
454
  reify_result <- reify name
455
  case reify_result of
456
    TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons
457
    o -> fail $ "Unhandled name passed to reifyConsNames, expected\
458
                \ type constructor but got '" ++ show o ++ "'"
459

    
460
-- | Builds the generic constructor-to-string function.
461
--
462
-- This generates a simple function of the following form:
463
--
464
-- @
465
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne")
466
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo")
467
-- @
468
--
469
-- This builds a custom list of name\/string pairs and then uses
470
-- 'genToRaw' to actually generate the function.
471
genConstrToStr :: (String -> String) -> Name -> String -> Q [Dec]
472
genConstrToStr trans_fun name fname = do
473
  cnames <- reifyConsNames name
474
  let svalues = map (Left . trans_fun) cnames
475
  genToRaw ''String (mkName fname) name $ zip cnames svalues
476

    
477
-- | Constructor-to-string for OpCode.
478
genOpID :: Name -> String -> Q [Dec]
479
genOpID = genConstrToStr deCamelCase
480

    
481
-- | Builds a list with all defined constructor names for a type.
482
--
483
-- @
484
-- vstr :: String
485
-- vstr = [...]
486
-- @
487
--
488
-- Where the actual values of the string are the constructor names
489
-- mapped via @trans_fun@.
490
genAllConstr :: (String -> String) -> Name -> String -> Q [Dec]
491
genAllConstr trans_fun name vstr = do
492
  cnames <- reifyConsNames name
493
  let svalues = sort $ map trans_fun cnames
494
      vname = mkName vstr
495
      sig = SigD vname (AppT ListT (ConT ''String))
496
      body = NormalB (ListE (map (LitE . StringL) svalues))
497
  return $ [sig, ValD (VarP vname) body []]
498

    
499
-- | Generates a list of all defined opcode IDs.
500
genAllOpIDs :: Name -> String -> Q [Dec]
501
genAllOpIDs = genAllConstr deCamelCase
502

    
503
-- | OpCode parameter (field) type.
504
type OpParam = (String, Q Type, Q Exp)
505

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

    
525
  (savesig, savefn) <- genSaveOpCode tname "saveOpCode" cons
526
                         (uncurry saveConstructor)
527
  (loadsig, loadfn) <- genLoadOpCode cons
528
  return [declD, loadsig, loadfn, savesig, savefn]
529

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

    
552
-- | Generates the main save opcode function.
553
--
554
-- This builds a per-constructor match clause that contains the
555
-- respective constructor-serialisation code.
556
genSaveOpCode :: Name                            -- ^ Object ype
557
              -> String                          -- ^ Function name
558
              -> [(String, [Field])]             -- ^ Object definition
559
              -> ((String, [Field]) -> Q Clause) -- ^ Constructor save fn
560
              -> Q (Dec, Dec)
561
genSaveOpCode tname sname opdefs fn = do
562
  cclauses <- mapM fn opdefs
563
  let fname = mkName sname
564
      sigt = AppT  (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
565
  return $ (SigD fname sigt, FunD fname cclauses)
566

    
567
-- | Generates load code for a single constructor of the opcode data type.
568
loadConstructor :: String -> [Field] -> Q Exp
569
loadConstructor sname fields = do
570
  let name = mkName sname
571
  fbinds <- mapM loadObjectField fields
572
  let (fnames, fstmts) = unzip fbinds
573
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
574
      fstmts' = fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
575
  return $ DoE fstmts'
576

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

    
601
-- * Template code for luxi
602

    
603
-- | Constructor-to-string for LuxiOp.
604
genStrOfOp :: Name -> String -> Q [Dec]
605
genStrOfOp = genConstrToStr id
606

    
607
-- | Constructor-to-string for MsgKeys.
608
genStrOfKey :: Name -> String -> Q [Dec]
609
genStrOfKey = genConstrToStr ensureLower
610

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

    
641
-- | Generates the \"save\" expression for a single luxi parameter.
642
saveLuxiField :: Name -> SimpleField -> Q Exp
643
saveLuxiField fvar (_, qt) =
644
    [| JSON.showJSON $(varE fvar) |]
645

    
646
-- | Generates the \"save\" clause for entire LuxiOp constructor.
647
saveLuxiConstructor :: (String, [Field]) -> Q Clause
648
saveLuxiConstructor (sname, fields) = do
649
  let cname = mkName sname
650
  fnames <- mapM (newName . fieldVariable) fields
651
  let pat = conP cname (map varP fnames)
652
  let felems = map (uncurry saveObjectField) (zip fnames fields)
653
      flist = if null felems
654
                then [| JSON.showJSON () |]
655
                else [| JSON.showJSON (map snd $ concat $(listE felems)) |]
656
  clause [pat] (normalB flist) []
657

    
658
-- * "Objects" functionality
659

    
660
-- | Extract the field's declaration from a Field structure.
661
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
662
fieldTypeInfo field_pfx fd = do
663
  t <- actualFieldType fd
664
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
665
  return (n, NotStrict, t)
666

    
667
-- | Build an object declaration.
668
buildObject :: String -> String -> [Field] -> Q [Dec]
669
buildObject sname field_pfx fields = do
670
  let name = mkName sname
671
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
672
  let decl_d = RecC name fields_d
673
  let declD = DataD [] name [] [decl_d] [''Show, ''Read, ''Eq]
674
  ser_decls <- buildObjectSerialisation sname fields
675
  return $ declD:ser_decls
676

    
677
-- | Generates an object definition: data type and its JSON instance.
678
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
679
buildObjectSerialisation sname fields = do
680
  let name = mkName sname
681
  savedecls <- genSaveObject saveObjectField sname fields
682
  (loadsig, loadfn) <- genLoadObject loadObjectField sname fields
683
  shjson <- objectShowJSON sname
684
  rdjson <- objectReadJSON sname
685
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
686
                 [rdjson, shjson]
687
  return $ savedecls ++ [loadsig, loadfn, instdecl]
688

    
689
-- | The toDict function name for a given type.
690
toDictName :: String -> Name
691
toDictName sname = mkName ("toDict" ++ sname)
692

    
693
-- | Generates the save object functionality.
694
genSaveObject :: (Name -> Field -> Q Exp)
695
              -> String -> [Field] -> Q [Dec]
696
genSaveObject save_fn sname fields = do
697
  let name = mkName sname
698
  fnames <- mapM (newName . fieldVariable) fields
699
  let pat = conP name (map varP fnames)
700
  let tdname = toDictName sname
701
  tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |]
702

    
703
  let felems = map (uncurry save_fn) (zip fnames fields)
704
      flist = listE felems
705
      -- and finally convert all this to a json object
706
      tdlist = [| concat $flist |]
707
      iname = mkName "i"
708
  tclause <- clause [pat] (normalB tdlist) []
709
  cclause <- [| $(varNameE "makeObj") . $(varE tdname) |]
710
  let fname = mkName ("save" ++ sname)
711
  sigt <- [t| $(conT name) -> JSON.JSValue |]
712
  return [SigD tdname tdsigt, FunD tdname [tclause],
713
          SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
714

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

    
740
-- | Generates the showJSON clause for a given object name.
741
objectShowJSON :: String -> Q Dec
742
objectShowJSON name = do
743
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
744
  return $ FunD (mkName "showJSON") [Clause [] (NormalB body) []]
745

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

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

    
786
  return (fvar, BindS (VarP fvar) bexp)
787

    
788
-- | Builds the readJSON instance for a given object name.
789
objectReadJSON :: String -> Q Dec
790
objectReadJSON name = do
791
  let s = mkName "s"
792
  body <- [| case JSON.readJSON $(varE s) of
793
               JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s'
794
               JSON.Error e ->
795
                 JSON.Error $ "Can't parse value for type " ++
796
                       $(stringE name) ++ ": " ++ e
797
           |]
798
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
799

    
800
-- * Inheritable parameter tables implementation
801

    
802
-- | Compute parameter type names.
803
paramTypeNames :: String -> (String, String)
804
paramTypeNames root = ("Filled"  ++ root ++ "Params",
805
                       "Partial" ++ root ++ "Params")
806

    
807
-- | Compute information about the type of a parameter field.
808
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
809
paramFieldTypeInfo field_pfx fd = do
810
  t <- actualFieldType fd
811
  let n = mkName . (++ "P") . (field_pfx ++) .
812
          fieldRecordName $ fd
813
  return (n, NotStrict, AppT (ConT ''Maybe) t)
814

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

    
840
-- | Builds a list of all fields of a parameter.
841
buildParamAllFields :: String -> [Field] -> [Dec]
842
buildParamAllFields sname fields =
843
  let vname = mkName ("all" ++ sname ++ "ParamFields")
844
      sig = SigD vname (AppT ListT (ConT ''String))
845
      val = ListE $ map (LitE . StringL . fieldName) fields
846
  in [sig, ValD (VarP vname) (NormalB val) []]
847

    
848
-- | Builds the 'DictObject' instance for a filled parameter.
849
buildDictObjectInst :: Name -> String -> [Dec]
850
buildDictObjectInst name sname =
851
  [InstanceD [] (AppT (ConT ''DictObject) (ConT name))
852
   [ValD (VarP 'toDict) (NormalB (VarE (toDictName sname))) []]]
853

    
854
-- | Generates the serialisation for a partial parameter.
855
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
856
buildPParamSerialisation sname fields = do
857
  let name = mkName sname
858
  savedecls <- genSaveObject savePParamField sname fields
859
  (loadsig, loadfn) <- genLoadObject loadPParamField sname fields
860
  shjson <- objectShowJSON sname
861
  rdjson <- objectReadJSON sname
862
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
863
                 [rdjson, shjson]
864
  return $ savedecls ++ [loadsig, loadfn, instdecl]
865

    
866
-- | Generates code to save an optional parameter field.
867
savePParamField :: Name -> Field -> Q Exp
868
savePParamField fvar field = do
869
  checkNonOptDef field
870
  let actualVal = mkName "v"
871
  normalexpr <- saveObjectField actualVal field
872
  -- we have to construct the block here manually, because we can't
873
  -- splice-in-splice
874
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
875
                                       (NormalB (ConE '[])) []
876
                             , Match (ConP 'Just [VarP actualVal])
877
                                       (NormalB normalexpr) []
878
                             ]
879

    
880
-- | Generates code to load an optional parameter field.
881
loadPParamField :: Field -> Q (Name, Stmt)
882
loadPParamField field = do
883
  checkNonOptDef field
884
  let name = fieldName field
885
  fvar <- newName name
886
  -- these are used in all patterns below
887
  let objvar = varNameE "o"
888
      objfield = stringE name
889
      loadexp = [| $(varNameE "maybeFromObj") $objvar $objfield |]
890
  bexp <- loadFn field loadexp objvar
891
  return (fvar, BindS (VarP fvar) bexp)
892

    
893
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
894
buildFromMaybe :: String -> Q Dec
895
buildFromMaybe fname =
896
  valD (varP (mkName $ "n_" ++ fname))
897
         (normalB [| $(varNameE "fromMaybe")
898
                        $(varNameE $ "f_" ++ fname)
899
                        $(varNameE $ "p_" ++ fname) |]) []
900

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

    
926
-- * Template code for exceptions
927

    
928
-- | Exception simple error message field.
929
excErrMsg :: (String, Q Type)
930
excErrMsg = ("errMsg", [t| String |])
931

    
932
-- | Builds an exception type definition.
933
genException :: String                  -- ^ Name of new type
934
             -> SimpleObject -- ^ Constructor name and parameters
935
             -> Q [Dec]
936
genException name cons = do
937
  let tname = mkName name
938
  declD <- buildSimpleCons tname cons
939
  (savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $
940
                         uncurry saveExcCons
941
  (loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons
942
  return [declD, loadsig, loadfn, savesig, savefn]
943

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

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

    
984
{-| Generates the loadException function.
985

    
986
This generates a quite complicated function, along the lines of:
987

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