Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 32a569fe

History | View | Annotate | Download (38.8 kB)

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