Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 557f5dad

History | View | Annotate | Download (10.9 kB)

1
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| JSON utility functions. -}
5

    
6
{-
7

    
8
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
9

    
10
This program is free software; you can redistribute it and/or modify
11
it under the terms of the GNU General Public License as published by
12
the Free Software Foundation; either version 2 of the License, or
13
(at your option) any later version.
14

    
15
This program is distributed in the hope that it will be useful, but
16
WITHOUT ANY WARRANTY; without even the implied warranty of
17
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
General Public License for more details.
19

    
20
You should have received a copy of the GNU General Public License
21
along with this program; if not, write to the Free Software
22
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23
02110-1301, USA.
24

    
25
-}
26

    
27
module Ganeti.JSON
28
  ( fromJResult
29
  , fromJResultE
30
  , readEitherString
31
  , JSRecord
32
  , loadJSArray
33
  , fromObj
34
  , maybeFromObj
35
  , fromObjWithDefault
36
  , fromKeyValue
37
  , fromJVal
38
  , fromJValE
39
  , jsonHead
40
  , getMaybeJsonHead
41
  , getMaybeJsonElem
42
  , asJSObject
43
  , asObjectList
44
  , tryFromObj
45
  , arrayMaybeFromJVal
46
  , tryArrayMaybeFromObj
47
  , toArray
48
  , optionalJSField
49
  , optFieldsToObj
50
  , HasStringRepr(..)
51
  , GenericContainer(..)
52
  , Container
53
  , MaybeForJSON(..)
54
  )
55
  where
56

    
57
import Control.DeepSeq
58
import Control.Monad (liftM)
59
import Control.Monad.Error.Class
60
import Data.Maybe (fromMaybe, catMaybes)
61
import qualified Data.Map as Map
62
import Text.Printf (printf)
63

    
64
import qualified Text.JSON as J
65
import Text.JSON.Pretty (pp_value)
66

    
67
-- Note: this module should not import any Ganeti-specific modules
68
-- beside BasicTypes, since it's used in THH which is used itself to
69
-- build many other modules.
70

    
71
import Ganeti.BasicTypes
72

    
73
-- * JSON-related functions
74

    
75
instance NFData J.JSValue where
76
  rnf J.JSNull           = ()
77
  rnf (J.JSBool b)       = rnf b
78
  rnf (J.JSRational b r) = rnf b `seq` rnf r
79
  rnf (J.JSString s)     = rnf $ J.fromJSString s
80
  rnf (J.JSArray a)      = rnf a
81
  rnf (J.JSObject o)     = rnf o
82

    
83
instance (NFData a) => NFData (J.JSObject a) where
84
  rnf = rnf . J.fromJSObject
85

    
86
-- | A type alias for a field of a JSRecord.
87
type JSField = (String, J.JSValue)
88

    
89
-- | A type alias for the list-based representation of J.JSObject.
90
type JSRecord = [JSField]
91

    
92
-- | Converts a JSON Result into a monadic value.
93
fromJResult :: Monad m => String -> J.Result a -> m a
94
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
95
fromJResult _ (J.Ok x) = return x
96

    
97
-- | Converts a JSON Result into a MonadError value.
98
fromJResultE :: (Error e, MonadError e m) => String -> J.Result a -> m a
99
fromJResultE s (J.Error x) = throwError . strMsg $ s ++ ": " ++ x
100
fromJResultE _ (J.Ok x) = return x
101

    
102
-- | Tries to read a string from a JSON value.
103
--
104
-- In case the value was not a string, we fail the read (in the
105
-- context of the current monad.
106
readEitherString :: (Monad m) => J.JSValue -> m String
107
readEitherString v =
108
  case v of
109
    J.JSString s -> return $ J.fromJSString s
110
    _ -> fail "Wrong JSON type"
111

    
112
-- | Converts a JSON message into an array of JSON objects.
113
loadJSArray :: (Monad m)
114
               => String -- ^ Operation description (for error reporting)
115
               -> String -- ^ Input message
116
               -> m [J.JSObject J.JSValue]
117
loadJSArray s = fromJResult s . J.decodeStrict
118

    
119
-- | Helper function for missing-key errors
120
buildNoKeyError :: JSRecord -> String -> String
121
buildNoKeyError o k =
122
  printf "key '%s' not found, object contains only %s" k (show (map fst o))
123

    
124
-- | Reads the value of a key in a JSON object.
125
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
126
fromObj o k =
127
  case lookup k o of
128
    Nothing -> fail $ buildNoKeyError o k
129
    Just val -> fromKeyValue k val
130

    
131
-- | Reads the value of an optional key in a JSON object. Missing
132
-- keys, or keys that have a \'null\' value, will be returned as
133
-- 'Nothing', otherwise we attempt deserialisation and return a 'Just'
134
-- value.
135
maybeFromObj :: (J.JSON a, Monad m) =>
136
                JSRecord -> String -> m (Maybe a)
137
maybeFromObj o k =
138
  case lookup k o of
139
    Nothing -> return Nothing
140
    -- a optional key with value JSNull is the same as missing, since
141
    -- we can't convert it meaningfully anyway to a Haskell type, and
142
    -- the Python code can emit 'null' for optional values (depending
143
    -- on usage), and finally our encoding rules treat 'null' values
144
    -- as 'missing'
145
    Just J.JSNull -> return Nothing
146
    Just val -> liftM Just (fromKeyValue k val)
147

    
148
-- | Reads the value of a key in a JSON object with a default if
149
-- missing. Note that both missing keys and keys with value \'null\'
150
-- will cause the default value to be returned.
151
fromObjWithDefault :: (J.JSON a, Monad m) =>
152
                      JSRecord -> String -> a -> m a
153
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
154

    
155
arrayMaybeFromJVal :: (J.JSON a, Monad m) => J.JSValue -> m [Maybe a]
156
arrayMaybeFromJVal (J.JSArray xs) =
157
  mapM parse xs
158
    where
159
      parse J.JSNull = return Nothing
160
      parse x = liftM Just $ fromJVal x
161
arrayMaybeFromJVal v =
162
  fail $ "Expecting array, got '" ++ show (pp_value v) ++ "'"
163

    
164
-- | Reads an array of optional items
165
arrayMaybeFromObj :: (J.JSON a, Monad m) =>
166
                     JSRecord -> String -> m [Maybe a]
167
arrayMaybeFromObj o k =
168
  case lookup k o of
169
    Just a -> arrayMaybeFromJVal a
170
    _ -> fail $ buildNoKeyError o k
171

    
172
-- | Wrapper for arrayMaybeFromObj with better diagnostic
173
tryArrayMaybeFromObj :: (J.JSON a)
174
                     => String     -- ^ Textual "owner" in error messages
175
                     -> JSRecord   -- ^ The object array
176
                     -> String     -- ^ The desired key from the object
177
                     -> Result [Maybe a]
178
tryArrayMaybeFromObj t o = annotateResult t . arrayMaybeFromObj o
179

    
180
-- | Reads a JValue, that originated from an object key.
181
fromKeyValue :: (J.JSON a, Monad m)
182
              => String     -- ^ The key name
183
              -> J.JSValue  -- ^ The value to read
184
              -> m a
185
fromKeyValue k val =
186
  fromJResult (printf "key '%s'" k) (J.readJSON val)
187

    
188
-- | Small wrapper over readJSON.
189
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
190
fromJVal v =
191
  case J.readJSON v of
192
    J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++
193
                       "', error: " ++ s)
194
    J.Ok x -> return x
195

    
196
-- | Small wrapper over 'readJSON' for 'MonadError'.
197
fromJValE :: (Error e, MonadError e m, J.JSON a) => J.JSValue -> m a
198
fromJValE v =
199
  case J.readJSON v of
200
    J.Error s -> throwError . strMsg $
201
                  "Cannot convert value '" ++ show (pp_value v) ++
202
                  "', error: " ++ s
203
    J.Ok x -> return x
204

    
205
-- | Helper function that returns Null or first element of the list.
206
jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue
207
jsonHead [] _ = J.JSNull
208
jsonHead (x:_) f = J.showJSON $ f x
209

    
210
-- | Helper for extracting Maybe values from a possibly empty list.
211
getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue
212
getMaybeJsonHead [] _ = J.JSNull
213
getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x)
214

    
215
-- | Helper for extracting Maybe values from a list that might be too short.
216
getMaybeJsonElem :: (J.JSON b) => [a] -> Int -> (a -> Maybe b) -> J.JSValue
217
getMaybeJsonElem [] _ _ = J.JSNull
218
getMaybeJsonElem xs 0 f = getMaybeJsonHead xs f
219
getMaybeJsonElem (_:xs) n f
220
  | n < 0 = J.JSNull
221
  | otherwise = getMaybeJsonElem xs (n - 1) f
222

    
223
-- | Converts a JSON value into a JSON object.
224
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
225
asJSObject (J.JSObject a) = return a
226
asJSObject _ = fail "not an object"
227

    
228
-- | Coneverts a list of JSON values into a list of JSON objects.
229
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
230
asObjectList = mapM asJSObject
231

    
232
-- | Try to extract a key from an object with better error reporting
233
-- than fromObj.
234
tryFromObj :: (J.JSON a) =>
235
              String     -- ^ Textual "owner" in error messages
236
           -> JSRecord   -- ^ The object array
237
           -> String     -- ^ The desired key from the object
238
           -> Result a
239
tryFromObj t o = annotateResult t . fromObj o
240

    
241
-- | Ensure a given JSValue is actually a JSArray.
242
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
243
toArray (J.JSArray arr) = return arr
244
toArray o =
245
  fail $ "Invalid input, expected array but got " ++ show (pp_value o)
246

    
247
-- | Creates a Maybe JSField. If the value string is Nothing, the JSField
248
-- will be Nothing as well.
249
optionalJSField :: (J.JSON a) => String -> Maybe a -> Maybe JSField
250
optionalJSField name (Just value) = Just (name, J.showJSON value)
251
optionalJSField _ Nothing = Nothing
252

    
253
-- | Creates an object with all the non-Nothing fields of the given list.
254
optFieldsToObj :: [Maybe JSField] -> J.JSValue
255
optFieldsToObj = J.makeObj . catMaybes
256

    
257
-- * Container type (special type for JSON serialisation)
258

    
259
-- | Class of types that can be converted from Strings. This is
260
-- similar to the 'Read' class, but it's using a different
261
-- serialisation format, so we have to define a separate class. Mostly
262
-- useful for custom key types in JSON dictionaries, which have to be
263
-- backed by strings.
264
class HasStringRepr a where
265
  fromStringRepr :: (Monad m) => String -> m a
266
  toStringRepr :: a -> String
267

    
268
-- | Trivial instance 'HasStringRepr' for 'String'.
269
instance HasStringRepr String where
270
  fromStringRepr = return
271
  toStringRepr = id
272

    
273
-- | The container type, a wrapper over Data.Map
274
newtype GenericContainer a b =
275
  GenericContainer { fromContainer :: Map.Map a b }
276
  deriving (Show, Eq)
277

    
278
instance (NFData a, NFData b) => NFData (GenericContainer a b) where
279
  rnf = rnf . Map.toList . fromContainer
280

    
281
-- | Type alias for string keys.
282
type Container = GenericContainer String
283

    
284
-- | Container loader.
285
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
286
                 J.JSObject J.JSValue -> m (GenericContainer a b)
287
readContainer obj = do
288
  let kjvlist = J.fromJSObject obj
289
  kalist <- mapM (\(k, v) -> do
290
                    k' <- fromStringRepr k
291
                    v' <- fromKeyValue k v
292
                    return (k', v')) kjvlist
293
  return $ GenericContainer (Map.fromList kalist)
294

    
295
{-# ANN showContainer "HLint: ignore Use ***" #-}
296
-- | Container dumper.
297
showContainer :: (HasStringRepr a, J.JSON b) =>
298
                 GenericContainer a b -> J.JSValue
299
showContainer =
300
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
301
  Map.toList . fromContainer
302

    
303
instance (HasStringRepr a, Ord a, J.JSON b) =>
304
         J.JSON (GenericContainer a b) where
305
  showJSON = showContainer
306
  readJSON (J.JSObject o) = readContainer o
307
  readJSON v = fail $ "Failed to load container, expected object but got "
308
               ++ show (pp_value v)
309

    
310
-- | A Maybe newtype that allows for serialization more appropriate to the
311
-- semantics of Maybe and JSON in our calls. Does not produce needless
312
-- and confusing dictionaries.
313
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
314
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
315
  readJSON = J.readJSON
316
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
317
  showJSON (MaybeForJSON Nothing)  = J.JSNull