Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ 8aab74e9

History | View | Annotate | Download (47.6 kB)

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