Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 9faf1c01

History | View | Annotate | Download (13.2 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 qualified Data.Foldable as F
66
import qualified Data.Traversable as F
67
import Data.Maybe (fromMaybe, catMaybes)
68
import qualified Data.Map as Map
69
import System.Time (ClockTime(..))
70
import Text.Printf (printf)
71

    
72
import qualified Text.JSON as J
73
import Text.JSON.Pretty (pp_value)
74

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

    
79
import Ganeti.BasicTypes
80

    
81
-- * JSON-related functions
82

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

    
91
instance (NFData a) => NFData (J.JSObject a) where
92
  rnf = rnf . J.fromJSObject
93

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
280
-- * Container type (special type for JSON serialisation)
281

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

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

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

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

    
304
instance Functor (GenericContainer a) where
305
  fmap f = GenericContainer . fmap f . fromContainer
306

    
307
instance F.Foldable (GenericContainer a) where
308
  foldMap f = F.foldMap f . fromContainer
309

    
310
instance F.Traversable (GenericContainer a) where
311
  traverse f = fmap GenericContainer . F.traverse f . fromContainer
312

    
313
-- | Type alias for string keys.
314
type Container = GenericContainer String
315

    
316
-- | Container loader.
317
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
318
                 J.JSObject J.JSValue -> m (GenericContainer a b)
319
readContainer obj = do
320
  let kjvlist = J.fromJSObject obj
321
  kalist <- mapM (\(k, v) -> do
322
                    k' <- fromStringRepr k
323
                    v' <- fromKeyValue k v
324
                    return (k', v')) kjvlist
325
  return $ GenericContainer (Map.fromList kalist)
326

    
327
{-# ANN showContainer "HLint: ignore Use ***" #-}
328
-- | Container dumper.
329
showContainer :: (HasStringRepr a, J.JSON b) =>
330
                 GenericContainer a b -> J.JSValue
331
showContainer =
332
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
333
  Map.toList . fromContainer
334

    
335
instance (HasStringRepr a, Ord a, J.JSON b) =>
336
         J.JSON (GenericContainer a b) where
337
  showJSON = showContainer
338
  readJSON (J.JSObject o) = readContainer o
339
  readJSON v = fail $ "Failed to load container, expected object but got "
340
               ++ show (pp_value v)
341

    
342
-- * Types that (de)serialize in a special form of JSON
343

    
344
-- | Class of objects that can be converted from and to 'JSObject'
345
-- lists-format.
346
class DictObject a where
347
  toDict :: a -> [(String, J.JSValue)]
348
  fromDict :: [(String, J.JSValue)] -> J.Result a
349

    
350
-- | Class of objects that can be converted from and to @[JSValue]@ with
351
-- a fixed length and order.
352
class ArrayObject a where
353
  toJSArray :: a -> [J.JSValue]
354
  fromJSArray :: [J.JSValue] -> J.Result a
355

    
356
-- * General purpose data types for working with JSON
357

    
358
-- | A Maybe newtype that allows for serialization more appropriate to the
359
-- semantics of Maybe and JSON in our calls. Does not produce needless
360
-- and confusing dictionaries.
361
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
362
  deriving (Show, Eq, Ord)
363
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
364
  readJSON J.JSNull = return $ MaybeForJSON Nothing
365
  readJSON x        = (MaybeForJSON . Just) `liftM` J.readJSON x
366
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
367
  showJSON (MaybeForJSON Nothing)  = J.JSNull
368

    
369
newtype TimeAsDoubleJSON
370
    = TimeAsDoubleJSON { unTimeAsDoubleJSON :: ClockTime }
371
  deriving (Show, Eq, Ord)
372
instance J.JSON TimeAsDoubleJSON where
373
  readJSON v = do
374
      t <- J.readJSON v :: J.Result Double
375
      return . TimeAsDoubleJSON . uncurry TOD
376
             $ divMod (round $ t * pico) (pico :: Integer)
377
    where
378
      pico :: (Num a) => a
379
      pico = 10^(12 :: Int)
380
  showJSON (TimeAsDoubleJSON (TOD ss ps)) = J.showJSON
381
      (fromIntegral ss + fromIntegral ps / 10^(12 :: Int) :: Double)