Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 885dafbc

History | View | Annotate | Download (12.3 kB)

1 edc1acde Iustin Pop
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
2 daa79414 Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 daa79414 Iustin Pop
4 f047f90f Iustin Pop
{-| JSON utility functions. -}
5 f047f90f Iustin Pop
6 f047f90f Iustin Pop
{-
7 f047f90f Iustin Pop
8 06fb92cf Bernardo Dal Seno
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
9 f047f90f Iustin Pop
10 f047f90f Iustin Pop
This program is free software; you can redistribute it and/or modify
11 f047f90f Iustin Pop
it under the terms of the GNU General Public License as published by
12 f047f90f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
13 f047f90f Iustin Pop
(at your option) any later version.
14 f047f90f Iustin Pop
15 f047f90f Iustin Pop
This program is distributed in the hope that it will be useful, but
16 f047f90f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
17 f047f90f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18 f047f90f Iustin Pop
General Public License for more details.
19 f047f90f Iustin Pop
20 f047f90f Iustin Pop
You should have received a copy of the GNU General Public License
21 f047f90f Iustin Pop
along with this program; if not, write to the Free Software
22 f047f90f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23 f047f90f Iustin Pop
02110-1301, USA.
24 f047f90f Iustin Pop
25 f047f90f Iustin Pop
-}
26 f047f90f Iustin Pop
27 f3baf5ef Iustin Pop
module Ganeti.JSON
28 ebf38064 Iustin Pop
  ( fromJResult
29 964a728f Petr Pudlak
  , fromJResultE
30 885dafbc Petr Pudlak
  , readJSONWithDesc
31 ebf38064 Iustin Pop
  , readEitherString
32 ebf38064 Iustin Pop
  , JSRecord
33 ebf38064 Iustin Pop
  , loadJSArray
34 ebf38064 Iustin Pop
  , fromObj
35 ebf38064 Iustin Pop
  , maybeFromObj
36 ebf38064 Iustin Pop
  , fromObjWithDefault
37 706f7f51 Iustin Pop
  , fromKeyValue
38 ebf38064 Iustin Pop
  , fromJVal
39 964a728f Petr Pudlak
  , fromJValE
40 77cab679 Agata Murawska
  , jsonHead
41 318853ab Iustin Pop
  , getMaybeJsonHead
42 06fb92cf Bernardo Dal Seno
  , getMaybeJsonElem
43 ebf38064 Iustin Pop
  , asJSObject
44 ebf38064 Iustin Pop
  , asObjectList
45 f3f76ccc Iustin Pop
  , tryFromObj
46 0ec8cce2 Bernardo Dal Seno
  , arrayMaybeFromJVal
47 a4f35477 Bernardo Dal Seno
  , tryArrayMaybeFromObj
48 3ad57194 Iustin Pop
  , toArray
49 3c8e6d09 Michele Tartara
  , optionalJSField
50 3c8e6d09 Michele Tartara
  , optFieldsToObj
51 edc1acde Iustin Pop
  , HasStringRepr(..)
52 edc1acde Iustin Pop
  , GenericContainer(..)
53 edc1acde Iustin Pop
  , Container
54 88b58ed6 Hrvoje Ribicic
  , MaybeForJSON(..)
55 5ea9f6cb Petr Pudlak
  , TimeAsDoubleJSON(..)
56 ebf38064 Iustin Pop
  )
57 ebf38064 Iustin Pop
  where
58 f047f90f Iustin Pop
59 daa79414 Iustin Pop
import Control.DeepSeq
60 f047f90f Iustin Pop
import Control.Monad (liftM)
61 964a728f Petr Pudlak
import Control.Monad.Error.Class
62 3c8e6d09 Michele Tartara
import Data.Maybe (fromMaybe, catMaybes)
63 84835174 Iustin Pop
import qualified Data.Map as Map
64 5ea9f6cb Petr Pudlak
import System.Time (ClockTime(..))
65 f047f90f Iustin Pop
import Text.Printf (printf)
66 f047f90f Iustin Pop
67 f047f90f Iustin Pop
import qualified Text.JSON as J
68 c12a68e2 Iustin Pop
import Text.JSON.Pretty (pp_value)
69 f047f90f Iustin Pop
70 32a569fe Iustin Pop
-- Note: this module should not import any Ganeti-specific modules
71 32a569fe Iustin Pop
-- beside BasicTypes, since it's used in THH which is used itself to
72 32a569fe Iustin Pop
-- build many other modules.
73 32a569fe Iustin Pop
74 f3f76ccc Iustin Pop
import Ganeti.BasicTypes
75 f3f76ccc Iustin Pop
76 f047f90f Iustin Pop
-- * JSON-related functions
77 f047f90f Iustin Pop
78 daa79414 Iustin Pop
instance NFData J.JSValue where
79 daa79414 Iustin Pop
  rnf J.JSNull           = ()
80 daa79414 Iustin Pop
  rnf (J.JSBool b)       = rnf b
81 daa79414 Iustin Pop
  rnf (J.JSRational b r) = rnf b `seq` rnf r
82 daa79414 Iustin Pop
  rnf (J.JSString s)     = rnf $ J.fromJSString s
83 daa79414 Iustin Pop
  rnf (J.JSArray a)      = rnf a
84 daa79414 Iustin Pop
  rnf (J.JSObject o)     = rnf o
85 daa79414 Iustin Pop
86 daa79414 Iustin Pop
instance (NFData a) => NFData (J.JSObject a) where
87 daa79414 Iustin Pop
  rnf = rnf . J.fromJSObject
88 daa79414 Iustin Pop
89 3c8e6d09 Michele Tartara
-- | A type alias for a field of a JSRecord.
90 3c8e6d09 Michele Tartara
type JSField = (String, J.JSValue)
91 3c8e6d09 Michele Tartara
92 f047f90f Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
93 3c8e6d09 Michele Tartara
type JSRecord = [JSField]
94 f047f90f Iustin Pop
95 885dafbc Petr Pudlak
-- | Annotate @readJSON@ error messages with descriptions of what
96 885dafbc Petr Pudlak
-- is being parsed into what.
97 885dafbc Petr Pudlak
readJSONWithDesc :: (J.JSON a)
98 885dafbc Petr Pudlak
                 => String                    -- ^ description of @a@
99 885dafbc Petr Pudlak
                 -> Bool                      -- ^ include input in
100 885dafbc Petr Pudlak
                                              --   error messages
101 885dafbc Petr Pudlak
                 -> J.JSValue                 -- ^ input value
102 885dafbc Petr Pudlak
                 -> J.Result a
103 885dafbc Petr Pudlak
readJSONWithDesc typ incInput input =
104 885dafbc Petr Pudlak
  case J.readJSON input of
105 885dafbc Petr Pudlak
    J.Ok r    -> J.Ok r
106 885dafbc Petr Pudlak
    J.Error e -> J.Error $ if incInput then msg ++ " from " ++ show input
107 885dafbc Petr Pudlak
                                       else msg
108 885dafbc Petr Pudlak
      where msg = "Can't parse value for type " ++ typ ++ ": " ++ e
109 885dafbc Petr Pudlak
110 f047f90f Iustin Pop
-- | Converts a JSON Result into a monadic value.
111 f047f90f Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
112 f047f90f Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
113 f047f90f Iustin Pop
fromJResult _ (J.Ok x) = return x
114 f047f90f Iustin Pop
115 964a728f Petr Pudlak
-- | Converts a JSON Result into a MonadError value.
116 964a728f Petr Pudlak
fromJResultE :: (Error e, MonadError e m) => String -> J.Result a -> m a
117 964a728f Petr Pudlak
fromJResultE s (J.Error x) = throwError . strMsg $ s ++ ": " ++ x
118 964a728f Petr Pudlak
fromJResultE _ (J.Ok x) = return x
119 964a728f Petr Pudlak
120 f047f90f Iustin Pop
-- | Tries to read a string from a JSON value.
121 f047f90f Iustin Pop
--
122 f047f90f Iustin Pop
-- In case the value was not a string, we fail the read (in the
123 f047f90f Iustin Pop
-- context of the current monad.
124 f047f90f Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
125 f047f90f Iustin Pop
readEitherString v =
126 ebf38064 Iustin Pop
  case v of
127 ebf38064 Iustin Pop
    J.JSString s -> return $ J.fromJSString s
128 ebf38064 Iustin Pop
    _ -> fail "Wrong JSON type"
129 f047f90f Iustin Pop
130 f047f90f Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
131 f047f90f Iustin Pop
loadJSArray :: (Monad m)
132 f047f90f Iustin Pop
               => String -- ^ Operation description (for error reporting)
133 f047f90f Iustin Pop
               -> String -- ^ Input message
134 f047f90f Iustin Pop
               -> m [J.JSObject J.JSValue]
135 f047f90f Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
136 f047f90f Iustin Pop
137 a4f35477 Bernardo Dal Seno
-- | Helper function for missing-key errors
138 a4f35477 Bernardo Dal Seno
buildNoKeyError :: JSRecord -> String -> String
139 a4f35477 Bernardo Dal Seno
buildNoKeyError o k =
140 a4f35477 Bernardo Dal Seno
  printf "key '%s' not found, object contains only %s" k (show (map fst o))
141 a4f35477 Bernardo Dal Seno
142 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object.
143 f047f90f Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
144 f047f90f Iustin Pop
fromObj o k =
145 ebf38064 Iustin Pop
  case lookup k o of
146 a4f35477 Bernardo Dal Seno
    Nothing -> fail $ buildNoKeyError o k
147 ebf38064 Iustin Pop
    Just val -> fromKeyValue k val
148 f047f90f Iustin Pop
149 f2f06e2e Iustin Pop
-- | Reads the value of an optional key in a JSON object. Missing
150 f2f06e2e Iustin Pop
-- keys, or keys that have a \'null\' value, will be returned as
151 f2f06e2e Iustin Pop
-- 'Nothing', otherwise we attempt deserialisation and return a 'Just'
152 f2f06e2e Iustin Pop
-- value.
153 f047f90f Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
154 f047f90f Iustin Pop
                JSRecord -> String -> m (Maybe a)
155 f047f90f Iustin Pop
maybeFromObj o k =
156 ebf38064 Iustin Pop
  case lookup k o of
157 ebf38064 Iustin Pop
    Nothing -> return Nothing
158 f2f06e2e Iustin Pop
    -- a optional key with value JSNull is the same as missing, since
159 f2f06e2e Iustin Pop
    -- we can't convert it meaningfully anyway to a Haskell type, and
160 f2f06e2e Iustin Pop
    -- the Python code can emit 'null' for optional values (depending
161 f2f06e2e Iustin Pop
    -- on usage), and finally our encoding rules treat 'null' values
162 f2f06e2e Iustin Pop
    -- as 'missing'
163 f2f06e2e Iustin Pop
    Just J.JSNull -> return Nothing
164 ebf38064 Iustin Pop
    Just val -> liftM Just (fromKeyValue k val)
165 f047f90f Iustin Pop
166 f2f06e2e Iustin Pop
-- | Reads the value of a key in a JSON object with a default if
167 f2f06e2e Iustin Pop
-- missing. Note that both missing keys and keys with value \'null\'
168 2f3d7a50 Jose A. Lopes
-- will cause the default value to be returned.
169 f047f90f Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
170 f047f90f Iustin Pop
                      JSRecord -> String -> a -> m a
171 f047f90f Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
172 f047f90f Iustin Pop
173 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal :: (J.JSON a, Monad m) => J.JSValue -> m [Maybe a]
174 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal (J.JSArray xs) =
175 0ec8cce2 Bernardo Dal Seno
  mapM parse xs
176 0ec8cce2 Bernardo Dal Seno
    where
177 0ec8cce2 Bernardo Dal Seno
      parse J.JSNull = return Nothing
178 0ec8cce2 Bernardo Dal Seno
      parse x = liftM Just $ fromJVal x
179 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal v =
180 0ec8cce2 Bernardo Dal Seno
  fail $ "Expecting array, got '" ++ show (pp_value v) ++ "'"
181 0ec8cce2 Bernardo Dal Seno
182 a4f35477 Bernardo Dal Seno
-- | Reads an array of optional items
183 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj :: (J.JSON a, Monad m) =>
184 a4f35477 Bernardo Dal Seno
                     JSRecord -> String -> m [Maybe a]
185 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj o k =
186 a4f35477 Bernardo Dal Seno
  case lookup k o of
187 0ec8cce2 Bernardo Dal Seno
    Just a -> arrayMaybeFromJVal a
188 a4f35477 Bernardo Dal Seno
    _ -> fail $ buildNoKeyError o k
189 a4f35477 Bernardo Dal Seno
190 a4f35477 Bernardo Dal Seno
-- | Wrapper for arrayMaybeFromObj with better diagnostic
191 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj :: (J.JSON a)
192 a4f35477 Bernardo Dal Seno
                     => String     -- ^ Textual "owner" in error messages
193 a4f35477 Bernardo Dal Seno
                     -> JSRecord   -- ^ The object array
194 a4f35477 Bernardo Dal Seno
                     -> String     -- ^ The desired key from the object
195 a4f35477 Bernardo Dal Seno
                     -> Result [Maybe a]
196 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj t o = annotateResult t . arrayMaybeFromObj o
197 a4f35477 Bernardo Dal Seno
198 f047f90f Iustin Pop
-- | Reads a JValue, that originated from an object key.
199 f047f90f Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
200 f047f90f Iustin Pop
              => String     -- ^ The key name
201 f047f90f Iustin Pop
              -> J.JSValue  -- ^ The value to read
202 f047f90f Iustin Pop
              -> m a
203 f047f90f Iustin Pop
fromKeyValue k val =
204 706f7f51 Iustin Pop
  fromJResult (printf "key '%s'" k) (J.readJSON val)
205 f047f90f Iustin Pop
206 f047f90f Iustin Pop
-- | Small wrapper over readJSON.
207 f047f90f Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
208 f047f90f Iustin Pop
fromJVal v =
209 ebf38064 Iustin Pop
  case J.readJSON v of
210 c12a68e2 Iustin Pop
    J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++
211 ebf38064 Iustin Pop
                       "', error: " ++ s)
212 ebf38064 Iustin Pop
    J.Ok x -> return x
213 f047f90f Iustin Pop
214 964a728f Petr Pudlak
-- | Small wrapper over 'readJSON' for 'MonadError'.
215 964a728f Petr Pudlak
fromJValE :: (Error e, MonadError e m, J.JSON a) => J.JSValue -> m a
216 964a728f Petr Pudlak
fromJValE v =
217 964a728f Petr Pudlak
  case J.readJSON v of
218 964a728f Petr Pudlak
    J.Error s -> throwError . strMsg $
219 964a728f Petr Pudlak
                  "Cannot convert value '" ++ show (pp_value v) ++
220 964a728f Petr Pudlak
                  "', error: " ++ s
221 964a728f Petr Pudlak
    J.Ok x -> return x
222 964a728f Petr Pudlak
223 77cab679 Agata Murawska
-- | Helper function that returns Null or first element of the list.
224 77cab679 Agata Murawska
jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue
225 77cab679 Agata Murawska
jsonHead [] _ = J.JSNull
226 77cab679 Agata Murawska
jsonHead (x:_) f = J.showJSON $ f x
227 77cab679 Agata Murawska
228 318853ab Iustin Pop
-- | Helper for extracting Maybe values from a possibly empty list.
229 318853ab Iustin Pop
getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue
230 318853ab Iustin Pop
getMaybeJsonHead [] _ = J.JSNull
231 318853ab Iustin Pop
getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x)
232 318853ab Iustin Pop
233 06fb92cf Bernardo Dal Seno
-- | Helper for extracting Maybe values from a list that might be too short.
234 06fb92cf Bernardo Dal Seno
getMaybeJsonElem :: (J.JSON b) => [a] -> Int -> (a -> Maybe b) -> J.JSValue
235 06fb92cf Bernardo Dal Seno
getMaybeJsonElem [] _ _ = J.JSNull
236 06fb92cf Bernardo Dal Seno
getMaybeJsonElem xs 0 f = getMaybeJsonHead xs f
237 06fb92cf Bernardo Dal Seno
getMaybeJsonElem (_:xs) n f
238 06fb92cf Bernardo Dal Seno
  | n < 0 = J.JSNull
239 06fb92cf Bernardo Dal Seno
  | otherwise = getMaybeJsonElem xs (n - 1) f
240 06fb92cf Bernardo Dal Seno
241 f047f90f Iustin Pop
-- | Converts a JSON value into a JSON object.
242 f047f90f Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
243 f047f90f Iustin Pop
asJSObject (J.JSObject a) = return a
244 f047f90f Iustin Pop
asJSObject _ = fail "not an object"
245 f047f90f Iustin Pop
246 f047f90f Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
247 f047f90f Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
248 f047f90f Iustin Pop
asObjectList = mapM asJSObject
249 f3f76ccc Iustin Pop
250 7209d304 Klaus Aehlig
-- | Try to extract a key from an object with better error reporting
251 f3f76ccc Iustin Pop
-- than fromObj.
252 f3f76ccc Iustin Pop
tryFromObj :: (J.JSON a) =>
253 f3f76ccc Iustin Pop
              String     -- ^ Textual "owner" in error messages
254 f3f76ccc Iustin Pop
           -> JSRecord   -- ^ The object array
255 f3f76ccc Iustin Pop
           -> String     -- ^ The desired key from the object
256 f3f76ccc Iustin Pop
           -> Result a
257 f3f76ccc Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
258 3ad57194 Iustin Pop
259 3ad57194 Iustin Pop
-- | Ensure a given JSValue is actually a JSArray.
260 3ad57194 Iustin Pop
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
261 3ad57194 Iustin Pop
toArray (J.JSArray arr) = return arr
262 c12a68e2 Iustin Pop
toArray o =
263 c12a68e2 Iustin Pop
  fail $ "Invalid input, expected array but got " ++ show (pp_value o)
264 84835174 Iustin Pop
265 3c8e6d09 Michele Tartara
-- | Creates a Maybe JSField. If the value string is Nothing, the JSField
266 3c8e6d09 Michele Tartara
-- will be Nothing as well.
267 3c8e6d09 Michele Tartara
optionalJSField :: (J.JSON a) => String -> Maybe a -> Maybe JSField
268 3c8e6d09 Michele Tartara
optionalJSField name (Just value) = Just (name, J.showJSON value)
269 3c8e6d09 Michele Tartara
optionalJSField _ Nothing = Nothing
270 3c8e6d09 Michele Tartara
271 3c8e6d09 Michele Tartara
-- | Creates an object with all the non-Nothing fields of the given list.
272 3c8e6d09 Michele Tartara
optFieldsToObj :: [Maybe JSField] -> J.JSValue
273 3c8e6d09 Michele Tartara
optFieldsToObj = J.makeObj . catMaybes
274 3c8e6d09 Michele Tartara
275 84835174 Iustin Pop
-- * Container type (special type for JSON serialisation)
276 84835174 Iustin Pop
277 edc1acde Iustin Pop
-- | Class of types that can be converted from Strings. This is
278 edc1acde Iustin Pop
-- similar to the 'Read' class, but it's using a different
279 edc1acde Iustin Pop
-- serialisation format, so we have to define a separate class. Mostly
280 edc1acde Iustin Pop
-- useful for custom key types in JSON dictionaries, which have to be
281 edc1acde Iustin Pop
-- backed by strings.
282 edc1acde Iustin Pop
class HasStringRepr a where
283 edc1acde Iustin Pop
  fromStringRepr :: (Monad m) => String -> m a
284 edc1acde Iustin Pop
  toStringRepr :: a -> String
285 edc1acde Iustin Pop
286 edc1acde Iustin Pop
-- | Trivial instance 'HasStringRepr' for 'String'.
287 edc1acde Iustin Pop
instance HasStringRepr String where
288 edc1acde Iustin Pop
  fromStringRepr = return
289 edc1acde Iustin Pop
  toStringRepr = id
290 edc1acde Iustin Pop
291 84835174 Iustin Pop
-- | The container type, a wrapper over Data.Map
292 edc1acde Iustin Pop
newtype GenericContainer a b =
293 edc1acde Iustin Pop
  GenericContainer { fromContainer :: Map.Map a b }
294 139c0683 Iustin Pop
  deriving (Show, Eq)
295 84835174 Iustin Pop
296 daa79414 Iustin Pop
instance (NFData a, NFData b) => NFData (GenericContainer a b) where
297 daa79414 Iustin Pop
  rnf = rnf . Map.toList . fromContainer
298 daa79414 Iustin Pop
299 edc1acde Iustin Pop
-- | Type alias for string keys.
300 edc1acde Iustin Pop
type Container = GenericContainer String
301 edc1acde Iustin Pop
302 84835174 Iustin Pop
-- | Container loader.
303 edc1acde Iustin Pop
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
304 edc1acde Iustin Pop
                 J.JSObject J.JSValue -> m (GenericContainer a b)
305 84835174 Iustin Pop
readContainer obj = do
306 84835174 Iustin Pop
  let kjvlist = J.fromJSObject obj
307 edc1acde Iustin Pop
  kalist <- mapM (\(k, v) -> do
308 edc1acde Iustin Pop
                    k' <- fromStringRepr k
309 edc1acde Iustin Pop
                    v' <- fromKeyValue k v
310 edc1acde Iustin Pop
                    return (k', v')) kjvlist
311 edc1acde Iustin Pop
  return $ GenericContainer (Map.fromList kalist)
312 84835174 Iustin Pop
313 417ab39c Iustin Pop
{-# ANN showContainer "HLint: ignore Use ***" #-}
314 84835174 Iustin Pop
-- | Container dumper.
315 edc1acde Iustin Pop
showContainer :: (HasStringRepr a, J.JSON b) =>
316 edc1acde Iustin Pop
                 GenericContainer a b -> J.JSValue
317 84835174 Iustin Pop
showContainer =
318 edc1acde Iustin Pop
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
319 edc1acde Iustin Pop
  Map.toList . fromContainer
320 84835174 Iustin Pop
321 edc1acde Iustin Pop
instance (HasStringRepr a, Ord a, J.JSON b) =>
322 edc1acde Iustin Pop
         J.JSON (GenericContainer a b) where
323 84835174 Iustin Pop
  showJSON = showContainer
324 84835174 Iustin Pop
  readJSON (J.JSObject o) = readContainer o
325 84835174 Iustin Pop
  readJSON v = fail $ "Failed to load container, expected object but got "
326 c12a68e2 Iustin Pop
               ++ show (pp_value v)
327 88b58ed6 Hrvoje Ribicic
328 88b58ed6 Hrvoje Ribicic
-- | A Maybe newtype that allows for serialization more appropriate to the
329 88b58ed6 Hrvoje Ribicic
-- semantics of Maybe and JSON in our calls. Does not produce needless
330 88b58ed6 Hrvoje Ribicic
-- and confusing dictionaries.
331 88b58ed6 Hrvoje Ribicic
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
332 6879dfd2 Petr Pudlak
  deriving (Show, Eq, Ord)
333 88b58ed6 Hrvoje Ribicic
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
334 6879dfd2 Petr Pudlak
  readJSON J.JSNull = return $ MaybeForJSON Nothing
335 6879dfd2 Petr Pudlak
  readJSON x        = (MaybeForJSON . Just) `liftM` J.readJSON x
336 88b58ed6 Hrvoje Ribicic
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
337 88b58ed6 Hrvoje Ribicic
  showJSON (MaybeForJSON Nothing)  = J.JSNull
338 5ea9f6cb Petr Pudlak
339 5ea9f6cb Petr Pudlak
newtype TimeAsDoubleJSON
340 5ea9f6cb Petr Pudlak
    = TimeAsDoubleJSON { unTimeAsDoubleJSON :: ClockTime }
341 5ea9f6cb Petr Pudlak
  deriving (Show, Eq, Ord)
342 5ea9f6cb Petr Pudlak
instance J.JSON TimeAsDoubleJSON where
343 5ea9f6cb Petr Pudlak
  readJSON v = do
344 5ea9f6cb Petr Pudlak
      t <- J.readJSON v :: J.Result Double
345 5ea9f6cb Petr Pudlak
      return . TimeAsDoubleJSON . uncurry TOD
346 5ea9f6cb Petr Pudlak
             $ divMod (round $ t * pico) (pico :: Integer)
347 5ea9f6cb Petr Pudlak
    where
348 5ea9f6cb Petr Pudlak
      pico :: (Num a) => a
349 5ea9f6cb Petr Pudlak
      pico = 10^(12 :: Int)
350 5ea9f6cb Petr Pudlak
  showJSON (TimeAsDoubleJSON (TOD ss ps)) = J.showJSON
351 5ea9f6cb Petr Pudlak
      (fromIntegral ss + fromIntegral ps / 10^(12 :: Int) :: Double)