Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ 72375ff8

History | View | Annotate | Download (50.9 kB)

1
{-# LANGUAGE ParallelListComp, 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, 2013, 2014 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
                  , declareLADT
34
                  , declareILADT
35
                  , declareIADT
36
                  , makeJSONInstance
37
                  , deCamelCase
38
                  , genOpID
39
                  , genOpLowerStrip
40
                  , genAllConstr
41
                  , genAllOpIDs
42
                  , PyValue(..)
43
                  , PyValueEx(..)
44
                  , OpCodeField(..)
45
                  , OpCodeDescriptor(..)
46
                  , genOpCode
47
                  , genStrOfOp
48
                  , genStrOfKey
49
                  , genLuxiOp
50
                  , Field (..)
51
                  , simpleField
52
                  , andRestArguments
53
                  , withDoc
54
                  , defaultField
55
                  , optionalField
56
                  , optionalNullSerField
57
                  , renameField
58
                  , customField
59
                  , buildObject
60
                  , buildObjectSerialisation
61
                  , buildParam
62
                  , genException
63
                  , excErrMsg
64
                  ) where
65

    
66
import Control.Arrow ((&&&))
67
import Control.Applicative
68
import Control.Monad
69
import Control.Monad.Base () -- Needed to prevent spurious GHC linking errors.
70
import Data.Attoparsec () -- Needed to prevent spurious GHC 7.4 linking errors.
71
  -- See issue #683 and https://ghc.haskell.org/trac/ghc/ticket/4899
72
import Data.Char
73
import Data.List
74
import Data.Maybe
75
import qualified Data.Map as M
76
import Language.Haskell.TH
77
import Language.Haskell.TH.Syntax (lift)
78

    
79
import qualified Text.JSON as JSON
80
import Text.JSON.Pretty (pp_value)
81

    
82
import Ganeti.JSON
83
import Ganeti.PyValue
84
import Ganeti.THH.PyType
85

    
86

    
87
-- * Exported types
88

    
89
-- | Optional field information.
90
data OptionalType
91
  = NotOptional           -- ^ Field is not optional
92
  | OptionalOmitNull      -- ^ Field is optional, null is not serialised
93
  | OptionalSerializeNull -- ^ Field is optional, null is serialised
94
  | AndRestArguments      -- ^ Special field capturing all the remaining fields
95
                          -- as plain JSON values
96
  deriving (Show, Eq)
97

    
98
-- | Serialised field data type describing how to generate code for the field.
99
-- Each field has a type, which isn't captured in the type of the data type,
100
-- but is saved in the 'Q' monad in 'fieldType'.
101
--
102
-- Let @t@ be a type we want to parametrize the field with. There are the
103
-- following possible types of fields:
104
--
105
--   [Mandatory with no default.] Then @fieldType@ holds @t@,
106
--     @fieldDefault = Nothing@ and @fieldIsOptional = NotOptional@.
107
--
108
--   [Field with a default value.] Then @fieldType@ holds @t@ and
109
--     @fieldDefault = Just exp@ where @exp@ is an expression of type @t@ and
110
--    @fieldIsOptional = NotOptional@.
111
--
112
--   [Optional, no default value.] Then @fieldType@ holds @Maybe t@,
113
--     @fieldDefault = Nothing@ and @fieldIsOptional@ is either
114
--     'OptionalOmitNull' or 'OptionalSerializeNull'.
115
--
116
-- Optional fields with a default value are prohibited, as their main
117
-- intention is to represent the information that a request didn't contain
118
-- the field data.
119
--
120
-- /Custom (de)serialization:/
121
-- Field can have custom (de)serialization functions that are stored in
122
-- 'fieldRead' and 'fieldShow'. If they aren't provided, the default is to use
123
-- 'readJSON' and 'showJSON' for the field's type @t@. If they are provided,
124
-- the type of the contained deserializing expression must be
125
--
126
-- @
127
--   [(String, JSON.JSValue)] -> JSON.JSValue -> JSON.Result t
128
-- @
129
--
130
-- where the first argument carries the whole record in the case the
131
-- deserializing function needs to process additional information.
132
--
133
-- The type of the contained serializing experssion must be
134
--
135
-- @
136
--   t -> (JSON.JSValue, [(String, JSON.JSValue)])
137
-- @
138
--
139
-- where the result can provide extra JSON fields to include in the output
140
-- record (or just return @[]@ if they're not needed).
141
--
142
-- Note that for optional fields the type appearing in the custom functions
143
-- is still @t@. Therefore making a field optional doesn't change the
144
-- functions.
145
--
146
-- There is also a special type of optional field 'AndRestArguments' which
147
-- allows to parse any additional arguments not covered by other fields. There
148
-- can be at most one such special field and it's type must be
149
-- @Map String JSON.JSValue@. See also 'andRestArguments'.
150
data Field = Field { fieldName        :: String
151
                   , fieldType        :: Q Type
152
                     -- ^ the type of the field, @t@ for non-optional fields,
153
                     -- @Maybe t@ for optional ones.
154
                   , fieldRead        :: Maybe (Q Exp)
155
                     -- ^ an optional custom deserialization function of type
156
                     -- @[(String, JSON.JSValue)] -> JSON.JSValue ->
157
                     -- JSON.Result t@
158
                   , fieldShow        :: Maybe (Q Exp)
159
                     -- ^ an optional custom serialization function of type
160
                     -- @t -> (JSON.JSValue, [(String, JSON.JSValue)])@
161
                   , fieldExtraKeys   :: [String]
162
                     -- ^ a list of extra keys added by 'fieldShow'
163
                   , fieldDefault     :: Maybe (Q Exp)
164
                     -- ^ an optional default value of type @t@
165
                   , fieldConstr      :: Maybe String
166
                   , fieldIsOptional  :: OptionalType
167
                     -- ^ determines if a field is optional, and if yes,
168
                     -- how
169
                   , fieldDoc         :: String
170
                   }
171

    
172
-- | Generates a simple field.
173
simpleField :: String -> Q Type -> Field
174
simpleField fname ftype =
175
  Field { fieldName        = fname
176
        , fieldType        = ftype
177
        , fieldRead        = Nothing
178
        , fieldShow        = Nothing
179
        , fieldExtraKeys   = []
180
        , fieldDefault     = Nothing
181
        , fieldConstr      = Nothing
182
        , fieldIsOptional  = NotOptional
183
        , fieldDoc         = ""
184
        }
185

    
186
-- | Generate an AndRestArguments catch-all field.
187
andRestArguments :: String -> Field
188
andRestArguments fname =
189
  Field { fieldName        = fname
190
        , fieldType        = [t| M.Map String JSON.JSValue |]
191
        , fieldRead        = Nothing
192
        , fieldShow        = Nothing
193
        , fieldExtraKeys   = []
194
        , fieldDefault     = Nothing
195
        , fieldConstr      = Nothing
196
        , fieldIsOptional  = AndRestArguments
197
        , fieldDoc         = ""
198
        }
199

    
200
withDoc :: String -> Field -> Field
201
withDoc doc field =
202
  field { fieldDoc = doc }
203

    
204
-- | Sets the renamed constructor field.
205
renameField :: String -> Field -> Field
206
renameField constrName field = field { fieldConstr = Just constrName }
207

    
208
-- | Sets the default value on a field (makes it optional with a
209
-- default value).
210
defaultField :: Q Exp -> Field -> Field
211
defaultField defval field = field { fieldDefault = Just defval }
212

    
213
-- | Marks a field optional (turning its base type into a Maybe).
214
optionalField :: Field -> Field
215
optionalField field = field { fieldIsOptional = OptionalOmitNull }
216

    
217
-- | Marks a field optional (turning its base type into a Maybe), but
218
-- with 'Nothing' serialised explicitly as /null/.
219
optionalNullSerField :: Field -> Field
220
optionalNullSerField field = field { fieldIsOptional = OptionalSerializeNull }
221

    
222
-- | Sets custom functions on a field.
223
customField :: Name      -- ^ The name of the read function
224
            -> Name      -- ^ The name of the show function
225
            -> [String]  -- ^ The name of extra field keys
226
            -> Field     -- ^ The original field
227
            -> Field     -- ^ Updated field
228
customField readfn showfn extra field =
229
  field { fieldRead = Just (varE readfn), fieldShow = Just (varE showfn)
230
        , fieldExtraKeys = extra }
231

    
232
-- | Computes the record name for a given field, based on either the
233
-- string value in the JSON serialisation or the custom named if any
234
-- exists.
235
fieldRecordName :: Field -> String
236
fieldRecordName (Field { fieldName = name, fieldConstr = alias }) =
237
  fromMaybe (camelCase name) alias
238

    
239
-- | Computes the preferred variable name to use for the value of this
240
-- field. If the field has a specific constructor name, then we use a
241
-- first-letter-lowercased version of that; otherwise, we simply use
242
-- the field name. See also 'fieldRecordName'.
243
fieldVariable :: Field -> String
244
fieldVariable f =
245
  case (fieldConstr f) of
246
    Just name -> ensureLower name
247
    _ -> map (\c -> if c == '-' then '_' else c) $ fieldName f
248

    
249
-- | Compute the actual field type (taking into account possible
250
-- optional status).
251
actualFieldType :: Field -> Q Type
252
actualFieldType f | fieldIsOptional f `elem` [NotOptional, AndRestArguments] = t
253
                  | otherwise =  [t| Maybe $t |]
254
                  where t = fieldType f
255

    
256
-- | Checks that a given field is not optional (for object types or
257
-- fields which should not allow this case).
258
checkNonOptDef :: (Monad m) => Field -> m ()
259
checkNonOptDef (Field { fieldIsOptional = OptionalOmitNull
260
                      , fieldName = name }) =
261
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
262
checkNonOptDef (Field { fieldIsOptional = OptionalSerializeNull
263
                      , fieldName = name }) =
264
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
265
checkNonOptDef (Field { fieldDefault = (Just _), fieldName = name }) =
266
  fail $ "Default field " ++ name ++ " used in parameter declaration"
267
checkNonOptDef _ = return ()
268

    
269
-- | Construct a function that parses a field value. If the field has
270
-- a custom 'fieldRead', it's applied to @o@ and used. Otherwise
271
-- @JSON.readJSON@ is used.
272
parseFn :: Field   -- ^ The field definition
273
        -> Q Exp   -- ^ The entire object in JSON object format
274
        -> Q Exp   -- ^ The resulting function that parses a JSON message
275
parseFn field o
276
  = maybe [| readJSONWithDesc $(stringE $ fieldName field) False |]
277
          (`appE` o) (fieldRead field)
278

    
279
-- | Produces the expression that will de-serialise a given
280
-- field. Since some custom parsing functions might need to use the
281
-- entire object, we do take and pass the object to any custom read
282
-- functions.
283
loadFn :: Field   -- ^ The field definition
284
       -> Q Exp   -- ^ The value of the field as existing in the JSON message
285
       -> Q Exp   -- ^ The entire object in JSON object format
286
       -> Q Exp   -- ^ Resulting expression
287
loadFn field expr o = [| $expr >>= $(parseFn field o) |]
288

    
289
-- | Just as 'loadFn', but for optional fields.
290
loadFnOpt :: Field   -- ^ The field definition
291
          -> Q Exp   -- ^ The value of the field as existing in the JSON message
292
                     -- as Maybe
293
          -> Q Exp   -- ^ The entire object in JSON object format
294
          -> Q Exp   -- ^ Resulting expression
295
loadFnOpt field@(Field { fieldDefault = Just def }) expr o
296
  = case fieldIsOptional field of
297
      NotOptional -> [| $expr >>= maybe (return $def) $(parseFn field o) |]
298
      _           -> fail $ "Field " ++ fieldName field ++ ":\
299
                            \ A field can't be optional and\
300
                            \ have a default value at the same time."
301
loadFnOpt field expr o
302
  = [| $expr >>= maybe (return Nothing) (liftM Just . $(parseFn field o)) |]
303

    
304
-- * Internal types
305

    
306
-- | A simple field, in constrast to the customisable 'Field' type.
307
type SimpleField = (String, Q Type)
308

    
309
-- | A definition for a single constructor for a simple object.
310
type SimpleConstructor = (String, [SimpleField])
311

    
312
-- | A definition for ADTs with simple fields.
313
type SimpleObject = [SimpleConstructor]
314

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

    
318
-- | A type alias for a Luxi constructor of a regular object.
319
type LuxiConstructor = (String, [Field])
320

    
321
-- * Helper functions
322

    
323
-- | Ensure first letter is lowercase.
324
--
325
-- Used to convert type name to function prefix, e.g. in @data Aa ->
326
-- aaToRaw@.
327
ensureLower :: String -> String
328
ensureLower [] = []
329
ensureLower (x:xs) = toLower x:xs
330

    
331
-- | Ensure first letter is uppercase.
332
--
333
-- Used to convert constructor name to component
334
ensureUpper :: String -> String
335
ensureUpper [] = []
336
ensureUpper (x:xs) = toUpper x:xs
337

    
338
-- | Helper for quoted expressions.
339
varNameE :: String -> Q Exp
340
varNameE = varE . mkName
341

    
342
-- | showJSON as an expression, for reuse.
343
showJSONE :: Q Exp
344
showJSONE = varE 'JSON.showJSON
345

    
346
-- | makeObj as an expression, for reuse.
347
makeObjE :: Q Exp
348
makeObjE = varE 'JSON.makeObj
349

    
350
-- | fromObj (Ganeti specific) as an expression, for reuse.
351
fromObjE :: Q Exp
352
fromObjE = varE 'fromObj
353

    
354
-- | ToRaw function name.
355
toRawName :: String -> Name
356
toRawName = mkName . (++ "ToRaw") . ensureLower
357

    
358
-- | FromRaw function name.
359
fromRawName :: String -> Name
360
fromRawName = mkName . (++ "FromRaw") . ensureLower
361

    
362
-- | Converts a name to it's varE\/litE representations.
363
reprE :: Either String Name -> Q Exp
364
reprE = either stringE varE
365

    
366
-- | Smarter function application.
367
--
368
-- This does simply f x, except that if is 'id', it will skip it, in
369
-- order to generate more readable code when using -ddump-splices.
370
appFn :: Exp -> Exp -> Exp
371
appFn f x | f == VarE 'id = x
372
          | otherwise = AppE f x
373

    
374
-- | Builds a field for a normal constructor.
375
buildConsField :: Q Type -> StrictTypeQ
376
buildConsField ftype = do
377
  ftype' <- ftype
378
  return (NotStrict, ftype')
379

    
380
-- | Builds a constructor based on a simple definition (not field-based).
381
buildSimpleCons :: Name -> SimpleObject -> Q Dec
382
buildSimpleCons tname cons = do
383
  decl_d <- mapM (\(cname, fields) -> do
384
                    fields' <- mapM (buildConsField . snd) fields
385
                    return $ NormalC (mkName cname) fields') cons
386
  return $ DataD [] tname [] decl_d [''Show, ''Eq]
387

    
388
-- | Generate the save function for a given type.
389
genSaveSimpleObj :: Name                            -- ^ Object type
390
                 -> String                          -- ^ Function name
391
                 -> SimpleObject                    -- ^ Object definition
392
                 -> (SimpleConstructor -> Q Clause) -- ^ Constructor save fn
393
                 -> Q (Dec, Dec)
394
genSaveSimpleObj tname sname opdefs fn = do
395
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT ''JSON.JSValue)
396
      fname = mkName sname
397
  cclauses <- mapM fn opdefs
398
  return $ (SigD fname sigt, FunD fname cclauses)
399

    
400
-- * Template code for simple raw type-equivalent ADTs
401

    
402
-- | Generates a data type declaration.
403
--
404
-- The type will have a fixed list of instances.
405
strADTDecl :: Name -> [String] -> Dec
406
strADTDecl name constructors =
407
  DataD [] name []
408
          (map (flip NormalC [] . mkName) constructors)
409
          [''Show, ''Eq, ''Enum, ''Bounded, ''Ord]
410

    
411
-- | Generates a toRaw function.
412
--
413
-- This generates a simple function of the form:
414
--
415
-- @
416
-- nameToRaw :: Name -> /traw/
417
-- nameToRaw Cons1 = var1
418
-- nameToRaw Cons2 = \"value2\"
419
-- @
420
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
421
genToRaw traw fname tname constructors = do
422
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw)
423
  -- the body clauses, matching on the constructor and returning the
424
  -- raw value
425
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
426
                             (normalB (reprE v)) []) constructors
427
  return [SigD fname sigt, FunD fname clauses]
428

    
429
-- | Generates a fromRaw function.
430
--
431
-- The function generated is monadic and can fail parsing the
432
-- raw value. It is of the form:
433
--
434
-- @
435
-- nameFromRaw :: (Monad m) => /traw/ -> m Name
436
-- nameFromRaw s | s == var1       = Cons1
437
--               | s == \"value2\" = Cons2
438
--               | otherwise = fail /.../
439
-- @
440
genFromRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
441
genFromRaw traw fname tname constructors = do
442
  -- signature of form (Monad m) => String -> m $name
443
  sigt <- [t| (Monad m) => $(conT traw) -> m $(conT tname) |]
444
  -- clauses for a guarded pattern
445
  let varp = mkName "s"
446
      varpe = varE varp
447
  clauses <- mapM (\(c, v) -> do
448
                     -- the clause match condition
449
                     g <- normalG [| $varpe == $(reprE v) |]
450
                     -- the clause result
451
                     r <- [| return $(conE (mkName c)) |]
452
                     return (g, r)) constructors
453
  -- the otherwise clause (fallback)
454
  oth_clause <- do
455
    g <- normalG [| otherwise |]
456
    r <- [|fail ("Invalid string value for type " ++
457
                 $(litE (stringL (nameBase tname))) ++ ": " ++ show $varpe) |]
458
    return (g, r)
459
  let fun = FunD fname [Clause [VarP varp]
460
                        (GuardedB (clauses++[oth_clause])) []]
461
  return [SigD fname sigt, fun]
462

    
463
-- | Generates a data type from a given raw format.
464
--
465
-- The format is expected to multiline. The first line contains the
466
-- type name, and the rest of the lines must contain two words: the
467
-- constructor name and then the string representation of the
468
-- respective constructor.
469
--
470
-- The function will generate the data type declaration, and then two
471
-- functions:
472
--
473
-- * /name/ToRaw, which converts the type to a raw type
474
--
475
-- * /name/FromRaw, which (monadically) converts from a raw type to the type
476
--
477
-- Note that this is basically just a custom show\/read instance,
478
-- nothing else.
479
declareADT
480
  :: (a -> Either String Name) -> Name -> String -> [(String, a)] -> Q [Dec]
481
declareADT fn traw sname cons = do
482
  let name = mkName sname
483
      ddecl = strADTDecl name (map fst cons)
484
      -- process cons in the format expected by genToRaw
485
      cons' = map (\(a, b) -> (a, fn b)) cons
486
  toraw <- genToRaw traw (toRawName sname) name cons'
487
  fromraw <- genFromRaw traw (fromRawName sname) name cons'
488
  return $ ddecl:toraw ++ fromraw
489

    
490
declareLADT :: Name -> String -> [(String, String)] -> Q [Dec]
491
declareLADT = declareADT Left
492

    
493
declareILADT :: String -> [(String, Int)] -> Q [Dec]
494
declareILADT sname cons = do
495
  consNames <- sequence [ newName ('_':n) | (n, _) <- cons ]
496
  consFns <- concat <$> sequence
497
             [ do sig <- sigD n [t| Int |]
498
                  let expr = litE (IntegerL (toInteger i))
499
                  fn <- funD n [clause [] (normalB expr) []]
500
                  return [sig, fn]
501
             | n <- consNames
502
             | (_, i) <- cons ]
503
  let cons' = [ (n, n') | (n, _) <- cons | n' <- consNames ]
504
  (consFns ++) <$> declareADT Right ''Int sname cons'
505

    
506
declareIADT :: String -> [(String, Name)] -> Q [Dec]
507
declareIADT = declareADT Right ''Int
508

    
509
declareSADT :: String -> [(String, Name)] -> Q [Dec]
510
declareSADT = declareADT Right ''String
511

    
512
-- | Creates the showJSON member of a JSON instance declaration.
513
--
514
-- This will create what is the equivalent of:
515
--
516
-- @
517
-- showJSON = showJSON . /name/ToRaw
518
-- @
519
--
520
-- in an instance JSON /name/ declaration
521
genShowJSON :: String -> Q Dec
522
genShowJSON name = do
523
  body <- [| JSON.showJSON . $(varE (toRawName name)) |]
524
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
525

    
526
-- | Creates the readJSON member of a JSON instance declaration.
527
--
528
-- This will create what is the equivalent of:
529
--
530
-- @
531
-- readJSON s = case readJSON s of
532
--                Ok s' -> /name/FromRaw s'
533
--                Error e -> Error /description/
534
-- @
535
--
536
-- in an instance JSON /name/ declaration
537
genReadJSON :: String -> Q Dec
538
genReadJSON name = do
539
  let s = mkName "s"
540
  body <- [| $(varE (fromRawName name)) =<<
541
             readJSONWithDesc $(stringE name) True $(varE s) |]
542
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
543

    
544
-- | Generates a JSON instance for a given type.
545
--
546
-- This assumes that the /name/ToRaw and /name/FromRaw functions
547
-- have been defined as by the 'declareSADT' function.
548
makeJSONInstance :: Name -> Q [Dec]
549
makeJSONInstance name = do
550
  let base = nameBase name
551
  showJ <- genShowJSON base
552
  readJ <- genReadJSON base
553
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]]
554

    
555
-- * Template code for opcodes
556

    
557
-- | Transforms a CamelCase string into an_underscore_based_one.
558
deCamelCase :: String -> String
559
deCamelCase =
560
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
561

    
562
-- | Transform an underscore_name into a CamelCase one.
563
camelCase :: String -> String
564
camelCase = concatMap (ensureUpper . drop 1) .
565
            groupBy (\_ b -> b /= '_' && b /= '-') . ('_':)
566

    
567
-- | Computes the name of a given constructor.
568
constructorName :: Con -> Q Name
569
constructorName (NormalC name _) = return name
570
constructorName (RecC name _)    = return name
571
constructorName x                = fail $ "Unhandled constructor " ++ show x
572

    
573
-- | Extract all constructor names from a given type.
574
reifyConsNames :: Name -> Q [String]
575
reifyConsNames name = do
576
  reify_result <- reify name
577
  case reify_result of
578
    TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons
579
    o -> fail $ "Unhandled name passed to reifyConsNames, expected\
580
                \ type constructor but got '" ++ show o ++ "'"
581

    
582
-- | Builds the generic constructor-to-string function.
583
--
584
-- This generates a simple function of the following form:
585
--
586
-- @
587
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne")
588
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo")
589
-- @
590
--
591
-- This builds a custom list of name\/string pairs and then uses
592
-- 'genToRaw' to actually generate the function.
593
genConstrToStr :: (String -> Q String) -> Name -> String -> Q [Dec]
594
genConstrToStr trans_fun name fname = do
595
  cnames <- reifyConsNames name
596
  svalues <- mapM (liftM Left . trans_fun) cnames
597
  genToRaw ''String (mkName fname) name $ zip cnames svalues
598

    
599
-- | Constructor-to-string for OpCode.
600
genOpID :: Name -> String -> Q [Dec]
601
genOpID = genConstrToStr (return . deCamelCase)
602

    
603
-- | Strips @Op@ from the constructor name, converts to lower-case
604
-- and adds a given prefix.
605
genOpLowerStrip :: String -> Name -> String -> Q [Dec]
606
genOpLowerStrip prefix =
607
    genConstrToStr (liftM ((prefix ++) . map toLower . deCamelCase)
608
                    . stripPrefixM "Op")
609
  where
610
    stripPrefixM :: String -> String -> Q String
611
    stripPrefixM pfx s = maybe (fail $ s ++ " doesn't start with " ++ pfx)
612
                               return
613
                         $ stripPrefix pfx s
614

    
615
-- | Builds a list with all defined constructor names for a type.
616
--
617
-- @
618
-- vstr :: String
619
-- vstr = [...]
620
-- @
621
--
622
-- Where the actual values of the string are the constructor names
623
-- mapped via @trans_fun@.
624
genAllConstr :: (String -> String) -> Name -> String -> Q [Dec]
625
genAllConstr trans_fun name vstr = do
626
  cnames <- reifyConsNames name
627
  let svalues = sort $ map trans_fun cnames
628
      vname = mkName vstr
629
      sig = SigD vname (AppT ListT (ConT ''String))
630
      body = NormalB (ListE (map (LitE . StringL) svalues))
631
  return $ [sig, ValD (VarP vname) body []]
632

    
633
-- | Generates a list of all defined opcode IDs.
634
genAllOpIDs :: Name -> String -> Q [Dec]
635
genAllOpIDs = genAllConstr deCamelCase
636

    
637
-- | OpCode parameter (field) type.
638
type OpParam = (String, Q Type, Q Exp)
639

    
640
-- * Python code generation
641

    
642
data OpCodeField = OpCodeField { ocfName :: String
643
                               , ocfType :: PyType
644
                               , ocfDefl :: Maybe PyValueEx
645
                               , ocfDoc  :: String
646
                               }
647

    
648
-- | Transfers opcode data between the opcode description (through
649
-- @genOpCode@) and the Python code generation functions.
650
data OpCodeDescriptor = OpCodeDescriptor { ocdName   :: String
651
                                         , ocdType   :: PyType
652
                                         , ocdDoc    :: String
653
                                         , ocdFields :: [OpCodeField]
654
                                         , ocdDescr  :: String
655
                                         }
656

    
657
-- | Optionally encapsulates default values in @PyValueEx@.
658
--
659
-- @maybeApp exp typ@ returns a quoted expression that encapsulates
660
-- the default value @exp@ of an opcode parameter cast to @typ@ in a
661
-- @PyValueEx@, if @exp@ is @Just@.  Otherwise, it returns a quoted
662
-- expression with @Nothing@.
663
maybeApp :: Maybe (Q Exp) -> Q Type -> Q Exp
664
maybeApp Nothing _ =
665
  [| Nothing |]
666

    
667
maybeApp (Just expr) typ =
668
  [| Just ($(conE (mkName "PyValueEx")) ($expr :: $typ)) |]
669

    
670
-- | Generates a Python type according to whether the field is
671
-- optional.
672
--
673
-- The type of created expression is PyType.
674
genPyType' :: OptionalType -> Q Type -> Q PyType
675
genPyType' opt typ = typ >>= pyOptionalType (opt /= NotOptional)
676

    
677
-- | Generates Python types from opcode parameters.
678
genPyType :: Field -> Q PyType
679
genPyType f = genPyType' (fieldIsOptional f) (fieldType f)
680

    
681
-- | Generates Python default values from opcode parameters.
682
genPyDefault :: Field -> Q Exp
683
genPyDefault f = maybeApp (fieldDefault f) (fieldType f)
684

    
685
pyField :: Field -> Q Exp
686
pyField f = genPyType f >>= \t ->
687
            [| OpCodeField $(stringE (fieldName f))
688
                           t
689
                           $(genPyDefault f)
690
                           $(stringE (fieldDoc f)) |]
691

    
692
-- | Generates a Haskell function call to "showPyClass" with the
693
-- necessary information on how to build the Python class string.
694
pyClass :: OpCodeConstructor -> Q Exp
695
pyClass (consName, consType, consDoc, consFields, consDscField) =
696
  do let pyClassVar = varNameE "showPyClass"
697
         consName' = stringE consName
698
     consType' <- genPyType' NotOptional consType
699
     let consDoc' = stringE consDoc
700
     [| OpCodeDescriptor $consName'
701
                         consType'
702
                         $consDoc'
703
                         $(listE $ map pyField consFields)
704
                         consDscField |]
705

    
706
-- | Generates a function called "pyClasses" that holds the list of
707
-- all the opcode descriptors necessary for generating the Python
708
-- opcodes.
709
pyClasses :: [OpCodeConstructor] -> Q [Dec]
710
pyClasses cons =
711
  do let name = mkName "pyClasses"
712
         sig = SigD name (AppT ListT (ConT ''OpCodeDescriptor))
713
     fn <- FunD name <$> (:[]) <$> declClause cons
714
     return [sig, fn]
715
  where declClause c =
716
          clause [] (normalB (ListE <$> mapM pyClass c)) []
717

    
718
-- | Converts from an opcode constructor to a Luxi constructor.
719
opcodeConsToLuxiCons :: (a, b, c, d, e) -> (a, d)
720
opcodeConsToLuxiCons (x, _, _, y, _) = (x, y)
721

    
722
-- | Generates the OpCode data type.
723
--
724
-- This takes an opcode logical definition, and builds both the
725
-- datatype and the JSON serialisation out of it. We can't use a
726
-- generic serialisation since we need to be compatible with Ganeti's
727
-- own, so we have a few quirks to work around.
728
genOpCode :: String              -- ^ Type name to use
729
          -> [OpCodeConstructor] -- ^ Constructor name and parameters
730
          -> Q [Dec]
731
genOpCode name cons = do
732
  let tname = mkName name
733
  decl_d <- mapM (\(cname, _, _, fields, _) -> do
734
                    -- we only need the type of the field, without Q
735
                    fields' <- mapM (fieldTypeInfo "op") fields
736
                    return $ RecC (mkName cname) fields')
737
            cons
738
  let declD = DataD [] tname [] decl_d [''Show, ''Eq]
739
  let (allfsig, allffn) = genAllOpFields "allOpFields" cons
740
  save_decs <- genSaveOpCode tname "saveOpCode" "toDictOpCode"
741
               (map opcodeConsToLuxiCons cons) saveConstructor True
742
  (loadsig, loadfn) <- genLoadOpCode cons
743
  pyDecls <- pyClasses cons
744
  return $ [declD, allfsig, allffn, loadsig, loadfn] ++ save_decs ++ pyDecls
745

    
746
-- | Generates the function pattern returning the list of fields for a
747
-- given constructor.
748
genOpConsFields :: OpCodeConstructor -> Clause
749
genOpConsFields (cname, _, _, fields, _) =
750
  let op_id = deCamelCase cname
751
      fvals = map (LitE . StringL) . sort . nub $
752
              concatMap (\f -> fieldName f:fieldExtraKeys f) fields
753
  in Clause [LitP (StringL op_id)] (NormalB $ ListE fvals) []
754

    
755
-- | Generates a list of all fields of an opcode constructor.
756
genAllOpFields  :: String              -- ^ Function name
757
                -> [OpCodeConstructor] -- ^ Object definition
758
                -> (Dec, Dec)
759
genAllOpFields sname opdefs =
760
  let cclauses = map genOpConsFields opdefs
761
      other = Clause [WildP] (NormalB (ListE [])) []
762
      fname = mkName sname
763
      sigt = AppT  (AppT ArrowT (ConT ''String)) (AppT ListT (ConT ''String))
764
  in (SigD fname sigt, FunD fname (cclauses++[other]))
765

    
766
-- | Generates the \"save\" clause for an entire opcode constructor.
767
--
768
-- This matches the opcode with variables named the same as the
769
-- constructor fields (just so that the spliced in code looks nicer),
770
-- and passes those name plus the parameter definition to 'saveObjectField'.
771
saveConstructor :: LuxiConstructor -- ^ The constructor
772
                -> Q Clause        -- ^ Resulting clause
773
saveConstructor (sname, fields) = do
774
  let cname = mkName sname
775
  fnames <- mapM (newName . fieldVariable) fields
776
  let pat = conP cname (map varP fnames)
777
  let felems = zipWith saveObjectField fnames fields
778
      -- now build the OP_ID serialisation
779
      opid = [| [( $(stringE "OP_ID"),
780
                   JSON.showJSON $(stringE . deCamelCase $ sname) )] |]
781
      flist = listE (opid:felems)
782
      -- and finally convert all this to a json object
783
      flist' = [| concat $flist |]
784
  clause [pat] (normalB flist') []
785

    
786
-- | Generates the main save opcode function.
787
--
788
-- This builds a per-constructor match clause that contains the
789
-- respective constructor-serialisation code.
790
genSaveOpCode :: Name                          -- ^ Object ype
791
              -> String                        -- ^ To 'JSValue' function name
792
              -> String                        -- ^ To 'JSObject' function name
793
              -> [LuxiConstructor]             -- ^ Object definition
794
              -> (LuxiConstructor -> Q Clause) -- ^ Constructor save fn
795
              -> Bool                          -- ^ Whether to generate
796
                                               -- obj or just a
797
                                               -- list\/tuple of values
798
              -> Q [Dec]
799
genSaveOpCode tname jvalstr tdstr opdefs fn gen_object = do
800
  tdclauses <- mapM fn opdefs
801
  let typecon = ConT tname
802
      jvalname = mkName jvalstr
803
      jvalsig = AppT  (AppT ArrowT typecon) (ConT ''JSON.JSValue)
804
      tdname = mkName tdstr
805
  tdsig <- [t| $(return typecon) -> [(String, JSON.JSValue)] |]
806
  jvalclause <- if gen_object
807
                  then [| $makeObjE . $(varE tdname) |]
808
                  else [| JSON.showJSON . map snd . $(varE tdname) |]
809
  return [ SigD tdname tdsig
810
         , FunD tdname tdclauses
811
         , SigD jvalname jvalsig
812
         , ValD (VarP jvalname) (NormalB jvalclause) []]
813

    
814
-- | Generates load code for a single constructor of the opcode data type.
815
loadConstructor :: Name -> (Field -> Q Exp) -> [Field] -> Q Exp
816
loadConstructor name loadfn fields = do
817
  fnames <- mapM (newName . ("r_" ++) . fieldName) fields
818
  fexps <- mapM loadfn fields
819
  let fstmts = zipWith (BindS . VarP) fnames fexps
820
      cexp = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
821
      retstmt = [NoBindS (AppE (VarE 'return) cexp)]
822
      -- FIXME: should we require an empty dict for an empty type?
823
      -- this allows any JSValue right now
824
  return $ DoE (fstmts ++ retstmt)
825

    
826
-- | Generates load code for a single constructor of the opcode data type.
827
loadOpConstructor :: OpCodeConstructor -> Q Exp
828
loadOpConstructor (sname, _, _, fields, _) =
829
  loadConstructor (mkName sname) (loadObjectField fields) fields
830

    
831
-- | Generates the loadOpCode function.
832
genLoadOpCode :: [OpCodeConstructor] -> Q (Dec, Dec)
833
genLoadOpCode opdefs = do
834
  let fname = mkName "loadOpCode"
835
      arg1 = mkName "v"
836
      objname = objVarName
837
      opid = mkName "op_id"
838
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
839
                                 (JSON.readJSON $(varE arg1)) |]
840
  st2 <- bindS (varP opid) [| $fromObjE $(varE objname) $(stringE "OP_ID") |]
841
  -- the match results (per-constructor blocks)
842
  mexps <- mapM loadOpConstructor opdefs
843
  fails <- [| fail $ "Unknown opcode " ++ $(varE opid) |]
844
  let mpats = map (\(me, (consName, _, _, _, _)) ->
845
                       let mp = LitP . StringL . deCamelCase $ consName
846
                       in Match mp (NormalB me) []
847
                  ) $ zip mexps opdefs
848
      defmatch = Match WildP (NormalB fails) []
849
      cst = NoBindS $ CaseE (VarE opid) $ mpats++[defmatch]
850
      body = DoE [st1, st2, cst]
851
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT (mkName "OpCode")) |]
852
  return $ (SigD fname sigt, FunD fname [Clause [VarP arg1] (NormalB body) []])
853

    
854
-- * Template code for luxi
855

    
856
-- | Constructor-to-string for LuxiOp.
857
genStrOfOp :: Name -> String -> Q [Dec]
858
genStrOfOp = genConstrToStr return
859

    
860
-- | Constructor-to-string for MsgKeys.
861
genStrOfKey :: Name -> String -> Q [Dec]
862
genStrOfKey = genConstrToStr (return . ensureLower)
863

    
864
-- | Generates the LuxiOp data type.
865
--
866
-- This takes a Luxi operation definition and builds both the
867
-- datatype and the function transforming the arguments to JSON.
868
-- We can't use anything less generic, because the way different
869
-- operations are serialized differs on both parameter- and top-level.
870
--
871
-- There are two things to be defined for each parameter:
872
--
873
-- * name
874
--
875
-- * type
876
--
877
genLuxiOp :: String -> [LuxiConstructor] -> Q [Dec]
878
genLuxiOp name cons = do
879
  let tname = mkName name
880
  decl_d <- mapM (\(cname, fields) -> do
881
                    -- we only need the type of the field, without Q
882
                    fields' <- mapM actualFieldType fields
883
                    let fields'' = zip (repeat NotStrict) fields'
884
                    return $ NormalC (mkName cname) fields'')
885
            cons
886
  let declD = DataD [] (mkName name) [] decl_d [''Show, ''Eq]
887
  save_decs <- genSaveOpCode tname "opToArgs" "opToDict"
888
               cons saveLuxiConstructor False
889
  req_defs <- declareSADT "LuxiReq" .
890
              map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $
891
                  cons
892
  return $ declD:save_decs ++ req_defs
893

    
894
-- | Generates the \"save\" clause for entire LuxiOp constructor.
895
saveLuxiConstructor :: LuxiConstructor -> Q Clause
896
saveLuxiConstructor (sname, fields) = do
897
  let cname = mkName sname
898
  fnames <- mapM (newName . fieldVariable) fields
899
  let pat = conP cname (map varP fnames)
900
  let felems = zipWith saveObjectField fnames fields
901
      flist = [| concat $(listE felems) |]
902
  clause [pat] (normalB flist) []
903

    
904
-- * "Objects" functionality
905

    
906
-- | Extract the field's declaration from a Field structure.
907
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
908
fieldTypeInfo field_pfx fd = do
909
  t <- actualFieldType fd
910
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
911
  return (n, NotStrict, t)
912

    
913
-- | Build an object declaration.
914
buildObject :: String -> String -> [Field] -> Q [Dec]
915
buildObject sname field_pfx fields = do
916
  when (any ((==) AndRestArguments . fieldIsOptional)
917
         . drop 1 $ reverse fields)
918
    $ fail "Objects may have only one AndRestArguments field,\
919
           \ and it must be the last one."
920
  let name = mkName sname
921
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
922
  let decl_d = RecC name fields_d
923
  let declD = DataD [] name [] [decl_d] [''Show, ''Eq]
924
  ser_decls <- buildObjectSerialisation sname fields
925
  return $ declD:ser_decls
926

    
927
-- | Generates an object definition: data type and its JSON instance.
928
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
929
buildObjectSerialisation sname fields = do
930
  let name = mkName sname
931
  dictdecls <- genDictObject saveObjectField
932
                             (loadObjectField fields) sname fields
933
  savedecls <- genSaveObject sname
934
  (loadsig, loadfn) <- genLoadObject sname
935
  shjson <- objectShowJSON sname
936
  rdjson <- objectReadJSON sname
937
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
938
                 [rdjson, shjson]
939
  return $ dictdecls ++ savedecls ++ [loadsig, loadfn, instdecl]
940

    
941
-- | An internal name used for naming variables that hold the entire
942
-- object of type @[(String,JSValue)]@.
943
objVarName :: Name
944
objVarName = mkName "_o"
945

    
946
-- | Provides a default 'toJSArray' for 'ArrayObject' instance using its
947
-- existing 'DictObject' instance. The keys are serialized in the order
948
-- they're declared. The list must contain all keys possibly generated by
949
-- 'toDict'.
950
defaultToJSArray :: (DictObject a) => [String] -> a -> [JSON.JSValue]
951
defaultToJSArray keys o =
952
  let m = M.fromList $ toDict o
953
  in map (fromMaybe JSON.JSNull . flip M.lookup m) keys
954

    
955
-- | Provides a default 'fromJSArray' for 'ArrayObject' instance using its
956
-- existing 'DictObject' instance. The fields are deserialized in the order
957
-- they're declared.
958
defaultFromJSArray :: (DictObject a)
959
                   => [String] -> [JSON.JSValue] -> JSON.Result a
960
defaultFromJSArray keys xs = do
961
  let xslen = length xs
962
      explen = length keys
963
  unless (xslen == explen) (fail $ "Expected " ++ show explen
964
                                   ++ " arguments, got " ++ show xslen)
965
  fromDict $ zip keys xs
966

    
967
-- | Generates an additional 'ArrayObject' instance using its
968
-- existing 'DictObject' instance.
969
--
970
-- See 'defaultToJSArray' and 'defaultFromJSArray'.
971
genArrayObjectInstance :: Name -> [Field] -> Q Dec
972
genArrayObjectInstance name fields = do
973
  let fnames = concatMap (liftA2 (:) fieldName fieldExtraKeys) fields
974
  instanceD (return []) (appT (conT ''ArrayObject) (conT name))
975
    [ valD (varP 'toJSArray) (normalB [| defaultToJSArray $(lift fnames) |]) []
976
    , valD (varP 'fromJSArray) (normalB [| defaultFromJSArray fnames |]) []
977
    ]
978

    
979
-- | Generates 'DictObject' instance.
980
genDictObject :: (Name -> Field -> Q Exp)  -- ^ a saving function
981
              -> (Field -> Q Exp)          -- ^ a loading function
982
              -> String                    -- ^ an object name
983
              -> [Field]                   -- ^ a list of fields
984
              -> Q [Dec]
985
genDictObject save_fn load_fn sname fields = do
986
  let name = mkName sname
987
  -- toDict
988
  fnames <- mapM (newName . fieldVariable) fields
989
  let pat = conP name (map varP fnames)
990
      tdexp = [| concat $(listE $ zipWith save_fn fnames fields) |]
991
  tdclause <- clause [pat] (normalB tdexp) []
992
  -- fromDict
993
  fdexp <- loadConstructor name load_fn fields
994
  let fdclause = Clause [VarP objVarName] (NormalB fdexp) []
995
  -- the ArrayObject instance generated from DictObject
996
  arrdec <- genArrayObjectInstance name fields
997
  -- the final instance
998
  return $ [InstanceD [] (AppT (ConT ''DictObject) (ConT name))
999
             [ FunD 'toDict [tdclause]
1000
             , FunD 'fromDict [fdclause]
1001
             ]]
1002
         ++ [arrdec]
1003

    
1004
-- | Generates the save object functionality.
1005
genSaveObject :: String -> Q [Dec]
1006
genSaveObject sname = do
1007
  let fname = mkName ("save" ++ sname)
1008
  sigt <- [t| $(conT $ mkName sname) -> JSON.JSValue |]
1009
  cclause <- [| $makeObjE . $(varE $ 'toDict) |]
1010
  return [SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
1011

    
1012
-- | Generates the code for saving an object's field, handling the
1013
-- various types of fields that we have.
1014
saveObjectField :: Name -> Field -> Q Exp
1015
saveObjectField fvar field =
1016
  let formatFn = fromMaybe [| JSON.showJSON &&& (const []) |] $
1017
                           fieldShow field
1018
      formatCode v = [| let (actual, extra) = $formatFn $(v)
1019
                         in ($nameE, actual) : extra |]
1020
  in case fieldIsOptional field of
1021
    OptionalOmitNull ->       [| case $(fvarE) of
1022
                                   Nothing -> []
1023
                                   Just v  -> $(formatCode [| v |])
1024
                              |]
1025
    OptionalSerializeNull ->  [| case $(fvarE) of
1026
                                   Nothing -> [( $nameE, JSON.JSNull )]
1027
                                   Just v  -> $(formatCode [| v |])
1028
                              |]
1029
    NotOptional ->            formatCode fvarE
1030
    AndRestArguments -> [| M.toList $(varE fvar) |]
1031
  where nameE = stringE (fieldName field)
1032
        fvarE = varE fvar
1033

    
1034
-- | Generates the showJSON clause for a given object name.
1035
objectShowJSON :: String -> Q Dec
1036
objectShowJSON name = do
1037
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
1038
  return $ FunD 'JSON.showJSON [Clause [] (NormalB body) []]
1039

    
1040
-- | Generates the load object functionality.
1041
genLoadObject :: String -> Q (Dec, Dec)
1042
genLoadObject sname = do
1043
  let fname = mkName $ "load" ++ sname
1044
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT $ mkName sname) |]
1045
  cclause <- [| fromDict <=< liftM JSON.fromJSObject . JSON.readJSON |]
1046
  return $ (SigD fname sigt,
1047
            FunD fname [Clause [] (NormalB cclause) []])
1048

    
1049
-- | Generates code for loading an object's field.
1050
loadObjectField :: [Field] -> Field -> Q Exp
1051
loadObjectField allFields field = do
1052
  let name = fieldVariable field
1053
      names = map fieldVariable allFields
1054
      otherNames = listE . map stringE $ names \\ [name]
1055
  -- these are used in all patterns below
1056
  let objvar = varE objVarName
1057
      objfield = stringE (fieldName field)
1058
  case (fieldDefault field, fieldIsOptional field) of
1059
            -- Only non-optional fields without defaults must have a value;
1060
            -- we treat both optional types the same, since
1061
            -- 'maybeFromObj' can deal with both missing and null values
1062
            -- appropriately (the same)
1063
            (Nothing, NotOptional) ->
1064
                  loadFn field [| fromObj $objvar $objfield |] objvar
1065
            -- AndRestArguments need not to be parsed at all,
1066
            -- they're just extracted from the list of other fields.
1067
            (Nothing, AndRestArguments) ->
1068
                  [| return . M.fromList
1069
                     $ filter (not . (`elem` $otherNames) . fst) $objvar |]
1070
            _ ->  loadFnOpt field [| maybeFromObj $objvar $objfield |] objvar
1071

    
1072
-- | Builds the readJSON instance for a given object name.
1073
objectReadJSON :: String -> Q Dec
1074
objectReadJSON name = do
1075
  let s = mkName "s"
1076
  body <- [| $(varE . mkName $ "load" ++ name) =<<
1077
             readJSONWithDesc $(stringE name) False $(varE s) |]
1078
  return $ FunD 'JSON.readJSON [Clause [VarP s] (NormalB body) []]
1079

    
1080
-- * Inheritable parameter tables implementation
1081

    
1082
-- | Compute parameter type names.
1083
paramTypeNames :: String -> (String, String)
1084
paramTypeNames root = ("Filled"  ++ root ++ "Params",
1085
                       "Partial" ++ root ++ "Params")
1086

    
1087
-- | Compute information about the type of a parameter field.
1088
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
1089
paramFieldTypeInfo field_pfx fd = do
1090
  t <- actualFieldType fd
1091
  let n = mkName . (++ "P") . (field_pfx ++) .
1092
          fieldRecordName $ fd
1093
  return (n, NotStrict, AppT (ConT ''Maybe) t)
1094

    
1095
-- | Build a parameter declaration.
1096
--
1097
-- This function builds two different data structures: a /filled/ one,
1098
-- in which all fields are required, and a /partial/ one, in which all
1099
-- fields are optional. Due to the current record syntax issues, the
1100
-- fields need to be named differrently for the two structures, so the
1101
-- partial ones get a /P/ suffix.
1102
buildParam :: String -> String -> [Field] -> Q [Dec]
1103
buildParam sname field_pfx fields = do
1104
  let (sname_f, sname_p) = paramTypeNames sname
1105
      name_f = mkName sname_f
1106
      name_p = mkName sname_p
1107
  fields_f <- mapM (fieldTypeInfo field_pfx) fields
1108
  fields_p <- mapM (paramFieldTypeInfo field_pfx) fields
1109
  let decl_f = RecC name_f fields_f
1110
      decl_p = RecC name_p fields_p
1111
  let declF = DataD [] name_f [] [decl_f] [''Show, ''Eq]
1112
      declP = DataD [] name_p [] [decl_p] [''Show, ''Eq]
1113
  ser_decls_f <- buildObjectSerialisation sname_f fields
1114
  ser_decls_p <- buildPParamSerialisation sname_p fields
1115
  fill_decls <- fillParam sname field_pfx fields
1116
  return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls ++
1117
           buildParamAllFields sname fields
1118

    
1119
-- | Builds a list of all fields of a parameter.
1120
buildParamAllFields :: String -> [Field] -> [Dec]
1121
buildParamAllFields sname fields =
1122
  let vname = mkName ("all" ++ sname ++ "ParamFields")
1123
      sig = SigD vname (AppT ListT (ConT ''String))
1124
      val = ListE $ map (LitE . StringL . fieldName) fields
1125
  in [sig, ValD (VarP vname) (NormalB val) []]
1126

    
1127
-- | Generates the serialisation for a partial parameter.
1128
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
1129
buildPParamSerialisation sname fields = do
1130
  let name = mkName sname
1131
  dictdecls <- genDictObject savePParamField loadPParamField sname fields
1132
  savedecls <- genSaveObject sname
1133
  (loadsig, loadfn) <- genLoadObject sname
1134
  shjson <- objectShowJSON sname
1135
  rdjson <- objectReadJSON sname
1136
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
1137
                 [rdjson, shjson]
1138
  return $ dictdecls ++ savedecls ++ [loadsig, loadfn, instdecl]
1139

    
1140
-- | Generates code to save an optional parameter field.
1141
savePParamField :: Name -> Field -> Q Exp
1142
savePParamField fvar field = do
1143
  checkNonOptDef field
1144
  let actualVal = mkName "v"
1145
  normalexpr <- saveObjectField actualVal field
1146
  -- we have to construct the block here manually, because we can't
1147
  -- splice-in-splice
1148
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
1149
                                       (NormalB (ConE '[])) []
1150
                             , Match (ConP 'Just [VarP actualVal])
1151
                                       (NormalB normalexpr) []
1152
                             ]
1153

    
1154
-- | Generates code to load an optional parameter field.
1155
loadPParamField :: Field -> Q Exp
1156
loadPParamField field = do
1157
  checkNonOptDef field
1158
  let name = fieldName field
1159
  -- these are used in all patterns below
1160
  let objvar = varE objVarName
1161
      objfield = stringE name
1162
      loadexp = [| $(varE 'maybeFromObj) $objvar $objfield |]
1163
  loadFnOpt field loadexp objvar
1164

    
1165
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
1166
buildFromMaybe :: String -> Q Dec
1167
buildFromMaybe fname =
1168
  valD (varP (mkName $ "n_" ++ fname))
1169
         (normalB [| $(varE 'fromMaybe)
1170
                        $(varNameE $ "f_" ++ fname)
1171
                        $(varNameE $ "p_" ++ fname) |]) []
1172

    
1173
-- | Builds a function that executes the filling of partial parameter
1174
-- from a full copy (similar to Python's fillDict).
1175
fillParam :: String -> String -> [Field] -> Q [Dec]
1176
fillParam sname field_pfx fields = do
1177
  let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields
1178
      (sname_f, sname_p) = paramTypeNames sname
1179
      oname_f = "fobj"
1180
      oname_p = "pobj"
1181
      name_f = mkName sname_f
1182
      name_p = mkName sname_p
1183
      fun_name = mkName $ "fill" ++ sname ++ "Params"
1184
      le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames))
1185
                (NormalB . VarE . mkName $ oname_f) []
1186
      le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames))
1187
                (NormalB . VarE . mkName $ oname_p) []
1188
      obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f)
1189
                $ map (mkName . ("n_" ++)) fnames
1190
  le_new <- mapM buildFromMaybe fnames
1191
  funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |]
1192
  let sig = SigD fun_name funt
1193
      fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)]
1194
                (NormalB $ LetE (le_full:le_part:le_new) obj_new) []
1195
      fun = FunD fun_name [fclause]
1196
  return [sig, fun]
1197

    
1198
-- * Template code for exceptions
1199

    
1200
-- | Exception simple error message field.
1201
excErrMsg :: (String, Q Type)
1202
excErrMsg = ("errMsg", [t| String |])
1203

    
1204
-- | Builds an exception type definition.
1205
genException :: String                  -- ^ Name of new type
1206
             -> SimpleObject -- ^ Constructor name and parameters
1207
             -> Q [Dec]
1208
genException name cons = do
1209
  let tname = mkName name
1210
  declD <- buildSimpleCons tname cons
1211
  (savesig, savefn) <- genSaveSimpleObj tname ("save" ++ name) cons $
1212
                         uncurry saveExcCons
1213
  (loadsig, loadfn) <- genLoadExc tname ("load" ++ name) cons
1214
  return [declD, loadsig, loadfn, savesig, savefn]
1215

    
1216
-- | Generates the \"save\" clause for an entire exception constructor.
1217
--
1218
-- This matches the exception with variables named the same as the
1219
-- constructor fields (just so that the spliced in code looks nicer),
1220
-- and calls showJSON on it.
1221
saveExcCons :: String        -- ^ The constructor name
1222
            -> [SimpleField] -- ^ The parameter definitions for this
1223
                             -- constructor
1224
            -> Q Clause      -- ^ Resulting clause
1225
saveExcCons sname fields = do
1226
  let cname = mkName sname
1227
  fnames <- mapM (newName . fst) fields
1228
  let pat = conP cname (map varP fnames)
1229
      felems = if null fnames
1230
                 then conE '() -- otherwise, empty list has no type
1231
                 else listE $ map (\f -> [| JSON.showJSON $(varE f) |]) fnames
1232
  let tup = tupE [ litE (stringL sname), felems ]
1233
  clause [pat] (normalB [| JSON.showJSON $tup |]) []
1234

    
1235
-- | Generates load code for a single constructor of an exception.
1236
--
1237
-- Generates the code (if there's only one argument, we will use a
1238
-- list, not a tuple:
1239
--
1240
-- @
1241
-- do
1242
--  (x1, x2, ...) <- readJSON args
1243
--  return $ Cons x1 x2 ...
1244
-- @
1245
loadExcConstructor :: Name -> String -> [SimpleField] -> Q Exp
1246
loadExcConstructor inname sname fields = do
1247
  let name = mkName sname
1248
  f_names <- mapM (newName . fst) fields
1249
  let read_args = AppE (VarE 'JSON.readJSON) (VarE inname)
1250
  let binds = case f_names of
1251
                [x] -> BindS (ListP [VarP x])
1252
                _   -> BindS (TupP (map VarP f_names))
1253
      cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) f_names
1254
  return $ DoE [binds read_args, NoBindS (AppE (VarE 'return) cval)]
1255

    
1256
{-| Generates the loadException function.
1257

    
1258
This generates a quite complicated function, along the lines of:
1259

    
1260
@
1261
loadFn (JSArray [JSString name, args]) = case name of
1262
   "A1" -> do
1263
     (x1, x2, ...) <- readJSON args
1264
     return $ A1 x1 x2 ...
1265
   "a2" -> ...
1266
   s -> fail $ "Unknown exception" ++ s
1267
loadFn v = fail $ "Expected array but got " ++ show v
1268
@
1269
-}
1270
genLoadExc :: Name -> String -> SimpleObject -> Q (Dec, Dec)
1271
genLoadExc tname sname opdefs = do
1272
  let fname = mkName sname
1273
  exc_name <- newName "name"
1274
  exc_args <- newName "args"
1275
  exc_else <- newName "s"
1276
  arg_else <- newName "v"
1277
  fails <- [| fail $ "Unknown exception '" ++ $(varE exc_else) ++ "'" |]
1278
  -- default match for unknown exception name
1279
  let defmatch = Match (VarP exc_else) (NormalB fails) []
1280
  -- the match results (per-constructor blocks)
1281
  str_matches <-
1282
    mapM (\(s, params) -> do
1283
            body_exp <- loadExcConstructor exc_args s params
1284
            return $ Match (LitP (StringL s)) (NormalB body_exp) [])
1285
    opdefs
1286
  -- the first function clause; we can't use [| |] due to TH
1287
  -- limitations, so we have to build the AST by hand
1288
  let clause1 = Clause [ConP 'JSON.JSArray
1289
                               [ListP [ConP 'JSON.JSString [VarP exc_name],
1290
                                            VarP exc_args]]]
1291
                (NormalB (CaseE (AppE (VarE 'JSON.fromJSString)
1292
                                        (VarE exc_name))
1293
                          (str_matches ++ [defmatch]))) []
1294
  -- the fail expression for the second function clause
1295
  fail_type <- [| fail $ "Invalid exception: expected '(string, [args])' " ++
1296
                  "      but got " ++ show (pp_value $(varE arg_else)) ++ "'"
1297
                |]
1298
  -- the second function clause
1299
  let clause2 = Clause [VarP arg_else] (NormalB fail_type) []
1300
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT tname) |]
1301
  return $ (SigD fname sigt, FunD fname [clause1, clause2])