Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 37904802

History | View | Annotate | Download (38.7 kB)

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