Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ 45f75526

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