Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 5ea9f6cb

History | View | Annotate | Download (11.5 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
  , TimeAsDoubleJSON(..)
55
  )
56
  where
57

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

    
66
import qualified Text.JSON as J
67
import Text.JSON.Pretty (pp_value)
68

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

    
73
import Ganeti.BasicTypes
74

    
75
-- * JSON-related functions
76

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

    
85
instance (NFData a) => NFData (J.JSObject a) where
86
  rnf = rnf . J.fromJSObject
87

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
259
-- * Container type (special type for JSON serialisation)
260

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

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

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

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

    
283
-- | Type alias for string keys.
284
type Container = GenericContainer String
285

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

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

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

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

    
321
newtype TimeAsDoubleJSON
322
    = TimeAsDoubleJSON { unTimeAsDoubleJSON :: ClockTime }
323
  deriving (Show, Eq, Ord)
324
instance J.JSON TimeAsDoubleJSON where
325
  readJSON v = do
326
      t <- J.readJSON v :: J.Result Double
327
      return . TimeAsDoubleJSON . uncurry TOD
328
             $ divMod (round $ t * pico) (pico :: Integer)
329
    where
330
      pico :: (Num a) => a
331
      pico = 10^(12 :: Int)
332
  showJSON (TimeAsDoubleJSON (TOD ss ps)) = J.showJSON
333
      (fromIntegral ss + fromIntegral ps / 10^(12 :: Int) :: Double)