Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH.hs @ 13d26b66

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