Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ c92b4671

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