Statistics
| Branch: | Tag: | Revision:

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

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