Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ 1c9e817d

History | View | Annotate | Download (46.2 kB)

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