Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 13d26b66

History | View | Annotate | Download (12.3 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
  , HasStringRepr(..)
53
  , GenericContainer(..)
54
  , Container
55
  , MaybeForJSON(..)
56
  , TimeAsDoubleJSON(..)
57
  )
58
  where
59

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

    
68
import qualified Text.JSON as J
69
import Text.JSON.Pretty (pp_value)
70

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

    
75
import Ganeti.BasicTypes
76

    
77
-- * JSON-related functions
78

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

    
87
instance (NFData a) => NFData (J.JSObject a) where
88
  rnf = rnf . J.fromJSObject
89

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
276
-- * Container type (special type for JSON serialisation)
277

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

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

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

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

    
300
-- | Type alias for string keys.
301
type Container = GenericContainer String
302

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

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

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

    
329
-- | A Maybe newtype that allows for serialization more appropriate to the
330
-- semantics of Maybe and JSON in our calls. Does not produce needless
331
-- and confusing dictionaries.
332
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
333
  deriving (Show, Eq, Ord)
334
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
335
  readJSON J.JSNull = return $ MaybeForJSON Nothing
336
  readJSON x        = (MaybeForJSON . Just) `liftM` J.readJSON x
337
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
338
  showJSON (MaybeForJSON Nothing)  = J.JSNull
339

    
340
newtype TimeAsDoubleJSON
341
    = TimeAsDoubleJSON { unTimeAsDoubleJSON :: ClockTime }
342
  deriving (Show, Eq, Ord)
343
instance J.JSON TimeAsDoubleJSON where
344
  readJSON v = do
345
      t <- J.readJSON v :: J.Result Double
346
      return . TimeAsDoubleJSON . uncurry TOD
347
             $ divMod (round $ t * pico) (pico :: Integer)
348
    where
349
      pico :: (Num a) => a
350
      pico = 10^(12 :: Int)
351
  showJSON (TimeAsDoubleJSON (TOD ss ps)) = J.showJSON
352
      (fromIntegral ss + fromIntegral ps / 10^(12 :: Int) :: Double)