Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 9b156883

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

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

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

    
71
-- * Exported types
72

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
181
-- * Common field declarations
182

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

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

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

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

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

    
207
-- * Internal types
208

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

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

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

    
218
-- * Helper functions
219

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
432
-- * Template code for opcodes
433

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

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

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

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

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

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

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

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

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

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

    
523
  (savesig, savefn) <- genSaveOpCode cons
524
  (loadsig, loadfn) <- genLoadOpCode cons
525
  return [declD, loadsig, loadfn, savesig, savefn]
526

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

    
549
-- | Generates the main save opcode function.
550
--
551
-- This builds a per-constructor match clause that contains the
552
-- respective constructor-serialisation code.
553
genSaveOpCode :: [(String, [Field])] -> Q (Dec, Dec)
554
genSaveOpCode opdefs = do
555
  cclauses <- mapM (uncurry saveConstructor) opdefs
556
  let fname = mkName "saveOpCode"
557
  sigt <- [t| $(conT (mkName "OpCode")) -> JSON.JSValue |]
558
  return $ (SigD fname sigt, FunD fname cclauses)
559

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

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

    
594
-- * Template code for luxi
595

    
596
-- | Constructor-to-string for LuxiOp.
597
genStrOfOp :: Name -> String -> Q [Dec]
598
genStrOfOp = genConstrToStr id
599

    
600
-- | Constructor-to-string for MsgKeys.
601
genStrOfKey :: Name -> String -> Q [Dec]
602
genStrOfKey = genConstrToStr ensureLower
603

    
604
-- | Generates the LuxiOp data type.
605
--
606
-- This takes a Luxi operation definition and builds both the
607
-- datatype and the function trnasforming the arguments to JSON.
608
-- We can't use anything less generic, because the way different
609
-- operations are serialized differs on both parameter- and top-level.
610
--
611
-- There are two things to be defined for each parameter:
612
--
613
-- * name
614
--
615
-- * type
616
--
617
genLuxiOp :: String -> SimpleObject -> Q [Dec]
618
genLuxiOp name cons = do
619
  let tname = mkName name
620
  declD <- buildSimpleCons tname cons
621
  (savesig, savefn) <- genSaveSimpleObj tname "opToArgs"
622
                         cons saveLuxiConstructor
623
  req_defs <- declareSADT "LuxiReq" .
624
              map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $
625
                  cons
626
  return $ [declD, savesig, savefn] ++ req_defs
627

    
628
-- | Generates the \"save\" expression for a single luxi parameter.
629
saveLuxiField :: Name -> SimpleField -> Q Exp
630
saveLuxiField fvar (_, qt) =
631
    [| JSON.showJSON $(varE fvar) |]
632

    
633
-- | Generates the \"save\" clause for entire LuxiOp constructor.
634
saveLuxiConstructor :: SimpleConstructor -> Q Clause
635
saveLuxiConstructor (sname, fields) = do
636
  let cname = mkName sname
637
      fnames = map (mkName . fst) fields
638
      pat = conP cname (map varP fnames)
639
      flist = map (uncurry saveLuxiField) (zip fnames fields)
640
      finval = if null flist
641
               then [| JSON.showJSON ()    |]
642
               else [| JSON.showJSON $(listE flist) |]
643
  clause [pat] (normalB finval) []
644

    
645
-- * "Objects" functionality
646

    
647
-- | Extract the field's declaration from a Field structure.
648
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
649
fieldTypeInfo field_pfx fd = do
650
  t <- actualFieldType fd
651
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
652
  return (n, NotStrict, t)
653

    
654
-- | Build an object declaration.
655
buildObject :: String -> String -> [Field] -> Q [Dec]
656
buildObject sname field_pfx fields = do
657
  let name = mkName sname
658
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
659
  let decl_d = RecC name fields_d
660
  let declD = DataD [] name [] [decl_d] [''Show, ''Read, ''Eq]
661
  ser_decls <- buildObjectSerialisation sname fields
662
  return $ declD:ser_decls
663

    
664
-- | Generates an object definition: data type and its JSON instance.
665
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
666
buildObjectSerialisation sname fields = do
667
  let name = mkName sname
668
  savedecls <- genSaveObject saveObjectField sname fields
669
  (loadsig, loadfn) <- genLoadObject loadObjectField sname fields
670
  shjson <- objectShowJSON sname
671
  rdjson <- objectReadJSON sname
672
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
673
                 [rdjson, shjson]
674
  return $ savedecls ++ [loadsig, loadfn, instdecl]
675

    
676
-- | The toDict function name for a given type.
677
toDictName :: String -> Name
678
toDictName sname = mkName ("toDict" ++ sname)
679

    
680
-- | Generates the save object functionality.
681
genSaveObject :: (Name -> Field -> Q Exp)
682
              -> String -> [Field] -> Q [Dec]
683
genSaveObject save_fn sname fields = do
684
  let name = mkName sname
685
  fnames <- mapM (newName . fieldVariable) fields
686
  let pat = conP name (map varP fnames)
687
  let tdname = toDictName sname
688
  tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |]
689

    
690
  let felems = map (uncurry save_fn) (zip fnames fields)
691
      flist = listE felems
692
      -- and finally convert all this to a json object
693
      tdlist = [| concat $flist |]
694
      iname = mkName "i"
695
  tclause <- clause [pat] (normalB tdlist) []
696
  cclause <- [| $(varNameE "makeObj") . $(varE tdname) |]
697
  let fname = mkName ("save" ++ sname)
698
  sigt <- [t| $(conT name) -> JSON.JSValue |]
699
  return [SigD tdname tdsigt, FunD tdname [tclause],
700
          SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
701

    
702
-- | Generates the code for saving an object's field, handling the
703
-- various types of fields that we have.
704
saveObjectField :: Name -> Field -> Q Exp
705
saveObjectField fvar field =
706
  case fieldIsOptional field of
707
    OptionalOmitNull -> [| case $(varE fvar) of
708
                             Nothing -> []
709
                             Just v  -> [( $nameE, JSON.showJSON v )]
710
                         |]
711
    OptionalSerializeNull -> [| case $(varE fvar) of
712
                                  Nothing -> [( $nameE, JSON.JSNull )]
713
                                  Just v  -> [( $nameE, JSON.showJSON v )]
714
                              |]
715
    NotOptional ->
716
      case fieldShow field of
717
        Nothing -> [| [( $nameE, JSON.showJSON $fvarE)] |]
718
        Just fn -> [| let (actual, extra) = $fn $fvarE
719
                      in extra ++ [( $nameE, JSON.showJSON actual)]
720
                    |]
721
  where nameE = stringE (fieldName field)
722
        fvarE = varE fvar
723

    
724
-- | Generates the showJSON clause for a given object name.
725
objectShowJSON :: String -> Q Dec
726
objectShowJSON name = do
727
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
728
  return $ FunD (mkName "showJSON") [Clause [] (NormalB body) []]
729

    
730
-- | Generates the load object functionality.
731
genLoadObject :: (Field -> Q (Name, Stmt))
732
              -> String -> [Field] -> Q (Dec, Dec)
733
genLoadObject load_fn sname fields = do
734
  let name = mkName sname
735
      funname = mkName $ "load" ++ sname
736
      arg1 = mkName "v"
737
      objname = mkName "o"
738
      opid = mkName "op_id"
739
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
740
                                 (JSON.readJSON $(varE arg1)) |]
741
  fbinds <- mapM load_fn fields
742
  let (fnames, fstmts) = unzip fbinds
743
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
744
      fstmts' = st1:fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
745
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT name) |]
746
  return $ (SigD funname sigt,
747
            FunD funname [Clause [VarP arg1] (NormalB (DoE fstmts')) []])
748

    
749
-- | Generates code for loading an object's field.
750
loadObjectField :: Field -> Q (Name, Stmt)
751
loadObjectField field = do
752
  let name = fieldVariable field
753
  fvar <- newName name
754
  -- these are used in all patterns below
755
  let objvar = varNameE "o"
756
      objfield = stringE (fieldName field)
757
      loadexp =
758
        if fieldIsOptional field /= NotOptional
759
          -- we treat both optional types the same, since
760
          -- 'maybeFromObj' can deal with both missing and null values
761
          -- appropriately (the same)
762
          then [| $(varNameE "maybeFromObj") $objvar $objfield |]
763
          else case fieldDefault field of
764
                 Just defv ->
765
                   [| $(varNameE "fromObjWithDefault") $objvar
766
                      $objfield $defv |]
767
                 Nothing -> [| $(varNameE "fromObj") $objvar $objfield |]
768
  bexp <- loadFn field loadexp objvar
769

    
770
  return (fvar, BindS (VarP fvar) bexp)
771

    
772
-- | Builds the readJSON instance for a given object name.
773
objectReadJSON :: String -> Q Dec
774
objectReadJSON name = do
775
  let s = mkName "s"
776
  body <- [| case JSON.readJSON $(varE s) of
777
               JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s'
778
               JSON.Error e ->
779
                 JSON.Error $ "Can't parse value for type " ++
780
                       $(stringE name) ++ ": " ++ e
781
           |]
782
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
783

    
784
-- * Inheritable parameter tables implementation
785

    
786
-- | Compute parameter type names.
787
paramTypeNames :: String -> (String, String)
788
paramTypeNames root = ("Filled"  ++ root ++ "Params",
789
                       "Partial" ++ root ++ "Params")
790

    
791
-- | Compute information about the type of a parameter field.
792
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
793
paramFieldTypeInfo field_pfx fd = do
794
  t <- actualFieldType fd
795
  let n = mkName . (++ "P") . (field_pfx ++) .
796
          fieldRecordName $ fd
797
  return (n, NotStrict, AppT (ConT ''Maybe) t)
798

    
799
-- | Build a parameter declaration.
800
--
801
-- This function builds two different data structures: a /filled/ one,
802
-- in which all fields are required, and a /partial/ one, in which all
803
-- fields are optional. Due to the current record syntax issues, the
804
-- fields need to be named differrently for the two structures, so the
805
-- partial ones get a /P/ suffix.
806
buildParam :: String -> String -> [Field] -> Q [Dec]
807
buildParam sname field_pfx fields = do
808
  let (sname_f, sname_p) = paramTypeNames sname
809
      name_f = mkName sname_f
810
      name_p = mkName sname_p
811
  fields_f <- mapM (fieldTypeInfo field_pfx) fields
812
  fields_p <- mapM (paramFieldTypeInfo field_pfx) fields
813
  let decl_f = RecC name_f fields_f
814
      decl_p = RecC name_p fields_p
815
  let declF = DataD [] name_f [] [decl_f] [''Show, ''Read, ''Eq]
816
      declP = DataD [] name_p [] [decl_p] [''Show, ''Read, ''Eq]
817
  ser_decls_f <- buildObjectSerialisation sname_f fields
818
  ser_decls_p <- buildPParamSerialisation sname_p fields
819
  fill_decls <- fillParam sname field_pfx fields
820
  return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls ++
821
           buildParamAllFields sname fields ++
822
           buildDictObjectInst name_f sname_f
823

    
824
-- | Builds a list of all fields of a parameter.
825
buildParamAllFields :: String -> [Field] -> [Dec]
826
buildParamAllFields sname fields =
827
  let vname = mkName ("all" ++ sname ++ "ParamFields")
828
      sig = SigD vname (AppT ListT (ConT ''String))
829
      val = ListE $ map (LitE . StringL . fieldName) fields
830
  in [sig, ValD (VarP vname) (NormalB val) []]
831

    
832
-- | Builds the 'DictObject' instance for a filled parameter.
833
buildDictObjectInst :: Name -> String -> [Dec]
834
buildDictObjectInst name sname =
835
  [InstanceD [] (AppT (ConT ''DictObject) (ConT name))
836
   [ValD (VarP 'toDict) (NormalB (VarE (toDictName sname))) []]]
837

    
838
-- | Generates the serialisation for a partial parameter.
839
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
840
buildPParamSerialisation sname fields = do
841
  let name = mkName sname
842
  savedecls <- genSaveObject savePParamField sname fields
843
  (loadsig, loadfn) <- genLoadObject loadPParamField sname fields
844
  shjson <- objectShowJSON sname
845
  rdjson <- objectReadJSON sname
846
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
847
                 [rdjson, shjson]
848
  return $ savedecls ++ [loadsig, loadfn, instdecl]
849

    
850
-- | Generates code to save an optional parameter field.
851
savePParamField :: Name -> Field -> Q Exp
852
savePParamField fvar field = do
853
  checkNonOptDef field
854
  let actualVal = mkName "v"
855
  normalexpr <- saveObjectField actualVal field
856
  -- we have to construct the block here manually, because we can't
857
  -- splice-in-splice
858
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
859
                                       (NormalB (ConE '[])) []
860
                             , Match (ConP 'Just [VarP actualVal])
861
                                       (NormalB normalexpr) []
862
                             ]
863

    
864
-- | Generates code to load an optional parameter field.
865
loadPParamField :: Field -> Q (Name, Stmt)
866
loadPParamField field = do
867
  checkNonOptDef field
868
  let name = fieldName field
869
  fvar <- newName name
870
  -- these are used in all patterns below
871
  let objvar = varNameE "o"
872
      objfield = stringE name
873
      loadexp = [| $(varNameE "maybeFromObj") $objvar $objfield |]
874
  bexp <- loadFn field loadexp objvar
875
  return (fvar, BindS (VarP fvar) bexp)
876

    
877
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
878
buildFromMaybe :: String -> Q Dec
879
buildFromMaybe fname =
880
  valD (varP (mkName $ "n_" ++ fname))
881
         (normalB [| $(varNameE "fromMaybe")
882
                        $(varNameE $ "f_" ++ fname)
883
                        $(varNameE $ "p_" ++ fname) |]) []
884

    
885
-- | Builds a function that executes the filling of partial parameter
886
-- from a full copy (similar to Python's fillDict).
887
fillParam :: String -> String -> [Field] -> Q [Dec]
888
fillParam sname field_pfx fields = do
889
  let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields
890
      (sname_f, sname_p) = paramTypeNames sname
891
      oname_f = "fobj"
892
      oname_p = "pobj"
893
      name_f = mkName sname_f
894
      name_p = mkName sname_p
895
      fun_name = mkName $ "fill" ++ sname ++ "Params"
896
      le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames))
897
                (NormalB . VarE . mkName $ oname_f) []
898
      le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames))
899
                (NormalB . VarE . mkName $ oname_p) []
900
      obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f)
901
                $ map (mkName . ("n_" ++)) fnames
902
  le_new <- mapM buildFromMaybe fnames
903
  funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |]
904
  let sig = SigD fun_name funt
905
      fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)]
906
                (NormalB $ LetE (le_full:le_part:le_new) obj_new) []
907
      fun = FunD fun_name [fclause]
908
  return [sig, fun]
909

    
910
-- * Template code for exceptions
911

    
912
-- | Exception simple error message field.
913
excErrMsg :: (String, Q Type)
914
excErrMsg = ("errMsg", [t| String |])
915

    
916
-- | Builds an exception type definition.
917
genException :: String                  -- ^ Name of new type
918
             -> SimpleObject -- ^ Constructor name and parameters
919
             -> Q [Dec]
920
genException name cons = do
921
  let tname = mkName name
922
  declD <- buildSimpleCons tname cons
923
  (savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $
924
                         uncurry saveExcCons
925
  (loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons
926
  return [declD, loadsig, loadfn, savesig, savefn]
927

    
928
-- | Generates the \"save\" clause for an entire exception constructor.
929
--
930
-- This matches the exception with variables named the same as the
931
-- constructor fields (just so that the spliced in code looks nicer),
932
-- and calls showJSON on it.
933
saveExcCons :: String        -- ^ The constructor name
934
            -> [SimpleField] -- ^ The parameter definitions for this
935
                             -- constructor
936
            -> Q Clause      -- ^ Resulting clause
937
saveExcCons sname fields = do
938
  let cname = mkName sname
939
  fnames <- mapM (newName . fst) fields
940
  let pat = conP cname (map varP fnames)
941
      felems = if null fnames
942
                 then conE '() -- otherwise, empty list has no type
943
                 else listE $ map (\f -> [| JSON.showJSON $(varE f) |]) fnames
944
  let tup = tupE [ litE (stringL sname), felems ]
945
  clause [pat] (normalB [| JSON.showJSON $tup |]) []
946

    
947
-- | Generates load code for a single constructor of an exception.
948
--
949
-- Generates the code (if there's only one argument, we will use a
950
-- list, not a tuple:
951
--
952
-- @
953
-- do
954
--  (x1, x2, ...) <- readJSON args
955
--  return $ Cons x1 x2 ...
956
-- @
957
loadExcConstructor :: Name -> String -> [SimpleField] -> Q Exp
958
loadExcConstructor inname sname fields = do
959
  let name = mkName sname
960
  f_names <- mapM (newName . fst) fields
961
  let read_args = AppE (VarE 'JSON.readJSON) (VarE inname)
962
  let binds = case f_names of
963
                [x] -> BindS (ListP [VarP x])
964
                _   -> BindS (TupP (map VarP f_names))
965
      cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) f_names
966
  return $ DoE [binds read_args, NoBindS (AppE (VarE 'return) cval)]
967

    
968
{-| Generates the loadException function.
969

    
970
This generates a quite complicated function, along the lines of:
971

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