Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 94518cdb

History | View | Annotate | Download (28.7 kB)

1 a1505857 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 e9aaa3c6 Iustin Pop
3 e9aaa3c6 Iustin Pop
{-| TemplateHaskell helper for HTools.
4 e9aaa3c6 Iustin Pop
5 e9aaa3c6 Iustin Pop
As TemplateHaskell require that splices be defined in a separate
6 e9aaa3c6 Iustin Pop
module, we combine all the TemplateHaskell functionality that HTools
7 e9aaa3c6 Iustin Pop
needs in this module (except the one for unittests).
8 e9aaa3c6 Iustin Pop
9 e9aaa3c6 Iustin Pop
-}
10 e9aaa3c6 Iustin Pop
11 e9aaa3c6 Iustin Pop
{-
12 e9aaa3c6 Iustin Pop
13 b1e81520 Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
14 e9aaa3c6 Iustin Pop
15 e9aaa3c6 Iustin Pop
This program is free software; you can redistribute it and/or modify
16 e9aaa3c6 Iustin Pop
it under the terms of the GNU General Public License as published by
17 e9aaa3c6 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
18 e9aaa3c6 Iustin Pop
(at your option) any later version.
19 e9aaa3c6 Iustin Pop
20 e9aaa3c6 Iustin Pop
This program is distributed in the hope that it will be useful, but
21 e9aaa3c6 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
22 e9aaa3c6 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
23 e9aaa3c6 Iustin Pop
General Public License for more details.
24 e9aaa3c6 Iustin Pop
25 e9aaa3c6 Iustin Pop
You should have received a copy of the GNU General Public License
26 e9aaa3c6 Iustin Pop
along with this program; if not, write to the Free Software
27 e9aaa3c6 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
28 e9aaa3c6 Iustin Pop
02110-1301, USA.
29 e9aaa3c6 Iustin Pop
30 e9aaa3c6 Iustin Pop
-}
31 e9aaa3c6 Iustin Pop
32 b20cbf06 Iustin Pop
module Ganeti.THH ( declareSADT
33 260d0bda Agata Murawska
                  , declareIADT
34 e9aaa3c6 Iustin Pop
                  , makeJSONInstance
35 6111e296 Iustin Pop
                  , genOpID
36 12c19659 Iustin Pop
                  , genOpCode
37 a0090487 Agata Murawska
                  , genStrOfOp
38 a0090487 Agata Murawska
                  , genStrOfKey
39 a0090487 Agata Murawska
                  , genLuxiOp
40 879273e3 Iustin Pop
                  , Field
41 879273e3 Iustin Pop
                  , simpleField
42 879273e3 Iustin Pop
                  , defaultField
43 879273e3 Iustin Pop
                  , optionalField
44 879273e3 Iustin Pop
                  , renameField
45 879273e3 Iustin Pop
                  , customField
46 879273e3 Iustin Pop
                  , timeStampFields
47 879273e3 Iustin Pop
                  , uuidFields
48 879273e3 Iustin Pop
                  , serialFields
49 02cccecd Iustin Pop
                  , tagsFields
50 879273e3 Iustin Pop
                  , buildObject
51 879273e3 Iustin Pop
                  , buildObjectSerialisation
52 879273e3 Iustin Pop
                  , buildParam
53 e9aaa3c6 Iustin Pop
                  ) where
54 e9aaa3c6 Iustin Pop
55 4b71f30c Iustin Pop
import Control.Monad (liftM)
56 e9aaa3c6 Iustin Pop
import Data.Char
57 6111e296 Iustin Pop
import Data.List
58 02cccecd Iustin Pop
import qualified Data.Set as Set
59 e9aaa3c6 Iustin Pop
import Language.Haskell.TH
60 e9aaa3c6 Iustin Pop
61 e9aaa3c6 Iustin Pop
import qualified Text.JSON as JSON
62 e9aaa3c6 Iustin Pop
63 879273e3 Iustin Pop
-- * Exported types
64 879273e3 Iustin Pop
65 879273e3 Iustin Pop
-- | Serialised field data type.
66 879273e3 Iustin Pop
data Field = Field { fieldName        :: String
67 879273e3 Iustin Pop
                   , fieldType        :: Q Type
68 879273e3 Iustin Pop
                   , fieldRead        :: Maybe (Q Exp)
69 879273e3 Iustin Pop
                   , fieldShow        :: Maybe (Q Exp)
70 879273e3 Iustin Pop
                   , fieldDefault     :: Maybe (Q Exp)
71 879273e3 Iustin Pop
                   , fieldConstr      :: Maybe String
72 879273e3 Iustin Pop
                   , fieldIsOptional  :: Bool
73 879273e3 Iustin Pop
                   }
74 879273e3 Iustin Pop
75 879273e3 Iustin Pop
-- | Generates a simple field.
76 879273e3 Iustin Pop
simpleField :: String -> Q Type -> Field
77 879273e3 Iustin Pop
simpleField fname ftype =
78 879273e3 Iustin Pop
  Field { fieldName        = fname
79 879273e3 Iustin Pop
        , fieldType        = ftype
80 879273e3 Iustin Pop
        , fieldRead        = Nothing
81 879273e3 Iustin Pop
        , fieldShow        = Nothing
82 879273e3 Iustin Pop
        , fieldDefault     = Nothing
83 879273e3 Iustin Pop
        , fieldConstr      = Nothing
84 879273e3 Iustin Pop
        , fieldIsOptional  = False
85 879273e3 Iustin Pop
        }
86 879273e3 Iustin Pop
87 879273e3 Iustin Pop
-- | Sets the renamed constructor field.
88 879273e3 Iustin Pop
renameField :: String -> Field -> Field
89 879273e3 Iustin Pop
renameField constrName field = field { fieldConstr = Just constrName }
90 879273e3 Iustin Pop
91 879273e3 Iustin Pop
-- | Sets the default value on a field (makes it optional with a
92 879273e3 Iustin Pop
-- default value).
93 879273e3 Iustin Pop
defaultField :: Q Exp -> Field -> Field
94 879273e3 Iustin Pop
defaultField defval field = field { fieldDefault = Just defval }
95 879273e3 Iustin Pop
96 879273e3 Iustin Pop
-- | Marks a field optional (turning its base type into a Maybe).
97 879273e3 Iustin Pop
optionalField :: Field -> Field
98 879273e3 Iustin Pop
optionalField field = field { fieldIsOptional = True }
99 879273e3 Iustin Pop
100 879273e3 Iustin Pop
-- | Sets custom functions on a field.
101 c2e60027 Iustin Pop
customField :: Name    -- ^ The name of the read function
102 c2e60027 Iustin Pop
            -> Name    -- ^ The name of the show function
103 c2e60027 Iustin Pop
            -> Field   -- ^ The original field
104 c2e60027 Iustin Pop
            -> Field   -- ^ Updated field
105 879273e3 Iustin Pop
customField readfn showfn field =
106 c2e60027 Iustin Pop
  field { fieldRead = Just (varE readfn), fieldShow = Just (varE showfn) }
107 879273e3 Iustin Pop
108 879273e3 Iustin Pop
fieldRecordName :: Field -> String
109 879273e3 Iustin Pop
fieldRecordName (Field { fieldName = name, fieldConstr = alias }) =
110 879273e3 Iustin Pop
  maybe (camelCase name) id alias
111 879273e3 Iustin Pop
112 a1505857 Iustin Pop
-- | Computes the preferred variable name to use for the value of this
113 a1505857 Iustin Pop
-- field. If the field has a specific constructor name, then we use a
114 a1505857 Iustin Pop
-- first-letter-lowercased version of that; otherwise, we simply use
115 a1505857 Iustin Pop
-- the field name. See also 'fieldRecordName'.
116 879273e3 Iustin Pop
fieldVariable :: Field -> String
117 a1505857 Iustin Pop
fieldVariable f =
118 a1505857 Iustin Pop
  case (fieldConstr f) of
119 a1505857 Iustin Pop
    Just name -> ensureLower name
120 d8cb8e13 Iustin Pop
    _ -> map (\c -> if c == '-' then '_' else c) $ fieldName f
121 879273e3 Iustin Pop
122 879273e3 Iustin Pop
actualFieldType :: Field -> Q Type
123 d5a93a80 Iustin Pop
actualFieldType f | fieldIsOptional f  = [t| Maybe $t     |]
124 879273e3 Iustin Pop
                  | otherwise = t
125 879273e3 Iustin Pop
                  where t = fieldType f
126 879273e3 Iustin Pop
127 879273e3 Iustin Pop
checkNonOptDef :: (Monad m) => Field -> m ()
128 879273e3 Iustin Pop
checkNonOptDef (Field { fieldIsOptional = True, fieldName = name }) =
129 879273e3 Iustin Pop
  fail $ "Optional field " ++ name ++ " used in parameter declaration"
130 879273e3 Iustin Pop
checkNonOptDef (Field { fieldDefault = (Just _), fieldName = name }) =
131 879273e3 Iustin Pop
  fail $ "Default field " ++ name ++ " used in parameter declaration"
132 879273e3 Iustin Pop
checkNonOptDef _ = return ()
133 879273e3 Iustin Pop
134 1c7bda0a Iustin Pop
-- | Produces the expression that will de-serialise a given
135 1c7bda0a Iustin Pop
-- field. Since some custom parsing functions might need to use the
136 1c7bda0a Iustin Pop
-- entire object, we do take and pass the object to any custom read
137 1c7bda0a Iustin Pop
-- functions.
138 1c7bda0a Iustin Pop
loadFn :: Field   -- ^ The field definition
139 1c7bda0a Iustin Pop
       -> Q Exp   -- ^ The value of the field as existing in the JSON message
140 1c7bda0a Iustin Pop
       -> Q Exp   -- ^ The entire object in JSON object format
141 1c7bda0a Iustin Pop
       -> Q Exp   -- ^ Resulting expression
142 1c7bda0a Iustin Pop
loadFn (Field { fieldRead = Just readfn }) expr o = [| $expr >>= $readfn $o |]
143 1c7bda0a Iustin Pop
loadFn _ expr _ = expr
144 879273e3 Iustin Pop
145 879273e3 Iustin Pop
-- * Common field declarations
146 879273e3 Iustin Pop
147 879273e3 Iustin Pop
timeStampFields :: [Field]
148 879273e3 Iustin Pop
timeStampFields =
149 879273e3 Iustin Pop
    [ defaultField [| 0::Double |] $ simpleField "ctime" [t| Double |]
150 879273e3 Iustin Pop
    , defaultField [| 0::Double |] $ simpleField "mtime" [t| Double |]
151 879273e3 Iustin Pop
    ]
152 879273e3 Iustin Pop
153 879273e3 Iustin Pop
serialFields :: [Field]
154 879273e3 Iustin Pop
serialFields =
155 879273e3 Iustin Pop
    [ renameField  "Serial" $ simpleField "serial_no" [t| Int |] ]
156 879273e3 Iustin Pop
157 879273e3 Iustin Pop
uuidFields :: [Field]
158 879273e3 Iustin Pop
uuidFields = [ simpleField "uuid" [t| String |] ]
159 879273e3 Iustin Pop
160 02cccecd Iustin Pop
-- | Tag field description.
161 02cccecd Iustin Pop
tagsFields :: [Field]
162 02cccecd Iustin Pop
tagsFields = [ defaultField [| Set.empty |] $
163 02cccecd Iustin Pop
               simpleField "tags" [t| Set.Set String |] ]
164 02cccecd Iustin Pop
165 53664e15 Iustin Pop
-- * Helper functions
166 53664e15 Iustin Pop
167 e9aaa3c6 Iustin Pop
-- | Ensure first letter is lowercase.
168 e9aaa3c6 Iustin Pop
--
169 e9aaa3c6 Iustin Pop
-- Used to convert type name to function prefix, e.g. in @data Aa ->
170 5f828ce4 Agata Murawska
-- aaToRaw@.
171 e9aaa3c6 Iustin Pop
ensureLower :: String -> String
172 e9aaa3c6 Iustin Pop
ensureLower [] = []
173 e9aaa3c6 Iustin Pop
ensureLower (x:xs) = toLower x:xs
174 e9aaa3c6 Iustin Pop
175 879273e3 Iustin Pop
-- | Ensure first letter is uppercase.
176 879273e3 Iustin Pop
--
177 879273e3 Iustin Pop
-- Used to convert constructor name to component
178 879273e3 Iustin Pop
ensureUpper :: String -> String
179 879273e3 Iustin Pop
ensureUpper [] = []
180 879273e3 Iustin Pop
ensureUpper (x:xs) = toUpper x:xs
181 879273e3 Iustin Pop
182 53664e15 Iustin Pop
-- | Helper for quoted expressions.
183 53664e15 Iustin Pop
varNameE :: String -> Q Exp
184 53664e15 Iustin Pop
varNameE = varE . mkName
185 53664e15 Iustin Pop
186 53664e15 Iustin Pop
-- | showJSON as an expression, for reuse.
187 53664e15 Iustin Pop
showJSONE :: Q Exp
188 53664e15 Iustin Pop
showJSONE = varNameE "showJSON"
189 53664e15 Iustin Pop
190 5f828ce4 Agata Murawska
-- | ToRaw function name.
191 5f828ce4 Agata Murawska
toRawName :: String -> Name
192 5f828ce4 Agata Murawska
toRawName = mkName . (++ "ToRaw") . ensureLower
193 e9aaa3c6 Iustin Pop
194 5f828ce4 Agata Murawska
-- | FromRaw function name.
195 5f828ce4 Agata Murawska
fromRawName :: String -> Name
196 5f828ce4 Agata Murawska
fromRawName = mkName . (++ "FromRaw") . ensureLower
197 260d0bda Agata Murawska
198 6111e296 Iustin Pop
-- | Converts a name to it's varE/litE representations.
199 6111e296 Iustin Pop
--
200 6111e296 Iustin Pop
reprE :: Either String Name -> Q Exp
201 53664e15 Iustin Pop
reprE = either stringE varE
202 53664e15 Iustin Pop
203 60de49c3 Iustin Pop
-- | Smarter function application.
204 60de49c3 Iustin Pop
--
205 60de49c3 Iustin Pop
-- This does simply f x, except that if is 'id', it will skip it, in
206 60de49c3 Iustin Pop
-- order to generate more readable code when using -ddump-splices.
207 60de49c3 Iustin Pop
appFn :: Exp -> Exp -> Exp
208 60de49c3 Iustin Pop
appFn f x | f == VarE 'id = x
209 60de49c3 Iustin Pop
          | otherwise = AppE f x
210 60de49c3 Iustin Pop
211 5f828ce4 Agata Murawska
-- * Template code for simple raw type-equivalent ADTs
212 6111e296 Iustin Pop
213 e9aaa3c6 Iustin Pop
-- | Generates a data type declaration.
214 e9aaa3c6 Iustin Pop
--
215 e9aaa3c6 Iustin Pop
-- The type will have a fixed list of instances.
216 e9aaa3c6 Iustin Pop
strADTDecl :: Name -> [String] -> Dec
217 e9aaa3c6 Iustin Pop
strADTDecl name constructors =
218 ebf38064 Iustin Pop
  DataD [] name []
219 ebf38064 Iustin Pop
          (map (flip NormalC [] . mkName) constructors)
220 ebf38064 Iustin Pop
          [''Show, ''Read, ''Eq, ''Enum, ''Bounded, ''Ord]
221 e9aaa3c6 Iustin Pop
222 5f828ce4 Agata Murawska
-- | Generates a toRaw function.
223 e9aaa3c6 Iustin Pop
--
224 e9aaa3c6 Iustin Pop
-- This generates a simple function of the form:
225 e9aaa3c6 Iustin Pop
--
226 e9aaa3c6 Iustin Pop
-- @
227 5f828ce4 Agata Murawska
-- nameToRaw :: Name -> /traw/
228 5f828ce4 Agata Murawska
-- nameToRaw Cons1 = var1
229 5f828ce4 Agata Murawska
-- nameToRaw Cons2 = \"value2\"
230 e9aaa3c6 Iustin Pop
-- @
231 5f828ce4 Agata Murawska
genToRaw :: Name -> Name -> Name -> [(String, Either String Name)] -> Q [Dec]
232 5f828ce4 Agata Murawska
genToRaw traw fname tname constructors = do
233 d80e3485 Iustin Pop
  let sigt = AppT (AppT ArrowT (ConT tname)) (ConT traw)
234 e9aaa3c6 Iustin Pop
  -- the body clauses, matching on the constructor and returning the
235 5f828ce4 Agata Murawska
  -- raw value
236 e9aaa3c6 Iustin Pop
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
237 6111e296 Iustin Pop
                             (normalB (reprE v)) []) constructors
238 e9aaa3c6 Iustin Pop
  return [SigD fname sigt, FunD fname clauses]
239 e9aaa3c6 Iustin Pop
240 5f828ce4 Agata Murawska
-- | Generates a fromRaw function.
241 e9aaa3c6 Iustin Pop
--
242 e9aaa3c6 Iustin Pop
-- The function generated is monadic and can fail parsing the
243 5f828ce4 Agata Murawska
-- raw value. It is of the form:
244 e9aaa3c6 Iustin Pop
--
245 e9aaa3c6 Iustin Pop
-- @
246 5f828ce4 Agata Murawska
-- nameFromRaw :: (Monad m) => /traw/ -> m Name
247 5f828ce4 Agata Murawska
-- nameFromRaw s | s == var1       = Cons1
248 5f828ce4 Agata Murawska
--               | s == \"value2\" = Cons2
249 5f828ce4 Agata Murawska
--               | otherwise = fail /.../
250 e9aaa3c6 Iustin Pop
-- @
251 5f828ce4 Agata Murawska
genFromRaw :: Name -> Name -> Name -> [(String, Name)] -> Q [Dec]
252 5f828ce4 Agata Murawska
genFromRaw traw fname tname constructors = do
253 e9aaa3c6 Iustin Pop
  -- signature of form (Monad m) => String -> m $name
254 5f828ce4 Agata Murawska
  sigt <- [t| (Monad m) => $(conT traw) -> m $(conT tname) |]
255 e9aaa3c6 Iustin Pop
  -- clauses for a guarded pattern
256 e9aaa3c6 Iustin Pop
  let varp = mkName "s"
257 e9aaa3c6 Iustin Pop
      varpe = varE varp
258 e9aaa3c6 Iustin Pop
  clauses <- mapM (\(c, v) -> do
259 e9aaa3c6 Iustin Pop
                     -- the clause match condition
260 e9aaa3c6 Iustin Pop
                     g <- normalG [| $varpe == $(varE v) |]
261 e9aaa3c6 Iustin Pop
                     -- the clause result
262 e9aaa3c6 Iustin Pop
                     r <- [| return $(conE (mkName c)) |]
263 e9aaa3c6 Iustin Pop
                     return (g, r)) constructors
264 e9aaa3c6 Iustin Pop
  -- the otherwise clause (fallback)
265 e9aaa3c6 Iustin Pop
  oth_clause <- do
266 e9aaa3c6 Iustin Pop
    g <- normalG [| otherwise |]
267 e9aaa3c6 Iustin Pop
    r <- [|fail ("Invalid string value for type " ++
268 5f828ce4 Agata Murawska
                 $(litE (stringL (nameBase tname))) ++ ": " ++ show $varpe) |]
269 e9aaa3c6 Iustin Pop
    return (g, r)
270 e9aaa3c6 Iustin Pop
  let fun = FunD fname [Clause [VarP varp]
271 e9aaa3c6 Iustin Pop
                        (GuardedB (clauses++[oth_clause])) []]
272 e9aaa3c6 Iustin Pop
  return [SigD fname sigt, fun]
273 e9aaa3c6 Iustin Pop
274 5f828ce4 Agata Murawska
-- | Generates a data type from a given raw format.
275 e9aaa3c6 Iustin Pop
--
276 e9aaa3c6 Iustin Pop
-- The format is expected to multiline. The first line contains the
277 e9aaa3c6 Iustin Pop
-- type name, and the rest of the lines must contain two words: the
278 e9aaa3c6 Iustin Pop
-- constructor name and then the string representation of the
279 e9aaa3c6 Iustin Pop
-- respective constructor.
280 e9aaa3c6 Iustin Pop
--
281 e9aaa3c6 Iustin Pop
-- The function will generate the data type declaration, and then two
282 e9aaa3c6 Iustin Pop
-- functions:
283 e9aaa3c6 Iustin Pop
--
284 5f828ce4 Agata Murawska
-- * /name/ToRaw, which converts the type to a raw type
285 e9aaa3c6 Iustin Pop
--
286 5f828ce4 Agata Murawska
-- * /name/FromRaw, which (monadically) converts from a raw type to the type
287 e9aaa3c6 Iustin Pop
--
288 e9aaa3c6 Iustin Pop
-- Note that this is basically just a custom show/read instance,
289 e9aaa3c6 Iustin Pop
-- nothing else.
290 5f828ce4 Agata Murawska
declareADT :: Name -> String -> [(String, Name)] -> Q [Dec]
291 5f828ce4 Agata Murawska
declareADT traw sname cons = do
292 e9aaa3c6 Iustin Pop
  let name = mkName sname
293 e9aaa3c6 Iustin Pop
      ddecl = strADTDecl name (map fst cons)
294 5f828ce4 Agata Murawska
      -- process cons in the format expected by genToRaw
295 6111e296 Iustin Pop
      cons' = map (\(a, b) -> (a, Right b)) cons
296 5f828ce4 Agata Murawska
  toraw <- genToRaw traw (toRawName sname) name cons'
297 5f828ce4 Agata Murawska
  fromraw <- genFromRaw traw (fromRawName sname) name cons
298 5f828ce4 Agata Murawska
  return $ ddecl:toraw ++ fromraw
299 e9aaa3c6 Iustin Pop
300 5f828ce4 Agata Murawska
declareIADT :: String -> [(String, Name)] -> Q [Dec]
301 5f828ce4 Agata Murawska
declareIADT = declareADT ''Int
302 5f828ce4 Agata Murawska
303 5f828ce4 Agata Murawska
declareSADT :: String -> [(String, Name)] -> Q [Dec]
304 5f828ce4 Agata Murawska
declareSADT = declareADT ''String
305 e9aaa3c6 Iustin Pop
306 e9aaa3c6 Iustin Pop
-- | Creates the showJSON member of a JSON instance declaration.
307 e9aaa3c6 Iustin Pop
--
308 e9aaa3c6 Iustin Pop
-- This will create what is the equivalent of:
309 e9aaa3c6 Iustin Pop
--
310 e9aaa3c6 Iustin Pop
-- @
311 5f828ce4 Agata Murawska
-- showJSON = showJSON . /name/ToRaw
312 e9aaa3c6 Iustin Pop
-- @
313 e9aaa3c6 Iustin Pop
--
314 e9aaa3c6 Iustin Pop
-- in an instance JSON /name/ declaration
315 ffbd9592 Iustin Pop
genShowJSON :: String -> Q Dec
316 ffbd9592 Iustin Pop
genShowJSON name = do
317 ffbd9592 Iustin Pop
  body <- [| JSON.showJSON . $(varE (toRawName name)) |]
318 ffbd9592 Iustin Pop
  return $ FunD (mkName "showJSON") [Clause [] (NormalB body) []]
319 e9aaa3c6 Iustin Pop
320 e9aaa3c6 Iustin Pop
-- | Creates the readJSON member of a JSON instance declaration.
321 e9aaa3c6 Iustin Pop
--
322 e9aaa3c6 Iustin Pop
-- This will create what is the equivalent of:
323 e9aaa3c6 Iustin Pop
--
324 e9aaa3c6 Iustin Pop
-- @
325 e9aaa3c6 Iustin Pop
-- readJSON s = case readJSON s of
326 5f828ce4 Agata Murawska
--                Ok s' -> /name/FromRaw s'
327 e9aaa3c6 Iustin Pop
--                Error e -> Error /description/
328 e9aaa3c6 Iustin Pop
-- @
329 e9aaa3c6 Iustin Pop
--
330 e9aaa3c6 Iustin Pop
-- in an instance JSON /name/ declaration
331 e9aaa3c6 Iustin Pop
genReadJSON :: String -> Q Dec
332 e9aaa3c6 Iustin Pop
genReadJSON name = do
333 e9aaa3c6 Iustin Pop
  let s = mkName "s"
334 e9aaa3c6 Iustin Pop
  body <- [| case JSON.readJSON $(varE s) of
335 5f828ce4 Agata Murawska
               JSON.Ok s' -> $(varE (fromRawName name)) s'
336 e9aaa3c6 Iustin Pop
               JSON.Error e ->
337 5f828ce4 Agata Murawska
                   JSON.Error $ "Can't parse raw value for type " ++
338 6bd26f00 Iustin Pop
                           $(stringE name) ++ ": " ++ e ++ " from " ++
339 6bd26f00 Iustin Pop
                           show $(varE s)
340 e9aaa3c6 Iustin Pop
           |]
341 e9aaa3c6 Iustin Pop
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
342 e9aaa3c6 Iustin Pop
343 e9aaa3c6 Iustin Pop
-- | Generates a JSON instance for a given type.
344 e9aaa3c6 Iustin Pop
--
345 5f828ce4 Agata Murawska
-- This assumes that the /name/ToRaw and /name/FromRaw functions
346 e9aaa3c6 Iustin Pop
-- have been defined as by the 'declareSADT' function.
347 e9aaa3c6 Iustin Pop
makeJSONInstance :: Name -> Q [Dec]
348 e9aaa3c6 Iustin Pop
makeJSONInstance name = do
349 e9aaa3c6 Iustin Pop
  let base = nameBase name
350 e9aaa3c6 Iustin Pop
  showJ <- genShowJSON base
351 e9aaa3c6 Iustin Pop
  readJ <- genReadJSON base
352 ffbd9592 Iustin Pop
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) [readJ,showJ]]
353 6111e296 Iustin Pop
354 53664e15 Iustin Pop
-- * Template code for opcodes
355 53664e15 Iustin Pop
356 6111e296 Iustin Pop
-- | Transforms a CamelCase string into an_underscore_based_one.
357 6111e296 Iustin Pop
deCamelCase :: String -> String
358 6111e296 Iustin Pop
deCamelCase =
359 6111e296 Iustin Pop
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
360 6111e296 Iustin Pop
361 879273e3 Iustin Pop
-- | Transform an underscore_name into a CamelCase one.
362 879273e3 Iustin Pop
camelCase :: String -> String
363 879273e3 Iustin Pop
camelCase = concatMap (ensureUpper . drop 1) .
364 d8cb8e13 Iustin Pop
            groupBy (\_ b -> b /= '_' && b /= '-') . ('_':)
365 879273e3 Iustin Pop
366 05ff7a00 Agata Murawska
-- | Computes the name of a given constructor.
367 6111e296 Iustin Pop
constructorName :: Con -> Q Name
368 6111e296 Iustin Pop
constructorName (NormalC name _) = return name
369 6111e296 Iustin Pop
constructorName (RecC name _)    = return name
370 6111e296 Iustin Pop
constructorName x                = fail $ "Unhandled constructor " ++ show x
371 6111e296 Iustin Pop
372 94518cdb Iustin Pop
-- | Extract all constructor names from a given type.
373 94518cdb Iustin Pop
reifyConsNames :: Name -> Q [String]
374 94518cdb Iustin Pop
reifyConsNames name = do
375 94518cdb Iustin Pop
  reify_result <- reify name
376 94518cdb Iustin Pop
  case reify_result of
377 94518cdb Iustin Pop
    TyConI (DataD _ _ _ cons _) -> mapM (liftM nameBase . constructorName) cons
378 94518cdb Iustin Pop
    o -> fail $ "Unhandled name passed to reifyConsNames, expected\
379 94518cdb Iustin Pop
                \ type constructor but got '" ++ show o ++ "'"
380 94518cdb Iustin Pop
381 a0090487 Agata Murawska
-- | Builds the generic constructor-to-string function.
382 6111e296 Iustin Pop
--
383 6111e296 Iustin Pop
-- This generates a simple function of the following form:
384 6111e296 Iustin Pop
--
385 6111e296 Iustin Pop
-- @
386 a0090487 Agata Murawska
-- fname (ConStructorOne {}) = trans_fun("ConStructorOne")
387 a0090487 Agata Murawska
-- fname (ConStructorTwo {}) = trans_fun("ConStructorTwo")
388 6111e296 Iustin Pop
-- @
389 6111e296 Iustin Pop
--
390 6111e296 Iustin Pop
-- This builds a custom list of name/string pairs and then uses
391 5f828ce4 Agata Murawska
-- 'genToRaw' to actually generate the function
392 a0090487 Agata Murawska
genConstrToStr :: (String -> String) -> Name -> String -> Q [Dec]
393 a0090487 Agata Murawska
genConstrToStr trans_fun name fname = do
394 94518cdb Iustin Pop
  cnames <- reifyConsNames name
395 a0090487 Agata Murawska
  let svalues = map (Left . trans_fun) cnames
396 5f828ce4 Agata Murawska
  genToRaw ''String (mkName fname) name $ zip cnames svalues
397 12c19659 Iustin Pop
398 a0090487 Agata Murawska
-- | Constructor-to-string for OpCode.
399 a0090487 Agata Murawska
genOpID :: Name -> String -> Q [Dec]
400 a0090487 Agata Murawska
genOpID = genConstrToStr deCamelCase
401 12c19659 Iustin Pop
402 05ff7a00 Agata Murawska
-- | OpCode parameter (field) type.
403 12c19659 Iustin Pop
type OpParam = (String, Q Type, Q Exp)
404 12c19659 Iustin Pop
405 12c19659 Iustin Pop
-- | Generates the OpCode data type.
406 12c19659 Iustin Pop
--
407 12c19659 Iustin Pop
-- This takes an opcode logical definition, and builds both the
408 12c19659 Iustin Pop
-- datatype and the JSON serialisation out of it. We can't use a
409 12c19659 Iustin Pop
-- generic serialisation since we need to be compatible with Ganeti's
410 12c19659 Iustin Pop
-- own, so we have a few quirks to work around.
411 12c19659 Iustin Pop
genOpCode :: String                -- ^ Type name to use
412 a1505857 Iustin Pop
          -> [(String, [Field])]   -- ^ Constructor name and parameters
413 12c19659 Iustin Pop
          -> Q [Dec]
414 12c19659 Iustin Pop
genOpCode name cons = do
415 12c19659 Iustin Pop
  decl_d <- mapM (\(cname, fields) -> do
416 12c19659 Iustin Pop
                    -- we only need the type of the field, without Q
417 a1505857 Iustin Pop
                    fields' <- mapM actualFieldType fields
418 a1505857 Iustin Pop
                    let fields'' = zip (repeat NotStrict) fields'
419 a1505857 Iustin Pop
                    return $ NormalC (mkName cname) fields'')
420 12c19659 Iustin Pop
            cons
421 12c19659 Iustin Pop
  let declD = DataD [] (mkName name) [] decl_d [''Show, ''Read, ''Eq]
422 12c19659 Iustin Pop
423 12c19659 Iustin Pop
  (savesig, savefn) <- genSaveOpCode cons
424 12c19659 Iustin Pop
  (loadsig, loadfn) <- genLoadOpCode cons
425 12c19659 Iustin Pop
  return [declD, loadsig, loadfn, savesig, savefn]
426 12c19659 Iustin Pop
427 05ff7a00 Agata Murawska
-- | Checks whether a given parameter is options.
428 12c19659 Iustin Pop
--
429 12c19659 Iustin Pop
-- This requires that it's a 'Maybe'.
430 12c19659 Iustin Pop
isOptional :: Type -> Bool
431 12c19659 Iustin Pop
isOptional (AppT (ConT dt) _) | dt == ''Maybe = True
432 12c19659 Iustin Pop
isOptional _ = False
433 12c19659 Iustin Pop
434 12c19659 Iustin Pop
-- | Generates the \"save\" clause for an entire opcode constructor.
435 12c19659 Iustin Pop
--
436 12c19659 Iustin Pop
-- This matches the opcode with variables named the same as the
437 12c19659 Iustin Pop
-- constructor fields (just so that the spliced in code looks nicer),
438 a1505857 Iustin Pop
-- and passes those name plus the parameter definition to 'saveObjectField'.
439 12c19659 Iustin Pop
saveConstructor :: String    -- ^ The constructor name
440 a1505857 Iustin Pop
                -> [Field]   -- ^ The parameter definitions for this
441 12c19659 Iustin Pop
                             -- constructor
442 12c19659 Iustin Pop
                -> Q Clause  -- ^ Resulting clause
443 12c19659 Iustin Pop
saveConstructor sname fields = do
444 12c19659 Iustin Pop
  let cname = mkName sname
445 d8cb8e13 Iustin Pop
  fnames <- mapM (newName . fieldVariable) fields
446 12c19659 Iustin Pop
  let pat = conP cname (map varP fnames)
447 a1505857 Iustin Pop
  let felems = map (uncurry saveObjectField) (zip fnames fields)
448 12c19659 Iustin Pop
      -- now build the OP_ID serialisation
449 53664e15 Iustin Pop
      opid = [| [( $(stringE "OP_ID"),
450 a07343b2 Iustin Pop
                   JSON.showJSON $(stringE . deCamelCase $ sname) )] |]
451 12c19659 Iustin Pop
      flist = listE (opid:felems)
452 12c19659 Iustin Pop
      -- and finally convert all this to a json object
453 53664e15 Iustin Pop
      flist' = [| $(varNameE "makeObj") (concat $flist) |]
454 12c19659 Iustin Pop
  clause [pat] (normalB flist') []
455 12c19659 Iustin Pop
456 12c19659 Iustin Pop
-- | Generates the main save opcode function.
457 12c19659 Iustin Pop
--
458 12c19659 Iustin Pop
-- This builds a per-constructor match clause that contains the
459 12c19659 Iustin Pop
-- respective constructor-serialisation code.
460 a1505857 Iustin Pop
genSaveOpCode :: [(String, [Field])] -> Q (Dec, Dec)
461 12c19659 Iustin Pop
genSaveOpCode opdefs = do
462 12c19659 Iustin Pop
  cclauses <- mapM (uncurry saveConstructor) opdefs
463 12c19659 Iustin Pop
  let fname = mkName "saveOpCode"
464 12c19659 Iustin Pop
  sigt <- [t| $(conT (mkName "OpCode")) -> JSON.JSValue |]
465 12c19659 Iustin Pop
  return $ (SigD fname sigt, FunD fname cclauses)
466 12c19659 Iustin Pop
467 a1505857 Iustin Pop
loadConstructor :: String -> [Field] -> Q Exp
468 12c19659 Iustin Pop
loadConstructor sname fields = do
469 12c19659 Iustin Pop
  let name = mkName sname
470 a1505857 Iustin Pop
  fbinds <- mapM loadObjectField fields
471 12c19659 Iustin Pop
  let (fnames, fstmts) = unzip fbinds
472 12c19659 Iustin Pop
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
473 12c19659 Iustin Pop
      fstmts' = fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
474 12c19659 Iustin Pop
  return $ DoE fstmts'
475 12c19659 Iustin Pop
476 a1505857 Iustin Pop
genLoadOpCode :: [(String, [Field])] -> Q (Dec, Dec)
477 12c19659 Iustin Pop
genLoadOpCode opdefs = do
478 12c19659 Iustin Pop
  let fname = mkName "loadOpCode"
479 12c19659 Iustin Pop
      arg1 = mkName "v"
480 12c19659 Iustin Pop
      objname = mkName "o"
481 12c19659 Iustin Pop
      opid = mkName "op_id"
482 12c19659 Iustin Pop
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
483 12c19659 Iustin Pop
                                 (JSON.readJSON $(varE arg1)) |]
484 53664e15 Iustin Pop
  st2 <- bindS (varP opid) [| $(varNameE "fromObj")
485 53664e15 Iustin Pop
                              $(varE objname) $(stringE "OP_ID") |]
486 12c19659 Iustin Pop
  -- the match results (per-constructor blocks)
487 12c19659 Iustin Pop
  mexps <- mapM (uncurry loadConstructor) opdefs
488 12c19659 Iustin Pop
  fails <- [| fail $ "Unknown opcode " ++ $(varE opid) |]
489 12c19659 Iustin Pop
  let mpats = map (\(me, c) ->
490 12c19659 Iustin Pop
                       let mp = LitP . StringL . deCamelCase . fst $ c
491 12c19659 Iustin Pop
                       in Match mp (NormalB me) []
492 12c19659 Iustin Pop
                  ) $ zip mexps opdefs
493 12c19659 Iustin Pop
      defmatch = Match WildP (NormalB fails) []
494 12c19659 Iustin Pop
      cst = NoBindS $ CaseE (VarE opid) $ mpats++[defmatch]
495 12c19659 Iustin Pop
      body = DoE [st1, st2, cst]
496 12c19659 Iustin Pop
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT (mkName "OpCode")) |]
497 12c19659 Iustin Pop
  return $ (SigD fname sigt, FunD fname [Clause [VarP arg1] (NormalB body) []])
498 12c19659 Iustin Pop
499 a0090487 Agata Murawska
-- * Template code for luxi
500 a0090487 Agata Murawska
501 a0090487 Agata Murawska
-- | Constructor-to-string for LuxiOp.
502 a0090487 Agata Murawska
genStrOfOp :: Name -> String -> Q [Dec]
503 a0090487 Agata Murawska
genStrOfOp = genConstrToStr id
504 a0090487 Agata Murawska
505 a0090487 Agata Murawska
-- | Constructor-to-string for MsgKeys.
506 a0090487 Agata Murawska
genStrOfKey :: Name -> String -> Q [Dec]
507 a0090487 Agata Murawska
genStrOfKey = genConstrToStr ensureLower
508 a0090487 Agata Murawska
509 a0090487 Agata Murawska
-- | LuxiOp parameter type.
510 4b71f30c Iustin Pop
type LuxiParam = (String, Q Type)
511 a0090487 Agata Murawska
512 a0090487 Agata Murawska
-- | Generates the LuxiOp data type.
513 a0090487 Agata Murawska
--
514 a0090487 Agata Murawska
-- This takes a Luxi operation definition and builds both the
515 a0090487 Agata Murawska
-- datatype and the function trnasforming the arguments to JSON.
516 a0090487 Agata Murawska
-- We can't use anything less generic, because the way different
517 a0090487 Agata Murawska
-- operations are serialized differs on both parameter- and top-level.
518 a0090487 Agata Murawska
--
519 4b71f30c Iustin Pop
-- There are two things to be defined for each parameter:
520 a0090487 Agata Murawska
--
521 a0090487 Agata Murawska
-- * name
522 a0090487 Agata Murawska
--
523 a0090487 Agata Murawska
-- * type
524 a0090487 Agata Murawska
--
525 b20cbf06 Iustin Pop
genLuxiOp :: String -> [(String, [LuxiParam])] -> Q [Dec]
526 a0090487 Agata Murawska
genLuxiOp name cons = do
527 b20cbf06 Iustin Pop
  decl_d <- mapM (\(cname, fields) -> do
528 4b71f30c Iustin Pop
                    fields' <- mapM (\(_, qt) ->
529 a0090487 Agata Murawska
                                         qt >>= \t -> return (NotStrict, t))
530 a0090487 Agata Murawska
                               fields
531 a0090487 Agata Murawska
                    return $ NormalC (mkName cname) fields')
532 a0090487 Agata Murawska
            cons
533 cdd495ae Iustin Pop
  let declD = DataD [] (mkName name) [] decl_d [''Show, ''Read, ''Eq]
534 a0090487 Agata Murawska
  (savesig, savefn) <- genSaveLuxiOp cons
535 95d0d502 Iustin Pop
  req_defs <- declareSADT "LuxiReq" .
536 95d0d502 Iustin Pop
              map (\(str, _) -> ("Req" ++ str, mkName ("luxiReq" ++ str))) $
537 95d0d502 Iustin Pop
                  cons
538 95d0d502 Iustin Pop
  return $ [declD, savesig, savefn] ++ req_defs
539 a0090487 Agata Murawska
540 92678b3c Iustin Pop
-- | Generates the \"save\" expression for a single luxi parameter.
541 b20cbf06 Iustin Pop
saveLuxiField :: Name -> LuxiParam -> Q Exp
542 4b71f30c Iustin Pop
saveLuxiField fvar (_, qt) =
543 4b71f30c Iustin Pop
    [| JSON.showJSON $(varE fvar) |]
544 92678b3c Iustin Pop
545 a0090487 Agata Murawska
-- | Generates the \"save\" clause for entire LuxiOp constructor.
546 b20cbf06 Iustin Pop
saveLuxiConstructor :: (String, [LuxiParam]) -> Q Clause
547 b20cbf06 Iustin Pop
saveLuxiConstructor (sname, fields) = do
548 a0090487 Agata Murawska
  let cname = mkName sname
549 4b71f30c Iustin Pop
      fnames = map (mkName . fst) fields
550 a0090487 Agata Murawska
      pat = conP cname (map varP fnames)
551 b20cbf06 Iustin Pop
      flist = map (uncurry saveLuxiField) (zip fnames fields)
552 b20cbf06 Iustin Pop
      finval = if null flist
553 b20cbf06 Iustin Pop
               then [| JSON.showJSON ()    |]
554 b20cbf06 Iustin Pop
               else [| JSON.showJSON $(listE flist) |]
555 92678b3c Iustin Pop
  clause [pat] (normalB finval) []
556 a0090487 Agata Murawska
557 a0090487 Agata Murawska
-- | Generates the main save LuxiOp function.
558 b20cbf06 Iustin Pop
genSaveLuxiOp :: [(String, [LuxiParam])]-> Q (Dec, Dec)
559 a0090487 Agata Murawska
genSaveLuxiOp opdefs = do
560 a0090487 Agata Murawska
  sigt <- [t| $(conT (mkName "LuxiOp")) -> JSON.JSValue |]
561 a0090487 Agata Murawska
  let fname = mkName "opToArgs"
562 a0090487 Agata Murawska
  cclauses <- mapM saveLuxiConstructor opdefs
563 a0090487 Agata Murawska
  return $ (SigD fname sigt, FunD fname cclauses)
564 879273e3 Iustin Pop
565 879273e3 Iustin Pop
-- * "Objects" functionality
566 879273e3 Iustin Pop
567 879273e3 Iustin Pop
-- | Extract the field's declaration from a Field structure.
568 879273e3 Iustin Pop
fieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
569 879273e3 Iustin Pop
fieldTypeInfo field_pfx fd = do
570 879273e3 Iustin Pop
  t <- actualFieldType fd
571 879273e3 Iustin Pop
  let n = mkName . (field_pfx ++) . fieldRecordName $ fd
572 879273e3 Iustin Pop
  return (n, NotStrict, t)
573 879273e3 Iustin Pop
574 879273e3 Iustin Pop
-- | Build an object declaration.
575 879273e3 Iustin Pop
buildObject :: String -> String -> [Field] -> Q [Dec]
576 879273e3 Iustin Pop
buildObject sname field_pfx fields = do
577 879273e3 Iustin Pop
  let name = mkName sname
578 879273e3 Iustin Pop
  fields_d <- mapM (fieldTypeInfo field_pfx) fields
579 879273e3 Iustin Pop
  let decl_d = RecC name fields_d
580 3c3c796e Iustin Pop
  let declD = DataD [] name [] [decl_d] [''Show, ''Read, ''Eq]
581 879273e3 Iustin Pop
  ser_decls <- buildObjectSerialisation sname fields
582 879273e3 Iustin Pop
  return $ declD:ser_decls
583 879273e3 Iustin Pop
584 879273e3 Iustin Pop
buildObjectSerialisation :: String -> [Field] -> Q [Dec]
585 879273e3 Iustin Pop
buildObjectSerialisation sname fields = do
586 879273e3 Iustin Pop
  let name = mkName sname
587 879273e3 Iustin Pop
  savedecls <- genSaveObject saveObjectField sname fields
588 879273e3 Iustin Pop
  (loadsig, loadfn) <- genLoadObject loadObjectField sname fields
589 879273e3 Iustin Pop
  shjson <- objectShowJSON sname
590 879273e3 Iustin Pop
  rdjson <- objectReadJSON sname
591 879273e3 Iustin Pop
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
592 ffbd9592 Iustin Pop
                 [rdjson, shjson]
593 879273e3 Iustin Pop
  return $ savedecls ++ [loadsig, loadfn, instdecl]
594 879273e3 Iustin Pop
595 879273e3 Iustin Pop
genSaveObject :: (Name -> Field -> Q Exp)
596 879273e3 Iustin Pop
              -> String -> [Field] -> Q [Dec]
597 879273e3 Iustin Pop
genSaveObject save_fn sname fields = do
598 879273e3 Iustin Pop
  let name = mkName sname
599 d8cb8e13 Iustin Pop
  fnames <- mapM (newName . fieldVariable) fields
600 879273e3 Iustin Pop
  let pat = conP name (map varP fnames)
601 879273e3 Iustin Pop
  let tdname = mkName ("toDict" ++ sname)
602 879273e3 Iustin Pop
  tdsigt <- [t| $(conT name) -> [(String, JSON.JSValue)] |]
603 879273e3 Iustin Pop
604 879273e3 Iustin Pop
  let felems = map (uncurry save_fn) (zip fnames fields)
605 879273e3 Iustin Pop
      flist = listE felems
606 879273e3 Iustin Pop
      -- and finally convert all this to a json object
607 879273e3 Iustin Pop
      tdlist = [| concat $flist |]
608 879273e3 Iustin Pop
      iname = mkName "i"
609 879273e3 Iustin Pop
  tclause <- clause [pat] (normalB tdlist) []
610 879273e3 Iustin Pop
  cclause <- [| $(varNameE "makeObj") . $(varE tdname) |]
611 879273e3 Iustin Pop
  let fname = mkName ("save" ++ sname)
612 879273e3 Iustin Pop
  sigt <- [t| $(conT name) -> JSON.JSValue |]
613 879273e3 Iustin Pop
  return [SigD tdname tdsigt, FunD tdname [tclause],
614 879273e3 Iustin Pop
          SigD fname sigt, ValD (VarP fname) (NormalB cclause) []]
615 879273e3 Iustin Pop
616 879273e3 Iustin Pop
saveObjectField :: Name -> Field -> Q Exp
617 879273e3 Iustin Pop
saveObjectField fvar field
618 879273e3 Iustin Pop
  | fisOptional = [| case $(varE fvar) of
619 879273e3 Iustin Pop
                      Nothing -> []
620 a07343b2 Iustin Pop
                      Just v -> [( $nameE, JSON.showJSON v)]
621 879273e3 Iustin Pop
                  |]
622 879273e3 Iustin Pop
  | otherwise = case fieldShow field of
623 a07343b2 Iustin Pop
      Nothing -> [| [( $nameE, JSON.showJSON $fvarE)] |]
624 1c7bda0a Iustin Pop
      Just fn -> [| let (actual, extra) = $fn $fvarE
625 1c7bda0a Iustin Pop
                    in extra ++ [( $nameE, JSON.showJSON actual)]
626 1c7bda0a Iustin Pop
                  |]
627 d5a93a80 Iustin Pop
  where fisOptional  = fieldIsOptional field
628 879273e3 Iustin Pop
        nameE = stringE (fieldName field)
629 879273e3 Iustin Pop
        fvarE = varE fvar
630 879273e3 Iustin Pop
631 ffbd9592 Iustin Pop
objectShowJSON :: String -> Q Dec
632 ffbd9592 Iustin Pop
objectShowJSON name = do
633 ffbd9592 Iustin Pop
  body <- [| JSON.showJSON . $(varE . mkName $ "save" ++ name) |]
634 ffbd9592 Iustin Pop
  return $ FunD (mkName "showJSON") [Clause [] (NormalB body) []]
635 879273e3 Iustin Pop
636 879273e3 Iustin Pop
genLoadObject :: (Field -> Q (Name, Stmt))
637 879273e3 Iustin Pop
              -> String -> [Field] -> Q (Dec, Dec)
638 879273e3 Iustin Pop
genLoadObject load_fn sname fields = do
639 879273e3 Iustin Pop
  let name = mkName sname
640 879273e3 Iustin Pop
      funname = mkName $ "load" ++ sname
641 879273e3 Iustin Pop
      arg1 = mkName "v"
642 879273e3 Iustin Pop
      objname = mkName "o"
643 879273e3 Iustin Pop
      opid = mkName "op_id"
644 879273e3 Iustin Pop
  st1 <- bindS (varP objname) [| liftM JSON.fromJSObject
645 879273e3 Iustin Pop
                                 (JSON.readJSON $(varE arg1)) |]
646 879273e3 Iustin Pop
  fbinds <- mapM load_fn fields
647 879273e3 Iustin Pop
  let (fnames, fstmts) = unzip fbinds
648 879273e3 Iustin Pop
  let cval = foldl (\accu fn -> AppE accu (VarE fn)) (ConE name) fnames
649 879273e3 Iustin Pop
      fstmts' = st1:fstmts ++ [NoBindS (AppE (VarE 'return) cval)]
650 879273e3 Iustin Pop
  sigt <- [t| JSON.JSValue -> JSON.Result $(conT name) |]
651 879273e3 Iustin Pop
  return $ (SigD funname sigt,
652 879273e3 Iustin Pop
            FunD funname [Clause [VarP arg1] (NormalB (DoE fstmts')) []])
653 879273e3 Iustin Pop
654 879273e3 Iustin Pop
loadObjectField :: Field -> Q (Name, Stmt)
655 879273e3 Iustin Pop
loadObjectField field = do
656 879273e3 Iustin Pop
  let name = fieldVariable field
657 d8cb8e13 Iustin Pop
  fvar <- newName name
658 879273e3 Iustin Pop
  -- these are used in all patterns below
659 879273e3 Iustin Pop
  let objvar = varNameE "o"
660 879273e3 Iustin Pop
      objfield = stringE (fieldName field)
661 879273e3 Iustin Pop
      loadexp =
662 879273e3 Iustin Pop
        if fieldIsOptional field
663 879273e3 Iustin Pop
          then [| $(varNameE "maybeFromObj") $objvar $objfield |]
664 879273e3 Iustin Pop
          else case fieldDefault field of
665 879273e3 Iustin Pop
                 Just defv ->
666 879273e3 Iustin Pop
                   [| $(varNameE "fromObjWithDefault") $objvar
667 879273e3 Iustin Pop
                      $objfield $defv |]
668 879273e3 Iustin Pop
                 Nothing -> [| $(varNameE "fromObj") $objvar $objfield |]
669 1c7bda0a Iustin Pop
  bexp <- loadFn field loadexp objvar
670 879273e3 Iustin Pop
671 879273e3 Iustin Pop
  return (fvar, BindS (VarP fvar) bexp)
672 879273e3 Iustin Pop
673 879273e3 Iustin Pop
objectReadJSON :: String -> Q Dec
674 879273e3 Iustin Pop
objectReadJSON name = do
675 879273e3 Iustin Pop
  let s = mkName "s"
676 879273e3 Iustin Pop
  body <- [| case JSON.readJSON $(varE s) of
677 879273e3 Iustin Pop
               JSON.Ok s' -> $(varE .mkName $ "load" ++ name) s'
678 879273e3 Iustin Pop
               JSON.Error e ->
679 879273e3 Iustin Pop
                 JSON.Error $ "Can't parse value for type " ++
680 879273e3 Iustin Pop
                       $(stringE name) ++ ": " ++ e
681 879273e3 Iustin Pop
           |]
682 879273e3 Iustin Pop
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
683 879273e3 Iustin Pop
684 879273e3 Iustin Pop
-- * Inheritable parameter tables implementation
685 879273e3 Iustin Pop
686 879273e3 Iustin Pop
-- | Compute parameter type names.
687 879273e3 Iustin Pop
paramTypeNames :: String -> (String, String)
688 879273e3 Iustin Pop
paramTypeNames root = ("Filled"  ++ root ++ "Params",
689 879273e3 Iustin Pop
                       "Partial" ++ root ++ "Params")
690 879273e3 Iustin Pop
691 879273e3 Iustin Pop
-- | Compute information about the type of a parameter field.
692 879273e3 Iustin Pop
paramFieldTypeInfo :: String -> Field -> Q (Name, Strict, Type)
693 879273e3 Iustin Pop
paramFieldTypeInfo field_pfx fd = do
694 879273e3 Iustin Pop
  t <- actualFieldType fd
695 879273e3 Iustin Pop
  let n = mkName . (++ "P") . (field_pfx ++) .
696 879273e3 Iustin Pop
          fieldRecordName $ fd
697 879273e3 Iustin Pop
  return (n, NotStrict, AppT (ConT ''Maybe) t)
698 879273e3 Iustin Pop
699 879273e3 Iustin Pop
-- | Build a parameter declaration.
700 879273e3 Iustin Pop
--
701 879273e3 Iustin Pop
-- This function builds two different data structures: a /filled/ one,
702 879273e3 Iustin Pop
-- in which all fields are required, and a /partial/ one, in which all
703 879273e3 Iustin Pop
-- fields are optional. Due to the current record syntax issues, the
704 879273e3 Iustin Pop
-- fields need to be named differrently for the two structures, so the
705 879273e3 Iustin Pop
-- partial ones get a /P/ suffix.
706 879273e3 Iustin Pop
buildParam :: String -> String -> [Field] -> Q [Dec]
707 879273e3 Iustin Pop
buildParam sname field_pfx fields = do
708 879273e3 Iustin Pop
  let (sname_f, sname_p) = paramTypeNames sname
709 879273e3 Iustin Pop
      name_f = mkName sname_f
710 879273e3 Iustin Pop
      name_p = mkName sname_p
711 879273e3 Iustin Pop
  fields_f <- mapM (fieldTypeInfo field_pfx) fields
712 879273e3 Iustin Pop
  fields_p <- mapM (paramFieldTypeInfo field_pfx) fields
713 879273e3 Iustin Pop
  let decl_f = RecC name_f fields_f
714 879273e3 Iustin Pop
      decl_p = RecC name_p fields_p
715 b1e81520 Iustin Pop
  let declF = DataD [] name_f [] [decl_f] [''Show, ''Read, ''Eq]
716 b1e81520 Iustin Pop
      declP = DataD [] name_p [] [decl_p] [''Show, ''Read, ''Eq]
717 879273e3 Iustin Pop
  ser_decls_f <- buildObjectSerialisation sname_f fields
718 879273e3 Iustin Pop
  ser_decls_p <- buildPParamSerialisation sname_p fields
719 879273e3 Iustin Pop
  fill_decls <- fillParam sname field_pfx fields
720 879273e3 Iustin Pop
  return $ [declF, declP] ++ ser_decls_f ++ ser_decls_p ++ fill_decls
721 879273e3 Iustin Pop
722 879273e3 Iustin Pop
buildPParamSerialisation :: String -> [Field] -> Q [Dec]
723 879273e3 Iustin Pop
buildPParamSerialisation sname fields = do
724 879273e3 Iustin Pop
  let name = mkName sname
725 879273e3 Iustin Pop
  savedecls <- genSaveObject savePParamField sname fields
726 879273e3 Iustin Pop
  (loadsig, loadfn) <- genLoadObject loadPParamField sname fields
727 879273e3 Iustin Pop
  shjson <- objectShowJSON sname
728 879273e3 Iustin Pop
  rdjson <- objectReadJSON sname
729 879273e3 Iustin Pop
  let instdecl = InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name))
730 ffbd9592 Iustin Pop
                 [rdjson, shjson]
731 879273e3 Iustin Pop
  return $ savedecls ++ [loadsig, loadfn, instdecl]
732 879273e3 Iustin Pop
733 879273e3 Iustin Pop
savePParamField :: Name -> Field -> Q Exp
734 879273e3 Iustin Pop
savePParamField fvar field = do
735 879273e3 Iustin Pop
  checkNonOptDef field
736 879273e3 Iustin Pop
  let actualVal = mkName "v"
737 879273e3 Iustin Pop
  normalexpr <- saveObjectField actualVal field
738 879273e3 Iustin Pop
  -- we have to construct the block here manually, because we can't
739 879273e3 Iustin Pop
  -- splice-in-splice
740 879273e3 Iustin Pop
  return $ CaseE (VarE fvar) [ Match (ConP 'Nothing [])
741 879273e3 Iustin Pop
                                       (NormalB (ConE '[])) []
742 879273e3 Iustin Pop
                             , Match (ConP 'Just [VarP actualVal])
743 879273e3 Iustin Pop
                                       (NormalB normalexpr) []
744 879273e3 Iustin Pop
                             ]
745 879273e3 Iustin Pop
loadPParamField :: Field -> Q (Name, Stmt)
746 879273e3 Iustin Pop
loadPParamField field = do
747 879273e3 Iustin Pop
  checkNonOptDef field
748 879273e3 Iustin Pop
  let name = fieldName field
749 d8cb8e13 Iustin Pop
  fvar <- newName name
750 879273e3 Iustin Pop
  -- these are used in all patterns below
751 879273e3 Iustin Pop
  let objvar = varNameE "o"
752 879273e3 Iustin Pop
      objfield = stringE name
753 879273e3 Iustin Pop
      loadexp = [| $(varNameE "maybeFromObj") $objvar $objfield |]
754 1c7bda0a Iustin Pop
  bexp <- loadFn field loadexp objvar
755 879273e3 Iustin Pop
  return (fvar, BindS (VarP fvar) bexp)
756 879273e3 Iustin Pop
757 879273e3 Iustin Pop
-- | Builds a simple declaration of type @n_x = fromMaybe f_x p_x@.
758 879273e3 Iustin Pop
buildFromMaybe :: String -> Q Dec
759 879273e3 Iustin Pop
buildFromMaybe fname =
760 879273e3 Iustin Pop
  valD (varP (mkName $ "n_" ++ fname))
761 879273e3 Iustin Pop
         (normalB [| $(varNameE "fromMaybe")
762 879273e3 Iustin Pop
                        $(varNameE $ "f_" ++ fname)
763 879273e3 Iustin Pop
                        $(varNameE $ "p_" ++ fname) |]) []
764 879273e3 Iustin Pop
765 879273e3 Iustin Pop
fillParam :: String -> String -> [Field] -> Q [Dec]
766 879273e3 Iustin Pop
fillParam sname field_pfx fields = do
767 879273e3 Iustin Pop
  let fnames = map (\fd -> field_pfx ++ fieldRecordName fd) fields
768 879273e3 Iustin Pop
      (sname_f, sname_p) = paramTypeNames sname
769 879273e3 Iustin Pop
      oname_f = "fobj"
770 879273e3 Iustin Pop
      oname_p = "pobj"
771 879273e3 Iustin Pop
      name_f = mkName sname_f
772 879273e3 Iustin Pop
      name_p = mkName sname_p
773 879273e3 Iustin Pop
      fun_name = mkName $ "fill" ++ sname ++ "Params"
774 879273e3 Iustin Pop
      le_full = ValD (ConP name_f (map (VarP . mkName . ("f_" ++)) fnames))
775 879273e3 Iustin Pop
                (NormalB . VarE . mkName $ oname_f) []
776 879273e3 Iustin Pop
      le_part = ValD (ConP name_p (map (VarP . mkName . ("p_" ++)) fnames))
777 879273e3 Iustin Pop
                (NormalB . VarE . mkName $ oname_p) []
778 879273e3 Iustin Pop
      obj_new = foldl (\accu vname -> AppE accu (VarE vname)) (ConE name_f)
779 879273e3 Iustin Pop
                $ map (mkName . ("n_" ++)) fnames
780 879273e3 Iustin Pop
  le_new <- mapM buildFromMaybe fnames
781 879273e3 Iustin Pop
  funt <- [t| $(conT name_f) -> $(conT name_p) -> $(conT name_f) |]
782 879273e3 Iustin Pop
  let sig = SigD fun_name funt
783 879273e3 Iustin Pop
      fclause = Clause [VarP (mkName oname_f), VarP (mkName oname_p)]
784 879273e3 Iustin Pop
                (NormalB $ LetE (le_full:le_part:le_new) obj_new) []
785 879273e3 Iustin Pop
      fun = FunD fun_name [fclause]
786 879273e3 Iustin Pop
  return [sig, fun]