Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ b9202225

History | View | Annotate | Download (49.5 kB)

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