Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 26e32dee

History | View | Annotate | Download (12.8 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
  , readJSONWithDesc
31
  , readEitherString
32
  , JSRecord
33
  , loadJSArray
34
  , fromObj
35
  , maybeFromObj
36
  , fromObjWithDefault
37
  , fromKeyValue
38
  , fromJVal
39
  , fromJValE
40
  , jsonHead
41
  , getMaybeJsonHead
42
  , getMaybeJsonElem
43
  , asJSObject
44
  , asObjectList
45
  , tryFromObj
46
  , arrayMaybeFromJVal
47
  , tryArrayMaybeFromObj
48
  , toArray
49
  , optionalJSField
50
  , optFieldsToObj
51
  , readContainer
52
  , DictObject(..)
53
  , ArrayObject(..)
54
  , HasStringRepr(..)
55
  , GenericContainer(..)
56
  , Container
57
  , MaybeForJSON(..)
58
  , TimeAsDoubleJSON(..)
59
  )
60
  where
61

    
62
import Control.DeepSeq
63
import Control.Monad (liftM)
64
import Control.Monad.Error.Class
65
import Data.Maybe (fromMaybe, catMaybes)
66
import qualified Data.Map as Map
67
import System.Time (ClockTime(..))
68
import Text.Printf (printf)
69

    
70
import qualified Text.JSON as J
71
import Text.JSON.Pretty (pp_value)
72

    
73
-- Note: this module should not import any Ganeti-specific modules
74
-- beside BasicTypes, since it's used in THH which is used itself to
75
-- build many other modules.
76

    
77
import Ganeti.BasicTypes
78

    
79
-- * JSON-related functions
80

    
81
instance NFData J.JSValue where
82
  rnf J.JSNull           = ()
83
  rnf (J.JSBool b)       = rnf b
84
  rnf (J.JSRational b r) = rnf b `seq` rnf r
85
  rnf (J.JSString s)     = rnf $ J.fromJSString s
86
  rnf (J.JSArray a)      = rnf a
87
  rnf (J.JSObject o)     = rnf o
88

    
89
instance (NFData a) => NFData (J.JSObject a) where
90
  rnf = rnf . J.fromJSObject
91

    
92
-- | A type alias for a field of a JSRecord.
93
type JSField = (String, J.JSValue)
94

    
95
-- | A type alias for the list-based representation of J.JSObject.
96
type JSRecord = [JSField]
97

    
98
-- | Annotate @readJSON@ error messages with descriptions of what
99
-- is being parsed into what.
100
readJSONWithDesc :: (J.JSON a)
101
                 => String                    -- ^ description of @a@
102
                 -> Bool                      -- ^ include input in
103
                                              --   error messages
104
                 -> J.JSValue                 -- ^ input value
105
                 -> J.Result a
106
readJSONWithDesc typ incInput input =
107
  case J.readJSON input of
108
    J.Ok r    -> J.Ok r
109
    J.Error e -> J.Error $ if incInput then msg ++ " from " ++ show input
110
                                       else msg
111
      where msg = "Can't parse value for type " ++ typ ++ ": " ++ e
112

    
113
-- | Converts a JSON Result into a monadic value.
114
fromJResult :: Monad m => String -> J.Result a -> m a
115
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
116
fromJResult _ (J.Ok x) = return x
117

    
118
-- | Converts a JSON Result into a MonadError value.
119
fromJResultE :: (Error e, MonadError e m) => String -> J.Result a -> m a
120
fromJResultE s (J.Error x) = throwError . strMsg $ s ++ ": " ++ x
121
fromJResultE _ (J.Ok x) = return x
122

    
123
-- | Tries to read a string from a JSON value.
124
--
125
-- In case the value was not a string, we fail the read (in the
126
-- context of the current monad.
127
readEitherString :: (Monad m) => J.JSValue -> m String
128
readEitherString v =
129
  case v of
130
    J.JSString s -> return $ J.fromJSString s
131
    _ -> fail "Wrong JSON type"
132

    
133
-- | Converts a JSON message into an array of JSON objects.
134
loadJSArray :: (Monad m)
135
               => String -- ^ Operation description (for error reporting)
136
               -> String -- ^ Input message
137
               -> m [J.JSObject J.JSValue]
138
loadJSArray s = fromJResult s . J.decodeStrict
139

    
140
-- | Helper function for missing-key errors
141
buildNoKeyError :: JSRecord -> String -> String
142
buildNoKeyError o k =
143
  printf "key '%s' not found, object contains only %s" k (show (map fst o))
144

    
145
-- | Reads the value of a key in a JSON object.
146
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
147
fromObj o k =
148
  case lookup k o of
149
    Nothing -> fail $ buildNoKeyError o k
150
    Just val -> fromKeyValue k val
151

    
152
-- | Reads the value of an optional key in a JSON object. Missing
153
-- keys, or keys that have a \'null\' value, will be returned as
154
-- 'Nothing', otherwise we attempt deserialisation and return a 'Just'
155
-- value.
156
maybeFromObj :: (J.JSON a, Monad m) =>
157
                JSRecord -> String -> m (Maybe a)
158
maybeFromObj o k =
159
  case lookup k o of
160
    Nothing -> return Nothing
161
    -- a optional key with value JSNull is the same as missing, since
162
    -- we can't convert it meaningfully anyway to a Haskell type, and
163
    -- the Python code can emit 'null' for optional values (depending
164
    -- on usage), and finally our encoding rules treat 'null' values
165
    -- as 'missing'
166
    Just J.JSNull -> return Nothing
167
    Just val -> liftM Just (fromKeyValue k val)
168

    
169
-- | Reads the value of a key in a JSON object with a default if
170
-- missing. Note that both missing keys and keys with value \'null\'
171
-- will cause the default value to be returned.
172
fromObjWithDefault :: (J.JSON a, Monad m) =>
173
                      JSRecord -> String -> a -> m a
174
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
175

    
176
arrayMaybeFromJVal :: (J.JSON a, Monad m) => J.JSValue -> m [Maybe a]
177
arrayMaybeFromJVal (J.JSArray xs) =
178
  mapM parse xs
179
    where
180
      parse J.JSNull = return Nothing
181
      parse x = liftM Just $ fromJVal x
182
arrayMaybeFromJVal v =
183
  fail $ "Expecting array, got '" ++ show (pp_value v) ++ "'"
184

    
185
-- | Reads an array of optional items
186
arrayMaybeFromObj :: (J.JSON a, Monad m) =>
187
                     JSRecord -> String -> m [Maybe a]
188
arrayMaybeFromObj o k =
189
  case lookup k o of
190
    Just a -> arrayMaybeFromJVal a
191
    _ -> fail $ buildNoKeyError o k
192

    
193
-- | Wrapper for arrayMaybeFromObj with better diagnostic
194
tryArrayMaybeFromObj :: (J.JSON a)
195
                     => String     -- ^ Textual "owner" in error messages
196
                     -> JSRecord   -- ^ The object array
197
                     -> String     -- ^ The desired key from the object
198
                     -> Result [Maybe a]
199
tryArrayMaybeFromObj t o = annotateResult t . arrayMaybeFromObj o
200

    
201
-- | Reads a JValue, that originated from an object key.
202
fromKeyValue :: (J.JSON a, Monad m)
203
              => String     -- ^ The key name
204
              -> J.JSValue  -- ^ The value to read
205
              -> m a
206
fromKeyValue k val =
207
  fromJResult (printf "key '%s'" k) (J.readJSON val)
208

    
209
-- | Small wrapper over readJSON.
210
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
211
fromJVal v =
212
  case J.readJSON v of
213
    J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++
214
                       "', error: " ++ s)
215
    J.Ok x -> return x
216

    
217
-- | Small wrapper over 'readJSON' for 'MonadError'.
218
fromJValE :: (Error e, MonadError e m, J.JSON a) => J.JSValue -> m a
219
fromJValE v =
220
  case J.readJSON v of
221
    J.Error s -> throwError . strMsg $
222
                  "Cannot convert value '" ++ show (pp_value v) ++
223
                  "', error: " ++ s
224
    J.Ok x -> return x
225

    
226
-- | Helper function that returns Null or first element of the list.
227
jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue
228
jsonHead [] _ = J.JSNull
229
jsonHead (x:_) f = J.showJSON $ f x
230

    
231
-- | Helper for extracting Maybe values from a possibly empty list.
232
getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue
233
getMaybeJsonHead [] _ = J.JSNull
234
getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x)
235

    
236
-- | Helper for extracting Maybe values from a list that might be too short.
237
getMaybeJsonElem :: (J.JSON b) => [a] -> Int -> (a -> Maybe b) -> J.JSValue
238
getMaybeJsonElem [] _ _ = J.JSNull
239
getMaybeJsonElem xs 0 f = getMaybeJsonHead xs f
240
getMaybeJsonElem (_:xs) n f
241
  | n < 0 = J.JSNull
242
  | otherwise = getMaybeJsonElem xs (n - 1) f
243

    
244
-- | Converts a JSON value into a JSON object.
245
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
246
asJSObject (J.JSObject a) = return a
247
asJSObject _ = fail "not an object"
248

    
249
-- | Coneverts a list of JSON values into a list of JSON objects.
250
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
251
asObjectList = mapM asJSObject
252

    
253
-- | Try to extract a key from an object with better error reporting
254
-- than fromObj.
255
tryFromObj :: (J.JSON a) =>
256
              String     -- ^ Textual "owner" in error messages
257
           -> JSRecord   -- ^ The object array
258
           -> String     -- ^ The desired key from the object
259
           -> Result a
260
tryFromObj t o = annotateResult t . fromObj o
261

    
262
-- | Ensure a given JSValue is actually a JSArray.
263
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
264
toArray (J.JSArray arr) = return arr
265
toArray o =
266
  fail $ "Invalid input, expected array but got " ++ show (pp_value o)
267

    
268
-- | Creates a Maybe JSField. If the value string is Nothing, the JSField
269
-- will be Nothing as well.
270
optionalJSField :: (J.JSON a) => String -> Maybe a -> Maybe JSField
271
optionalJSField name (Just value) = Just (name, J.showJSON value)
272
optionalJSField _ Nothing = Nothing
273

    
274
-- | Creates an object with all the non-Nothing fields of the given list.
275
optFieldsToObj :: [Maybe JSField] -> J.JSValue
276
optFieldsToObj = J.makeObj . catMaybes
277

    
278
-- * Container type (special type for JSON serialisation)
279

    
280
-- | Class of types that can be converted from Strings. This is
281
-- similar to the 'Read' class, but it's using a different
282
-- serialisation format, so we have to define a separate class. Mostly
283
-- useful for custom key types in JSON dictionaries, which have to be
284
-- backed by strings.
285
class HasStringRepr a where
286
  fromStringRepr :: (Monad m) => String -> m a
287
  toStringRepr :: a -> String
288

    
289
-- | Trivial instance 'HasStringRepr' for 'String'.
290
instance HasStringRepr String where
291
  fromStringRepr = return
292
  toStringRepr = id
293

    
294
-- | The container type, a wrapper over Data.Map
295
newtype GenericContainer a b =
296
  GenericContainer { fromContainer :: Map.Map a b }
297
  deriving (Show, Eq)
298

    
299
instance (NFData a, NFData b) => NFData (GenericContainer a b) where
300
  rnf = rnf . Map.toList . fromContainer
301

    
302
-- | Type alias for string keys.
303
type Container = GenericContainer String
304

    
305
-- | Container loader.
306
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
307
                 J.JSObject J.JSValue -> m (GenericContainer a b)
308
readContainer obj = do
309
  let kjvlist = J.fromJSObject obj
310
  kalist <- mapM (\(k, v) -> do
311
                    k' <- fromStringRepr k
312
                    v' <- fromKeyValue k v
313
                    return (k', v')) kjvlist
314
  return $ GenericContainer (Map.fromList kalist)
315

    
316
{-# ANN showContainer "HLint: ignore Use ***" #-}
317
-- | Container dumper.
318
showContainer :: (HasStringRepr a, J.JSON b) =>
319
                 GenericContainer a b -> J.JSValue
320
showContainer =
321
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
322
  Map.toList . fromContainer
323

    
324
instance (HasStringRepr a, Ord a, J.JSON b) =>
325
         J.JSON (GenericContainer a b) where
326
  showJSON = showContainer
327
  readJSON (J.JSObject o) = readContainer o
328
  readJSON v = fail $ "Failed to load container, expected object but got "
329
               ++ show (pp_value v)
330

    
331
-- * Types that (de)serialize in a special form of JSON
332

    
333
-- | Class of objects that can be converted from and to 'JSObject'
334
-- lists-format.
335
class DictObject a where
336
  toDict :: a -> [(String, J.JSValue)]
337
  fromDict :: [(String, J.JSValue)] -> J.Result a
338

    
339
-- | Class of objects that can be converted from and to @[JSValue]@ with
340
-- a fixed length and order.
341
class ArrayObject a where
342
  toJSArray :: a -> [J.JSValue]
343
  fromJSArray :: [J.JSValue] -> J.Result a
344

    
345
-- * General purpose data types for working with JSON
346

    
347
-- | A Maybe newtype that allows for serialization more appropriate to the
348
-- semantics of Maybe and JSON in our calls. Does not produce needless
349
-- and confusing dictionaries.
350
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
351
  deriving (Show, Eq, Ord)
352
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
353
  readJSON J.JSNull = return $ MaybeForJSON Nothing
354
  readJSON x        = (MaybeForJSON . Just) `liftM` J.readJSON x
355
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
356
  showJSON (MaybeForJSON Nothing)  = J.JSNull
357

    
358
newtype TimeAsDoubleJSON
359
    = TimeAsDoubleJSON { unTimeAsDoubleJSON :: ClockTime }
360
  deriving (Show, Eq, Ord)
361
instance J.JSON TimeAsDoubleJSON where
362
  readJSON v = do
363
      t <- J.readJSON v :: J.Result Double
364
      return . TimeAsDoubleJSON . uncurry TOD
365
             $ divMod (round $ t * pico) (pico :: Integer)
366
    where
367
      pico :: (Num a) => a
368
      pico = 10^(12 :: Int)
369
  showJSON (TimeAsDoubleJSON (TOD ss ps)) = J.showJSON
370
      (fromIntegral ss + fromIntegral ps / 10^(12 :: Int) :: Double)