Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ d9f1d93c

History | View | Annotate | Download (46 kB)

1
{-# LANGUAGE ExistentialQuantification, TemplateHaskell #-}
2

    
3
{-| TemplateHaskell helper for Ganeti Haskell code.
4

    
5
As TemplateHaskell require that splices be defined in a separate
6
module, we combine all the TemplateHaskell functionality that HTools
7
needs in this module (except the one for unittests).
8

    
9
-}
10

    
11
{-
12

    
13
Copyright (C) 2011, 2012 Google Inc.
14

    
15
This program is free software; you can redistribute it and/or modify
16
it under the terms of the GNU General Public License as published by
17
the Free Software Foundation; either version 2 of the License, or
18
(at your option) any later version.
19

    
20
This program is distributed in the hope that it will be useful, but
21
WITHOUT ANY WARRANTY; without even the implied warranty of
22
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23
General Public License for more details.
24

    
25
You should have received a copy of the GNU General Public License
26
along with this program; if not, write to the Free Software
27
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28
02110-1301, USA.
29

    
30
-}
31

    
32
module Ganeti.THH ( declareSADT
33
                  , declareIADT
34
                  , makeJSONInstance
35
                  , genOpID
36
                  , genAllConstr
37
                  , genAllOpIDs
38
                  , PyValue(..)
39
                  , PyValueEx(..)
40
                  , OpCodeDescriptor
41
                  , genOpCode
42
                  , genStrOfOp
43
                  , genStrOfKey
44
                  , genLuxiOp
45
                  , Field (..)
46
                  , simpleField
47
                  , withDoc
48
                  , defaultField
49
                  , optionalField
50
                  , optionalNullSerField
51
                  , renameField
52
                  , customField
53
                  , timeStampFields
54
                  , uuidFields
55
                  , serialFields
56
                  , tagsFields
57
                  , TagSet
58
                  , buildObject
59
                  , buildObjectSerialisation
60
                  , buildParam
61
                  , DictObject(..)
62
                  , genException
63
                  , excErrMsg
64
                  ) where
65

    
66
import Control.Monad (liftM)
67
import Data.Char
68
import Data.List
69
import qualified Data.Set as Set
70
import Language.Haskell.TH
71

    
72
import qualified Text.JSON as JSON
73
import Text.JSON.Pretty (pp_value)
74

    
75
import Ganeti.JSON
76

    
77
import Data.Maybe
78
import Data.Functor ((<$>))
79

    
80
-- * Exported types
81

    
82
-- | Class of objects that can be converted to 'JSObject'
83
-- lists-format.
84
class DictObject a where
85
  toDict :: a -> [(String, JSON.JSValue)]
86

    
87
-- | Optional field information.
88
data OptionalType
89
  = NotOptional           -- ^ Field is not optional
90
  | OptionalOmitNull      -- ^ Field is optional, null is not serialised
91
  | OptionalSerializeNull -- ^ Field is optional, null is serialised
92
  deriving (Show, Eq)
93

    
94
-- | Serialised field data type.
95
data Field = Field { fieldName        :: String
96
                   , fieldType        :: Q Type
97
                   , fieldRead        :: Maybe (Q Exp)
98
                   , fieldShow        :: Maybe (Q Exp)
99
                   , fieldExtraKeys   :: [String]
100
                   , fieldDefault     :: Maybe (Q Exp)
101
                   , fieldConstr      :: Maybe String
102
                   , fieldIsOptional  :: OptionalType
103
                   , fieldDoc         :: String
104
                   }
105

    
106
-- | Generates a simple field.
107
simpleField :: String -> Q Type -> Field
108
simpleField fname ftype =
109
  Field { fieldName        = fname
110
        , fieldType        = ftype
111
        , fieldRead        = Nothing
112
        , fieldShow        = Nothing
113
        , fieldExtraKeys   = []
114
        , fieldDefault     = Nothing
115
        , fieldConstr      = Nothing
116
        , fieldIsOptional  = NotOptional
117
        , fieldDoc         = ""
118
        }
119

    
120
withDoc :: String -> Field -> Field
121
withDoc doc field =
122
  field { fieldDoc = doc }
123

    
124
-- | Sets the renamed constructor field.
125
renameField :: String -> Field -> Field
126
renameField constrName field = field { fieldConstr = Just constrName }
127

    
128
-- | Sets the default value on a field (makes it optional with a
129
-- default value).
130
defaultField :: Q Exp -> Field -> Field
131
defaultField defval field = field { fieldDefault = Just defval }
132

    
133
-- | Marks a field optional (turning its base type into a Maybe).
134
optionalField :: Field -> Field
135
optionalField field = field { fieldIsOptional = OptionalOmitNull }
136

    
137
-- | Marks a field optional (turning its base type into a Maybe), but
138
-- with 'Nothing' serialised explicitly as /null/.
139
optionalNullSerField :: Field -> Field
140
optionalNullSerField field = field { fieldIsOptional = OptionalSerializeNull }
141

    
142
-- | Sets custom functions on a field.
143
customField :: Name      -- ^ The name of the read function
144
            -> Name      -- ^ The name of the show function
145
            -> [String]  -- ^ The name of extra field keys
146
            -> Field     -- ^ The original field
147
            -> Field     -- ^ Updated field
148
customField readfn showfn extra field =
149
  field { fieldRead = Just (varE readfn), fieldShow = Just (varE showfn)
150
        , fieldExtraKeys = extra }
151

    
152
-- | Computes the record name for a given field, based on either the
153
-- string value in the JSON serialisation or the custom named if any
154
-- exists.
155
fieldRecordName :: Field -> String
156
fieldRecordName (Field { fieldName = name, fieldConstr = alias }) =
157
  fromMaybe (camelCase name) alias
158

    
159
-- | Computes the preferred variable name to use for the value of this
160
-- field. If the field has a specific constructor name, then we use a
161
-- first-letter-lowercased version of that; otherwise, we simply use
162
-- the field name. See also 'fieldRecordName'.
163
fieldVariable :: Field -> String
164
fieldVariable f =
165
  case (fieldConstr f) of
166
    Just name -> ensureLower name
167
    _ -> map (\c -> if c == '-' then '_' else c) $ fieldName f
168

    
169
-- | Compute the actual field type (taking into account possible
170
-- optional status).
171
actualFieldType :: Field -> Q Type
172
actualFieldType f | fieldIsOptional f /= NotOptional = [t| Maybe $t |]
173
                  | otherwise = t
174
                  where t = fieldType f
175

    
176
-- | Checks that a given field is not optional (for object types or
177
-- fields which should not allow this case).
178
checkNonOptDef :: (Monad m) => Field -> m ()
179
checkNonOptDef (Field { fieldIsOptional = OptionalOmitNull
180
                      , fieldName = name }) =
181
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
182
checkNonOptDef (Field { fieldIsOptional = OptionalSerializeNull
183
                      , fieldName = name }) =
184
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
185
checkNonOptDef (Field { fieldDefault = (Just _), fieldName = name }) =
186
  fail $ "Default field " ++ name ++ " used in parameter declaration"
187
checkNonOptDef _ = return ()
188

    
189
-- | Produces the expression that will de-serialise a given
190
-- field. Since some custom parsing functions might need to use the
191
-- entire object, we do take and pass the object to any custom read
192
-- functions.
193
loadFn :: Field   -- ^ The field definition
194
       -> Q Exp   -- ^ The value of the field as existing in the JSON message
195
       -> Q Exp   -- ^ The entire object in JSON object format
196
       -> Q Exp   -- ^ Resulting expression
197
loadFn (Field { fieldRead = Just readfn }) expr o = [| $expr >>= $readfn $o |]
198
loadFn _ expr _ = expr
199

    
200
-- * Common field declarations
201

    
202
-- | Timestamp fields description.
203
timeStampFields :: [Field]
204
timeStampFields =
205
    [ defaultField [| 0::Double |] $ simpleField "ctime" [t| Double |]
206
    , defaultField [| 0::Double |] $ simpleField "mtime" [t| Double |]
207
    ]
208

    
209
-- | Serial number fields description.
210
serialFields :: [Field]
211
serialFields =
212
    [ renameField  "Serial" $ simpleField "serial_no" [t| Int |] ]
213

    
214
-- | UUID fields description.
215
uuidFields :: [Field]
216
uuidFields = [ simpleField "uuid" [t| String |] ]
217

    
218
-- | Tag set type alias.
219
type TagSet = Set.Set String
220

    
221
-- | Tag field description.
222
tagsFields :: [Field]
223
tagsFields = [ defaultField [| Set.empty |] $
224
               simpleField "tags" [t| TagSet |] ]
225

    
226
-- * Internal types
227

    
228
-- | A simple field, in constrast to the customisable 'Field' type.
229
type SimpleField = (String, Q Type)
230

    
231
-- | A definition for a single constructor for a simple object.
232
type SimpleConstructor = (String, [SimpleField])
233

    
234
-- | A definition for ADTs with simple fields.
235
type SimpleObject = [SimpleConstructor]
236

    
237
-- | A type alias for an opcode constructor of a regular object.
238
type OpCodeConstructor = (String, Q Type, String, [Field], String)
239

    
240
-- | A type alias for a Luxi constructor of a regular object.
241
type LuxiConstructor = (String, [Field])
242

    
243
-- * Helper functions
244

    
245
-- | Ensure first letter is lowercase.
246
--
247
-- Used to convert type name to function prefix, e.g. in @data Aa ->
248
-- aaToRaw@.
249
ensureLower :: String -> String
250
ensureLower [] = []
251
ensureLower (x:xs) = toLower x:xs
252

    
253
-- | Ensure first letter is uppercase.
254
--
255
-- Used to convert constructor name to component
256
ensureUpper :: String -> String
257
ensureUpper [] = []
258
ensureUpper (x:xs) = toUpper x:xs
259

    
260
-- | Helper for quoted expressions.
261
varNameE :: String -> Q Exp
262
varNameE = varE . mkName
263

    
264
-- | showJSON as an expression, for reuse.
265
showJSONE :: Q Exp
266
showJSONE = varE 'JSON.showJSON
267

    
268
-- | makeObj as an expression, for reuse.
269
makeObjE :: Q Exp
270
makeObjE = varE 'JSON.makeObj
271

    
272
-- | fromObj (Ganeti specific) as an expression, for reuse.
273
fromObjE :: Q Exp
274
fromObjE = varE 'fromObj
275

    
276
-- | ToRaw function name.
277
toRawName :: String -> Name
278
toRawName = mkName . (++ "ToRaw") . ensureLower
279

    
280
-- | FromRaw function name.
281
fromRawName :: String -> Name
282
fromRawName = mkName . (++ "FromRaw") . ensureLower
283

    
284
-- | Converts a name to it's varE\/litE representations.
285
reprE :: Either String Name -> Q Exp
286
reprE = either stringE varE
287

    
288
-- | Smarter function application.
289
--
290
-- This does simply f x, except that if is 'id', it will skip it, in
291
-- order to generate more readable code when using -ddump-splices.
292
appFn :: Exp -> Exp -> Exp
293
appFn f x | f == VarE 'id = x
294
          | otherwise = AppE f x
295

    
296
-- | Builds a field for a normal constructor.
297
buildConsField :: Q Type -> StrictTypeQ
298
buildConsField ftype = do
299
  ftype' <- ftype
300
  return (NotStrict, ftype')
301

    
302
-- | Builds a constructor based on a simple definition (not field-based).
303
buildSimpleCons :: Name -> SimpleObject -> Q Dec
304
buildSimpleCons tname cons = do
305
  decl_d <- mapM (\(cname, fields) -> do
306
                    fields' <- mapM (buildConsField . snd) fields
307
                    return $ NormalC (mkName cname) fields') cons
308
  return $ DataD [] tname [] decl_d [''Show, ''Eq]
309

    
310
-- | Generate the save function for a given type.
311
genSaveSimpleObj :: Name                            -- ^ Object type
312
                 -> String                          -- ^ Function name
313
                 -> SimpleObject                    -- ^ Object definition
314
                 -> (SimpleConstructor -> Q Clause) -- ^ Constructor save fn
315
                 -> Q (Dec, Dec)
316
genSaveSimpleObj tname sname opdefs fn = do
317
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
318
      fname = mkName sname
319
  cclauses <- mapM fn opdefs
320
  return $ (SigD fname sigt, FunD fname cclauses)
321

    
322
-- * Template code for simple raw type-equivalent ADTs
323

    
324
-- | Generates a data type declaration.
325
--
326
-- The type will have a fixed list of instances.
327
strADTDecl :: Name -> [String] -> Dec
328
strADTDecl name constructors =
329
  DataD [] name []
330
          (map (flip NormalC [] . mkName) constructors)
331
          [''Show, ''Eq, ''Enum, ''Bounded, ''Ord]
332

    
333
-- | Generates a toRaw function.
334
--
335
-- This generates a simple function of the form:
336
--
337
-- @
338
-- nameToRaw :: Name -> /traw/
339
-- nameToRaw Cons1 = var1
340
-- nameToRaw Cons2 = \"value2\"
341
-- @
342
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
343
genToRaw traw fname tname constructors = do
344
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw)
345
  -- the body clauses, matching on the constructor and returning the
346
  -- raw value
347
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
348
                             (normalB (reprE v)) []) constructors
349
  return [SigD fname sigt, FunD fname clauses]
350

    
351
-- | Generates a fromRaw function.
352
--
353
-- The function generated is monadic and can fail parsing the
354
-- raw value. It is of the form:
355
--
356
-- @
357
-- nameFromRaw :: (Monad m) => /traw/ -> m Name
358
-- nameFromRaw s | s == var1       = Cons1
359
--               | s == \"value2\" = Cons2
360
--               | otherwise = fail /.../
361
-- @
362
genFromRaw :: Name -> Name -> Name -> [(String, Name)] -> Q [Dec]
363
genFromRaw traw fname tname constructors = do
364
  -- signature of form (Monad m) => String -> m $name
365
  sigt <- [t| (Monad m) => $(conT traw) -> m $(conT tname) |]
366
  -- clauses for a guarded pattern
367
  let varp = mkName "s"
368
      varpe = varE varp
369
  clauses <- mapM (\(c, v) -> do
370
                     -- the clause match condition
371
                     g <- normalG [| $varpe == $(varE v) |]
372
                     -- the clause result
373
                     r <- [| return $(conE (mkName c)) |]
374
                     return (g, r)) constructors
375
  -- the otherwise clause (fallback)
376
  oth_clause <- do
377
    g <- normalG [| otherwise |]
378
    r <- [|fail ("Invalid string value for type " ++
379
                 $(litE (stringL (nameBase tname))) ++ ": " ++ show $varpe) |]
380
    return (g, r)
381
  let fun = FunD fname [Clause [VarP varp]
382
                        (GuardedB (clauses++[oth_clause])) []]
383
  return [SigD fname sigt, fun]
384

    
385
-- | Generates a data type from a given raw format.
386
--
387
-- The format is expected to multiline. The first line contains the
388
-- type name, and the rest of the lines must contain two words: the
389
-- constructor name and then the string representation of the
390
-- respective constructor.
391
--
392
-- The function will generate the data type declaration, and then two
393
-- functions:
394
--
395
-- * /name/ToRaw, which converts the type to a raw type
396
--
397
-- * /name/FromRaw, which (monadically) converts from a raw type to the type
398
--
399
-- Note that this is basically just a custom show\/read instance,
400
-- nothing else.
401
declareADT :: Name -> String -> [(String, Name)] -> Q [Dec]
402
declareADT traw sname cons = do
403
  let name = mkName sname
404
      ddecl = strADTDecl name (map fst cons)
405
      -- process cons in the format expected by genToRaw
406
      cons' = map (\(a, b) -> (a, Right b)) cons
407
  toraw <- genToRaw traw (toRawName sname) name cons'
408
  fromraw <- genFromRaw traw (fromRawName sname) name cons
409
  return $ ddecl:toraw ++ fromraw
410

    
411
declareIADT :: String -> [(String, Name)] -> Q [Dec]
412
declareIADT = declareADT ''Int
413

    
414
declareSADT :: String -> [(String, Name)] -> Q [Dec]
415
declareSADT = declareADT ''String
416

    
417
-- | Creates the showJSON member of a JSON instance declaration.
418
--
419
-- This will create what is the equivalent of:
420
--
421
-- @
422
-- showJSON = showJSON . /name/ToRaw
423
-- @
424
--
425
-- in an instance JSON /name/ declaration
426
genShowJSON :: String -> Q Dec
427
genShowJSON name = do
428
  body <- [| JSON.showJSON . $(varE (toRawName name)) |]
429
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
430

    
431
-- | Creates the readJSON member of a JSON instance declaration.
432
--
433
-- This will create what is the equivalent of:
434
--
435
-- @
436
-- readJSON s = case readJSON s of
437
--                Ok s' -> /name/FromRaw s'
438
--                Error e -> Error /description/
439
-- @
440
--
441
-- in an instance JSON /name/ declaration
442
genReadJSON :: String -> Q Dec
443
genReadJSON name = do
444
  let s = mkName "s"
445
  body <- [| case JSON.readJSON $(varE s) of
446
               JSON.Ok s' -> $(varE (fromRawName name)) s'
447
               JSON.Error e ->
448
                   JSON.Error $ "Can't parse raw value for type " ++
449
                           $(stringE name) ++ ": " ++ e ++ " from " ++
450
                           show $(varE s)
451
           |]
452
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
453

    
454
-- | Generates a JSON instance for a given type.
455
--
456
-- This assumes that the /name/ToRaw and /name/FromRaw functions
457
-- have been defined as by the 'declareSADT' function.
458
makeJSONInstance :: Name -> Q [Dec]
459
makeJSONInstance name = do
460
  let base = nameBase name
461
  showJ <- genShowJSON base
462
  readJ <- genReadJSON base
463
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]]
464

    
465
-- * Template code for opcodes
466

    
467
-- | Transforms a CamelCase string into an_underscore_based_one.
468
deCamelCase :: String -> String
469
deCamelCase =
470
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
471

    
472
-- | Transform an underscore_name into a CamelCase one.
473
camelCase :: String -> String
474
camelCase = concatMap (ensureUpper . drop 1) .
475
            groupBy (\_ b -> b /= '_' && b /= '-') . ('_':)
476

    
477
-- | Computes the name of a given constructor.
478
constructorName :: Con -> Q Name
479
constructorName (NormalC name _) = return name
480
constructorName (RecC name _)    = return name
481
constructorName x                = fail $ "Unhandled constructor " ++ show x
482

    
483
-- | Extract all constructor names from a given type.
484
reifyConsNames :: Name -> Q [String]
485
reifyConsNames name = do
486
  reify_result <- reify name
487
  case reify_result of
488
    TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons
489
    o -> fail $ "Unhandled name passed to reifyConsNames, expected\
490
                \ type constructor but got '" ++ show o ++ "'"
491

    
492
-- | Builds the generic constructor-to-string function.
493
--
494
-- This generates a simple function of the following form:
495
--
496
-- @
497
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne")
498
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo")
499
-- @
500
--
501
-- This builds a custom list of name\/string pairs and then uses
502
-- 'genToRaw' to actually generate the function.
503
genConstrToStr :: (String -> String) -> Name -> String -> Q [Dec]
504
genConstrToStr trans_fun name fname = do
505
  cnames <- reifyConsNames name
506
  let svalues = map (Left . trans_fun) cnames
507
  genToRaw ''String (mkName fname) name $ zip cnames svalues
508

    
509
-- | Constructor-to-string for OpCode.
510
genOpID :: Name -> String -> Q [Dec]
511
genOpID = genConstrToStr deCamelCase
512

    
513
-- | Builds a list with all defined constructor names for a type.
514
--
515
-- @
516
-- vstr :: String
517
-- vstr = [...]
518
-- @
519
--
520
-- Where the actual values of the string are the constructor names
521
-- mapped via @trans_fun@.
522
genAllConstr :: (String -> String) -> Name -> String -> Q [Dec]
523
genAllConstr trans_fun name vstr = do
524
  cnames <- reifyConsNames name
525
  let svalues = sort $ map trans_fun cnames
526
      vname = mkName vstr
527
      sig = SigD vname (AppT ListT (ConT ''String))
528
      body = NormalB (ListE (map (LitE . StringL) svalues))
529
  return $ [sig, ValD (VarP vname) body []]
530

    
531
-- | Generates a list of all defined opcode IDs.
532
genAllOpIDs :: Name -> String -> Q [Dec]
533
genAllOpIDs = genAllConstr deCamelCase
534

    
535
-- | OpCode parameter (field) type.
536
type OpParam = (String, Q Type, Q Exp)
537

    
538
-- * Python code generation
539

    
540
-- | Converts Haskell values into Python values
541
--
542
-- This is necessary for the default values of opcode parameters and
543
-- return values.  For example, if a default value or return type is a
544
-- Data.Map, then it must be shown as a Python dictioanry.
545
class Show a => PyValue a where
546
  showValue :: a -> String
547
  showValue = show
548

    
549
-- | Encapsulates Python default values
550
data PyValueEx = forall a. PyValue a => PyValueEx a
551

    
552
-- | Transfers opcode data between the opcode description (through
553
-- @genOpCode@) and the Python code generation functions.
554
type OpCodeDescriptor =
555
  (String, String, String, [String],
556
   [String], [Maybe PyValueEx], [String], String)
557

    
558
-- | Strips out the module name
559
--
560
-- @
561
-- pyBaseName "Data.Map" = "Map"
562
-- @
563
pyBaseName :: String -> String
564
pyBaseName str =
565
  case span (/= '.') str of
566
    (x, []) -> x
567
    (_, _:x) -> pyBaseName x
568

    
569
-- | Converts a Haskell type name into a Python type name.
570
--
571
-- @
572
-- pyTypename "Bool" = "ht.TBool"
573
-- @
574
pyTypeName :: Show a => a -> String
575
pyTypeName name =
576
  "ht.T" ++ (case pyBaseName (show name) of
577
                "()" -> "None"
578
                "Map" -> "DictOf"
579
                "Set" -> "SetOf"
580
                "Either" -> "Or"
581
                "GenericContainer" -> "DictOf"
582
                "JSValue" -> "Any"
583
                "JSObject" -> "Object"
584
                str -> str)
585

    
586
-- | Converts a Haskell type into a Python type.
587
--
588
-- @
589
-- pyType [Int] = "ht.TListOf(ht.TInt)"
590
-- @
591
pyType :: Type -> Q String
592
pyType (AppT typ1 typ2) =
593
  do t <- pyCall typ1 typ2
594
     return $ t ++ ")"
595

    
596
pyType (ConT name) = return (pyTypeName name)
597
pyType ListT = return "ht.TListOf"
598
pyType (TupleT _) = return "ht.TTupleOf"
599
pyType typ = error $ "unhandled case for type " ++ show typ
600
        
601
-- | Converts a Haskell type application into a Python type.
602
--
603
-- @
604
-- Maybe Int = "ht.TMaybe(ht.TInt)"
605
-- @
606
pyCall :: Type -> Type -> Q String
607
pyCall (AppT typ1 typ2) arg =
608
  do t <- pyCall typ1 typ2
609
     targ <- pyType arg
610
     return $ t ++ ", " ++ targ
611

    
612
pyCall typ1 typ2 =
613
  do t1 <- pyType typ1
614
     t2 <- pyType typ2
615
     return $ t1 ++ "(" ++ t2
616

    
617
-- | @pyType opt typ@ converts Haskell type @typ@ into a Python type,
618
-- where @opt@ determines if the converted type is optional (i.e.,
619
-- Maybe).
620
--
621
-- @
622
-- pyType False [Int] = "ht.TListOf(ht.TInt)" (mandatory)
623
-- pyType True [Int] = "ht.TMaybe(ht.TListOf(ht.TInt))" (optional)
624
-- @
625
pyOptionalType :: Bool -> Type -> Q String
626
pyOptionalType opt typ
627
  | opt = do t <- pyType typ
628
             return $ "ht.TMaybe(" ++ t ++ ")"
629
  | otherwise = pyType typ
630

    
631
-- | Optionally encapsulates default values in @PyValueEx@.
632
--
633
-- @maybeApp exp typ@ returns a quoted expression that encapsulates
634
-- the default value @exp@ of an opcode parameter cast to @typ@ in a
635
-- @PyValueEx@, if @exp@ is @Just@.  Otherwise, it returns a quoted
636
-- expression with @Nothing@.
637
maybeApp :: Maybe (Q Exp) -> Q Type -> Q Exp
638
maybeApp Nothing _ =
639
  [| Nothing |]
640

    
641
maybeApp (Just expr) typ =
642
  [| Just ($(conE (mkName "PyValueEx")) ($expr :: $typ)) |]
643

    
644

    
645
-- | Generates a Python type according to whether the field is
646
-- optional
647
genPyType :: OptionalType -> Q Type -> Q ExpQ
648
genPyType opt typ =
649
  do t <- typ
650
     stringE <$> pyOptionalType (opt /= NotOptional) t
651

    
652
-- | Generates Python types from opcode parameters.
653
genPyTypes :: [Field] -> Q ExpQ
654
genPyTypes fs =
655
  listE <$> mapM (\f -> genPyType (fieldIsOptional f) (fieldType f)) fs
656

    
657
-- | Generates Python default values from opcode parameters.
658
genPyDefaults :: [Field] -> ExpQ
659
genPyDefaults fs =
660
  listE $ map (\f -> maybeApp (fieldDefault f) (fieldType f)) fs
661

    
662
-- | Generates a Haskell function call to "showPyClass" with the
663
-- necessary information on how to build the Python class string.
664
pyClass :: OpCodeConstructor -> ExpQ
665
pyClass (consName, consType, consDoc, consFields, consDscField) =
666
  do let pyClassVar = varNameE "showPyClass"
667
         consName' = stringE consName
668
     consType' <- genPyType NotOptional consType
669
     let consDoc' = stringE consDoc
670
         consFieldNames = listE $ map (stringE . fieldName) consFields
671
         consFieldDocs = listE $ map (stringE . fieldDoc) consFields
672
     consFieldTypes <- genPyTypes consFields
673
     let consFieldDefaults = genPyDefaults consFields
674
     [| ($consName',
675
         $consType',
676
         $consDoc',
677
         $consFieldNames,
678
         $consFieldTypes,
679
         $consFieldDefaults,
680
         $consFieldDocs,
681
         consDscField) |]
682

    
683
-- | Generates a function called "pyClasses" that holds the list of
684
-- all the opcode descriptors necessary for generating the Python
685
-- opcodes.
686
pyClasses :: [OpCodeConstructor] -> Q [Dec]
687
pyClasses cons =
688
  do let name = mkName "pyClasses"
689
         sig = SigD name (AppT ListT (ConT ''OpCodeDescriptor))
690
     fn <- FunD name <$> (:[]) <$> declClause cons
691
     return [sig, fn]
692
  where declClause c =
693
          clause [] (normalB (ListE <$> mapM pyClass c)) []
694

    
695
-- | Converts from an opcode constructor to a Luxi constructor.
696
opcodeConsToLuxiCons :: (a, b, c, d, e) -> (a, d)
697
opcodeConsToLuxiCons (x, _, _, y, _) = (x, y)
698

    
699
-- | Generates the OpCode data type.
700
--
701
-- This takes an opcode logical definition, and builds both the
702
-- datatype and the JSON serialisation out of it. We can't use a
703
-- generic serialisation since we need to be compatible with Ganeti's
704
-- own, so we have a few quirks to work around.
705
genOpCode :: String              -- ^ Type name to use
706
          -> [OpCodeConstructor] -- ^ Constructor name and parameters
707
          -> Q [Dec]
708
genOpCode name cons = do
709
  let tname = mkName name
710
  decl_d <- mapM (\(cname, _, _, fields, _) -> do
711
                    -- we only need the type of the field, without Q
712
                    fields' <- mapM (fieldTypeInfo "op") fields
713
                    return $ RecC (mkName cname) fields')
714
            cons
715
  let declD = DataD [] tname [] decl_d [''Show, ''Eq]
716
  let (allfsig, allffn) = genAllOpFields "allOpFields" cons
717
  save_decs <- genSaveOpCode tname "saveOpCode" "toDictOpCode"
718
               (map opcodeConsToLuxiCons cons) saveConstructor True
719
  (loadsig, loadfn) <- genLoadOpCode cons
720
  pyDecls <- pyClasses cons
721
  return $ [declD, allfsig, allffn, loadsig, loadfn] ++ save_decs ++ pyDecls
722

    
723
-- | Generates the function pattern returning the list of fields for a
724
-- given constructor.
725
genOpConsFields :: OpCodeConstructor -> Clause
726
genOpConsFields (cname, _, _, fields, _) =
727
  let op_id = deCamelCase cname
728
      fvals = map (LitE . StringL) . sort . nub $
729
              concatMap (\f -> fieldName f:fieldExtraKeys f) fields
730
  in Clause [LitP (StringL op_id)] (NormalB $ ListE fvals) []
731

    
732
-- | Generates a list of all fields of an opcode constructor.
733
genAllOpFields  :: String              -- ^ Function name
734
                -> [OpCodeConstructor] -- ^ Object definition
735
                -> (Dec, Dec)
736
genAllOpFields sname opdefs =
737
  let cclauses = map genOpConsFields opdefs
738
      other = Clause [WildP] (NormalB (ListE [])) []
739
      fname = mkName sname
740
      sigt = AppT  (AppT ArrowT (ConT ''String)) (AppT ListT (ConT ''String))
741
  in (SigD fname sigt, FunD fname (cclauses++[other]))
742

    
743
-- | Generates the \"save\" clause for an entire opcode constructor.
744
--
745
-- This matches the opcode with variables named the same as the
746
-- constructor fields (just so that the spliced in code looks nicer),
747
-- and passes those name plus the parameter definition to 'saveObjectField'.
748
saveConstructor :: LuxiConstructor -- ^ The constructor
749
                -> Q Clause        -- ^ Resulting clause
750
saveConstructor (sname, fields) = do
751
  let cname = mkName sname
752
  fnames <- mapM (newName . fieldVariable) fields
753
  let pat = conP cname (map varP fnames)
754
  let felems = map (uncurry saveObjectField) (zip fnames fields)
755
      -- now build the OP_ID serialisation
756
      opid = [| [( $(stringE "OP_ID"),
757
                   JSON.showJSON $(stringE . deCamelCase $ sname) )] |]
758
      flist = listE (opid:felems)
759
      -- and finally convert all this to a json object
760
      flist' = [| concat $flist |]
761
  clause [pat] (normalB flist') []
762

    
763
-- | Generates the main save opcode function.
764
--
765
-- This builds a per-constructor match clause that contains the
766
-- respective constructor-serialisation code.
767
genSaveOpCode :: Name                          -- ^ Object ype
768
              -> String                        -- ^ To 'JSValue' function name
769
              -> String                        -- ^ To 'JSObject' function name
770
              -> [LuxiConstructor]             -- ^ Object definition
771
              -> (LuxiConstructor -> Q Clause) -- ^ Constructor save fn
772
              -> Bool                          -- ^ Whether to generate
773
                                               -- obj or just a
774
                                               -- list\/tuple of values
775
              -> Q [Dec]
776
genSaveOpCode tname jvalstr tdstr opdefs fn gen_object = do
777
  tdclauses <- mapM fn opdefs
778
  let typecon = ConT tname
779
      jvalname = mkName jvalstr
780
      jvalsig = AppT  (AppT ArrowT typecon) (ConT ''JSON.JSValue)
781
      tdname = mkName tdstr
782
  tdsig <- [t| $(return typecon) -> [(String, JSON.JSValue)] |]
783
  jvalclause <- if gen_object
784
                  then [| $makeObjE . $(varE tdname) |]
785
                  else [| JSON.showJSON . map snd . $(varE tdname) |]
786
  return [ SigD tdname tdsig
787
         , FunD tdname tdclauses
788
         , SigD jvalname jvalsig
789
         , ValD (VarP jvalname) (NormalB jvalclause) []]
790

    
791
-- | Generates load code for a single constructor of the opcode data type.
792
loadConstructor :: OpCodeConstructor -> Q Exp
793
loadConstructor (sname, _, _, fields, _) = do
794
  let name = mkName sname
795
  fbinds <- mapM loadObjectField fields
796
  let (fnames, fstmts) = unzip fbinds
797
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
798
      fstmts' = fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
799
  return $ DoE fstmts'
800

    
801
-- | Generates the loadOpCode function.
802
genLoadOpCode :: [OpCodeConstructor] -> Q (Dec, Dec)
803
genLoadOpCode opdefs = do
804
  let fname = mkName "loadOpCode"
805
      arg1 = mkName "v"
806
      objname = mkName "o"
807
      opid = mkName "op_id"
808
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
809
                                 (JSON.readJSON $(varE arg1)) |]
810
  st2 <- bindS (varP opid) [| $fromObjE $(varE objname) $(stringE "OP_ID") |]
811
  -- the match results (per-constructor blocks)
812
  mexps <- mapM loadConstructor opdefs
813
  fails <- [| fail $ "Unknown opcode " ++ $(varE opid) |]
814
  let mpats = map (\(me, (consName, _, _, _, _)) ->
815
                       let mp = LitP . StringL . deCamelCase $ consName
816
                       in Match mp (NormalB me) []
817
                  ) $ zip mexps opdefs
818
      defmatch = Match WildP (NormalB fails) []
819
      cst = NoBindS $ CaseE (VarE opid) $ mpats++[defmatch]
820
      body = DoE [st1, st2, cst]
821
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT (mkName "OpCode")) |]
822
  return $ (SigD fname sigt, FunD fname [Clause [VarP arg1] (NormalB body) []])
823

    
824
-- * Template code for luxi
825

    
826
-- | Constructor-to-string for LuxiOp.
827
genStrOfOp :: Name -> String -> Q [Dec]
828
genStrOfOp = genConstrToStr id
829

    
830
-- | Constructor-to-string for MsgKeys.
831
genStrOfKey :: Name -> String -> Q [Dec]
832
genStrOfKey = genConstrToStr ensureLower
833

    
834
-- | Generates the LuxiOp data type.
835
--
836
-- This takes a Luxi operation definition and builds both the
837
-- datatype and the function transforming the arguments to JSON.
838
-- We can't use anything less generic, because the way different
839
-- operations are serialized differs on both parameter- and top-level.
840
--
841
-- There are two things to be defined for each parameter:
842
--
843
-- * name
844
--
845
-- * type
846
--
847
genLuxiOp :: String -> [LuxiConstructor] -> Q [Dec]
848
genLuxiOp name cons = do
849
  let tname = mkName name
850
  decl_d <- mapM (\(cname, fields) -> do
851
                    -- we only need the type of the field, without Q
852
                    fields' <- mapM actualFieldType fields
853
                    let fields'' = zip (repeat NotStrict) fields'
854
                    return $ NormalC (mkName cname) fields'')
855
            cons
856
  let declD = DataD [] (mkName name) [] decl_d [''Show, ''Eq]
857
  save_decs <- genSaveOpCode tname "opToArgs" "opToDict"
858
               cons saveLuxiConstructor False
859
  req_defs <- declareSADT "LuxiReq" .
860
              map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $
861
                  cons
862
  return $ declD:save_decs ++ req_defs
863

    
864
-- | Generates the \"save\" clause for entire LuxiOp constructor.
865
saveLuxiConstructor :: LuxiConstructor -> Q Clause
866
saveLuxiConstructor (sname, fields) = do
867
  let cname = mkName sname
868
  fnames <- mapM (newName . fieldVariable) fields
869
  let pat = conP cname (map varP fnames)
870
  let felems = map (uncurry saveObjectField) (zip fnames fields)
871
      flist = [| concat $(listE felems) |]
872
  clause [pat] (normalB flist) []
873

    
874
-- * "Objects" functionality
875

    
876
-- | Extract the field's declaration from a Field structure.
877
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
878
fieldTypeInfo field_pfx fd = do
879
  t <- actualFieldType fd
880
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
881
  return (n, NotStrict, t)
882

    
883
-- | Build an object declaration.
884
buildObject :: String -> String -> [Field] -> Q [Dec]
885
buildObject sname field_pfx fields = do
886
  let name = mkName sname
887
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
888
  let decl_d = RecC name fields_d
889
  let declD = DataD [] name [] [decl_d] [''Show, ''Eq]
890
  ser_decls <- buildObjectSerialisation sname fields
891
  return $ declD:ser_decls
892

    
893
-- | Generates an object definition: data type and its JSON instance.
894
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
895
buildObjectSerialisation sname fields = do
896
  let name = mkName sname
897
  savedecls <- genSaveObject saveObjectField sname fields
898
  (loadsig, loadfn) <- genLoadObject loadObjectField sname fields
899
  shjson <- objectShowJSON sname
900
  rdjson <- objectReadJSON sname
901
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
902
                 [rdjson, shjson]
903
  return $ savedecls ++ [loadsig, loadfn, instdecl]
904

    
905
-- | The toDict function name for a given type.
906
toDictName :: String -> Name
907
toDictName sname = mkName ("toDict" ++ sname)
908

    
909
-- | Generates the save object functionality.
910
genSaveObject :: (Name -> Field -> Q Exp)
911
              -> String -> [Field] -> Q [Dec]
912
genSaveObject save_fn sname fields = do
913
  let name = mkName sname
914
  fnames <- mapM (newName . fieldVariable) fields
915
  let pat = conP name (map varP fnames)
916
  let tdname = toDictName sname
917
  tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |]
918

    
919
  let felems = map (uncurry save_fn) (zip fnames fields)
920
      flist = listE felems
921
      -- and finally convert all this to a json object
922
      tdlist = [| concat $flist |]
923
      iname = mkName "i"
924
  tclause <- clause [pat] (normalB tdlist) []
925
  cclause <- [| $makeObjE . $(varE tdname) |]
926
  let fname = mkName ("save" ++ sname)
927
  sigt <- [t| $(conT name) -> JSON.JSValue |]
928
  return [SigD tdname tdsigt, FunD tdname [tclause],
929
          SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
930

    
931
-- | Generates the code for saving an object's field, handling the
932
-- various types of fields that we have.
933
saveObjectField :: Name -> Field -> Q Exp
934
saveObjectField fvar field =
935
  case fieldIsOptional field of
936
    OptionalOmitNull -> [| case $(varE fvar) of
937
                             Nothing -> []
938
                             Just v  -> [( $nameE, JSON.showJSON v )]
939
                         |]
940
    OptionalSerializeNull -> [| case $(varE fvar) of
941
                                  Nothing -> [( $nameE, JSON.JSNull )]
942
                                  Just v  -> [( $nameE, JSON.showJSON v )]
943
                              |]
944
    NotOptional ->
945
      case fieldShow field of
946
        -- Note: the order of actual:extra is important, since for
947
        -- some serialisation types (e.g. Luxi), we use tuples
948
        -- (positional info) rather than object (name info)
949
        Nothing -> [| [( $nameE, JSON.showJSON $fvarE)] |]
950
        Just fn -> [| let (actual, extra) = $fn $fvarE
951
                      in ($nameE, JSON.showJSON actual):extra
952
                    |]
953
  where nameE = stringE (fieldName field)
954
        fvarE = varE fvar
955

    
956
-- | Generates the showJSON clause for a given object name.
957
objectShowJSON :: String -> Q Dec
958
objectShowJSON name = do
959
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
960
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
961

    
962
-- | Generates the load object functionality.
963
genLoadObject :: (Field -> Q (Name, Stmt))
964
              -> String -> [Field] -> Q (Dec, Dec)
965
genLoadObject load_fn sname fields = do
966
  let name = mkName sname
967
      funname = mkName $ "load" ++ sname
968
      arg1 = mkName $ if null fields then "_" else "v"
969
      objname = mkName "o"
970
      opid = mkName "op_id"
971
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
972
                                 (JSON.readJSON $(varE arg1)) |]
973
  fbinds <- mapM load_fn fields
974
  let (fnames, fstmts) = unzip fbinds
975
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
976
      retstmt = [NoBindS (AppE (VarE 'return) cval)]
977
      -- FIXME: should we require an empty dict for an empty type?
978
      -- this allows any JSValue right now
979
      fstmts' = if null fields
980
                  then retstmt
981
                  else st1:fstmts ++ retstmt
982
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT name) |]
983
  return $ (SigD funname sigt,
984
            FunD funname [Clause [VarP arg1] (NormalB (DoE fstmts')) []])
985

    
986
-- | Generates code for loading an object's field.
987
loadObjectField :: Field -> Q (Name, Stmt)
988
loadObjectField field = do
989
  let name = fieldVariable field
990
  fvar <- newName name
991
  -- these are used in all patterns below
992
  let objvar = varNameE "o"
993
      objfield = stringE (fieldName field)
994
      loadexp =
995
        if fieldIsOptional field /= NotOptional
996
          -- we treat both optional types the same, since
997
          -- 'maybeFromObj' can deal with both missing and null values
998
          -- appropriately (the same)
999
          then [| $(varE 'maybeFromObj) $objvar $objfield |]
1000
          else case fieldDefault field of
1001
                 Just defv ->
1002
                   [| $(varE 'fromObjWithDefault) $objvar
1003
                      $objfield $defv |]
1004
                 Nothing -> [| $fromObjE $objvar $objfield |]
1005
  bexp <- loadFn field loadexp objvar
1006

    
1007
  return (fvar, BindS (VarP fvar) bexp)
1008

    
1009
-- | Builds the readJSON instance for a given object name.
1010
objectReadJSON :: String -> Q Dec
1011
objectReadJSON name = do
1012
  let s = mkName "s"
1013
  body <- [| case JSON.readJSON $(varE s) of
1014
               JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s'
1015
               JSON.Error e ->
1016
                 JSON.Error $ "Can't parse value for type " ++
1017
                       $(stringE name) ++ ": " ++ e
1018
           |]
1019
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
1020

    
1021
-- * Inheritable parameter tables implementation
1022

    
1023
-- | Compute parameter type names.
1024
paramTypeNames :: String -> (String, String)
1025
paramTypeNames root = ("Filled"  ++ root ++ "Params",
1026
                       "Partial" ++ root ++ "Params")
1027

    
1028
-- | Compute information about the type of a parameter field.
1029
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
1030
paramFieldTypeInfo field_pfx fd = do
1031
  t <- actualFieldType fd
1032
  let n = mkName . (++ "P") . (field_pfx ++) .
1033
          fieldRecordName $ fd
1034
  return (n, NotStrict, AppT (ConT ''Maybe) t)
1035

    
1036
-- | Build a parameter declaration.
1037
--
1038
-- This function builds two different data structures: a /filled/ one,
1039
-- in which all fields are required, and a /partial/ one, in which all
1040
-- fields are optional. Due to the current record syntax issues, the
1041
-- fields need to be named differrently for the two structures, so the
1042
-- partial ones get a /P/ suffix.
1043
buildParam :: String -> String -> [Field] -> Q [Dec]
1044
buildParam sname field_pfx fields = do
1045
  let (sname_f, sname_p) = paramTypeNames sname
1046
      name_f = mkName sname_f
1047
      name_p = mkName sname_p
1048
  fields_f <- mapM (fieldTypeInfo field_pfx) fields
1049
  fields_p <- mapM (paramFieldTypeInfo field_pfx) fields
1050
  let decl_f = RecC name_f fields_f
1051
      decl_p = RecC name_p fields_p
1052
  let declF = DataD [] name_f [] [decl_f] [''Show, ''Eq]
1053
      declP = DataD [] name_p [] [decl_p] [''Show, ''Eq]
1054
  ser_decls_f <- buildObjectSerialisation sname_f fields
1055
  ser_decls_p <- buildPParamSerialisation sname_p fields
1056
  fill_decls <- fillParam sname field_pfx fields
1057
  return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls ++
1058
           buildParamAllFields sname fields ++
1059
           buildDictObjectInst name_f sname_f
1060

    
1061
-- | Builds a list of all fields of a parameter.
1062
buildParamAllFields :: String -> [Field] -> [Dec]
1063
buildParamAllFields sname fields =
1064
  let vname = mkName ("all" ++ sname ++ "ParamFields")
1065
      sig = SigD vname (AppT ListT (ConT ''String))
1066
      val = ListE $ map (LitE . StringL . fieldName) fields
1067
  in [sig, ValD (VarP vname) (NormalB val) []]
1068

    
1069
-- | Builds the 'DictObject' instance for a filled parameter.
1070
buildDictObjectInst :: Name -> String -> [Dec]
1071
buildDictObjectInst name sname =
1072
  [InstanceD [] (AppT (ConT ''DictObject) (ConT name))
1073
   [ValD (VarP 'toDict) (NormalB (VarE (toDictName sname))) []]]
1074

    
1075
-- | Generates the serialisation for a partial parameter.
1076
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
1077
buildPParamSerialisation sname fields = do
1078
  let name = mkName sname
1079
  savedecls <- genSaveObject savePParamField sname fields
1080
  (loadsig, loadfn) <- genLoadObject loadPParamField sname fields
1081
  shjson <- objectShowJSON sname
1082
  rdjson <- objectReadJSON sname
1083
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
1084
                 [rdjson, shjson]
1085
  return $ savedecls ++ [loadsig, loadfn, instdecl]
1086

    
1087
-- | Generates code to save an optional parameter field.
1088
savePParamField :: Name -> Field -> Q Exp
1089
savePParamField fvar field = do
1090
  checkNonOptDef field
1091
  let actualVal = mkName "v"
1092
  normalexpr <- saveObjectField actualVal field
1093
  -- we have to construct the block here manually, because we can't
1094
  -- splice-in-splice
1095
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
1096
                                       (NormalB (ConE '[])) []
1097
                             , Match (ConP 'Just [VarP actualVal])
1098
                                       (NormalB normalexpr) []
1099
                             ]
1100

    
1101
-- | Generates code to load an optional parameter field.
1102
loadPParamField :: Field -> Q (Name, Stmt)
1103
loadPParamField field = do
1104
  checkNonOptDef field
1105
  let name = fieldName field
1106
  fvar <- newName name
1107
  -- these are used in all patterns below
1108
  let objvar = varNameE "o"
1109
      objfield = stringE name
1110
      loadexp = [| $(varE 'maybeFromObj) $objvar $objfield |]
1111
  bexp <- loadFn field loadexp objvar
1112
  return (fvar, BindS (VarP fvar) bexp)
1113

    
1114
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
1115
buildFromMaybe :: String -> Q Dec
1116
buildFromMaybe fname =
1117
  valD (varP (mkName $ "n_" ++ fname))
1118
         (normalB [| $(varE 'fromMaybe)
1119
                        $(varNameE $ "f_" ++ fname)
1120
                        $(varNameE $ "p_" ++ fname) |]) []
1121

    
1122
-- | Builds a function that executes the filling of partial parameter
1123
-- from a full copy (similar to Python's fillDict).
1124
fillParam :: String -> String -> [Field] -> Q [Dec]
1125
fillParam sname field_pfx fields = do
1126
  let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields
1127
      (sname_f, sname_p) = paramTypeNames sname
1128
      oname_f = "fobj"
1129
      oname_p = "pobj"
1130
      name_f = mkName sname_f
1131
      name_p = mkName sname_p
1132
      fun_name = mkName $ "fill" ++ sname ++ "Params"
1133
      le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames))
1134
                (NormalB . VarE . mkName $ oname_f) []
1135
      le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames))
1136
                (NormalB . VarE . mkName $ oname_p) []
1137
      obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f)
1138
                $ map (mkName . ("n_" ++)) fnames
1139
  le_new <- mapM buildFromMaybe fnames
1140
  funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |]
1141
  let sig = SigD fun_name funt
1142
      fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)]
1143
                (NormalB $ LetE (le_full:le_part:le_new) obj_new) []
1144
      fun = FunD fun_name [fclause]
1145
  return [sig, fun]
1146

    
1147
-- * Template code for exceptions
1148

    
1149
-- | Exception simple error message field.
1150
excErrMsg :: (String, Q Type)
1151
excErrMsg = ("errMsg", [t| String |])
1152

    
1153
-- | Builds an exception type definition.
1154
genException :: String                  -- ^ Name of new type
1155
             -> SimpleObject -- ^ Constructor name and parameters
1156
             -> Q [Dec]
1157
genException name cons = do
1158
  let tname = mkName name
1159
  declD <- buildSimpleCons tname cons
1160
  (savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $
1161
                         uncurry saveExcCons
1162
  (loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons
1163
  return [declD, loadsig, loadfn, savesig, savefn]
1164

    
1165
-- | Generates the \"save\" clause for an entire exception constructor.
1166
--
1167
-- This matches the exception with variables named the same as the
1168
-- constructor fields (just so that the spliced in code looks nicer),
1169
-- and calls showJSON on it.
1170
saveExcCons :: String        -- ^ The constructor name
1171
            -> [SimpleField] -- ^ The parameter definitions for this
1172
                             -- constructor
1173
            -> Q Clause      -- ^ Resulting clause
1174
saveExcCons sname fields = do
1175
  let cname = mkName sname
1176
  fnames <- mapM (newName . fst) fields
1177
  let pat = conP cname (map varP fnames)
1178
      felems = if null fnames
1179
                 then conE '() -- otherwise, empty list has no type
1180
                 else listE $ map (\f -> [| JSON.showJSON $(varE f) |]) fnames
1181
  let tup = tupE [ litE (stringL sname), felems ]
1182
  clause [pat] (normalB [| JSON.showJSON $tup |]) []
1183

    
1184
-- | Generates load code for a single constructor of an exception.
1185
--
1186
-- Generates the code (if there's only one argument, we will use a
1187
-- list, not a tuple:
1188
--
1189
-- @
1190
-- do
1191
--  (x1, x2, ...) <- readJSON args
1192
--  return $ Cons x1 x2 ...
1193
-- @
1194
loadExcConstructor :: Name -> String -> [SimpleField] -> Q Exp
1195
loadExcConstructor inname sname fields = do
1196
  let name = mkName sname
1197
  f_names <- mapM (newName . fst) fields
1198
  let read_args = AppE (VarE 'JSON.readJSON) (VarE inname)
1199
  let binds = case f_names of
1200
                [x] -> BindS (ListP [VarP x])
1201
                _   -> BindS (TupP (map VarP f_names))
1202
      cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) f_names
1203
  return $ DoE [binds read_args, NoBindS (AppE (VarE 'return) cval)]
1204

    
1205
{-| Generates the loadException function.
1206

    
1207
This generates a quite complicated function, along the lines of:
1208

    
1209
@
1210
loadFn (JSArray [JSString name, args]) = case name of
1211
   "A1" -> do
1212
     (x1, x2, ...) <- readJSON args
1213
     return $ A1 x1 x2 ...
1214
   "a2" -> ...
1215
   s -> fail $ "Unknown exception" ++ s
1216
loadFn v = fail $ "Expected array but got " ++ show v
1217
@
1218
-}
1219
genLoadExc :: Name -> String -> SimpleObject -> Q (Dec, Dec)
1220
genLoadExc tname sname opdefs = do
1221
  let fname = mkName sname
1222
  exc_name <- newName "name"
1223
  exc_args <- newName "args"
1224
  exc_else <- newName "s"
1225
  arg_else <- newName "v"
1226
  fails <- [| fail $ "Unknown exception '" ++ $(varE exc_else) ++ "'" |]
1227
  -- default match for unknown exception name
1228
  let defmatch = Match (VarP exc_else) (NormalB fails) []
1229
  -- the match results (per-constructor blocks)
1230
  str_matches <-
1231
    mapM (\(s, params) -> do
1232
            body_exp <- loadExcConstructor exc_args s params
1233
            return $ Match (LitP (StringL s)) (NormalB body_exp) [])
1234
    opdefs
1235
  -- the first function clause; we can't use [| |] due to TH
1236
  -- limitations, so we have to build the AST by hand
1237
  let clause1 = Clause [ConP 'JSON.JSArray
1238
                               [ListP [ConP 'JSON.JSString [VarP exc_name],
1239
                                            VarP exc_args]]]
1240
                (NormalB (CaseE (AppE (VarE 'JSON.fromJSString)
1241
                                        (VarE exc_name))
1242
                          (str_matches ++ [defmatch]))) []
1243
  -- the fail expression for the second function clause
1244
  fail_type <- [| fail $ "Invalid exception: expected '(string, [args])' " ++
1245
                  "      but got " ++ show (pp_value $(varE arg_else)) ++ "'"
1246
                |]
1247
  -- the second function clause
1248
  let clause2 = Clause [VarP arg_else] (NormalB fail_type) []
1249
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT tname) |]
1250
  return $ (SigD fname sigt, FunD fname [clause1, clause2])