Statistics
| Branch: | Tag: | Revision:

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

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