Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 014eaaa0

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