Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 12e8358c

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