Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ ec81293c

History | View | Annotate | Download (10.3 kB)

1 edc1acde Iustin Pop
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-}
2 daa79414 Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 daa79414 Iustin Pop
4 f047f90f Iustin Pop
{-| JSON utility functions. -}
5 f047f90f Iustin Pop
6 f047f90f Iustin Pop
{-
7 f047f90f Iustin Pop
8 06fb92cf Bernardo Dal Seno
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
9 f047f90f Iustin Pop
10 f047f90f Iustin Pop
This program is free software; you can redistribute it and/or modify
11 f047f90f Iustin Pop
it under the terms of the GNU General Public License as published by
12 f047f90f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
13 f047f90f Iustin Pop
(at your option) any later version.
14 f047f90f Iustin Pop
15 f047f90f Iustin Pop
This program is distributed in the hope that it will be useful, but
16 f047f90f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
17 f047f90f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18 f047f90f Iustin Pop
General Public License for more details.
19 f047f90f Iustin Pop
20 f047f90f Iustin Pop
You should have received a copy of the GNU General Public License
21 f047f90f Iustin Pop
along with this program; if not, write to the Free Software
22 f047f90f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23 f047f90f Iustin Pop
02110-1301, USA.
24 f047f90f Iustin Pop
25 f047f90f Iustin Pop
-}
26 f047f90f Iustin Pop
27 f3baf5ef Iustin Pop
module Ganeti.JSON
28 ebf38064 Iustin Pop
  ( fromJResult
29 ebf38064 Iustin Pop
  , readEitherString
30 ebf38064 Iustin Pop
  , JSRecord
31 ebf38064 Iustin Pop
  , loadJSArray
32 ebf38064 Iustin Pop
  , fromObj
33 ebf38064 Iustin Pop
  , maybeFromObj
34 ebf38064 Iustin Pop
  , fromObjWithDefault
35 706f7f51 Iustin Pop
  , fromKeyValue
36 ebf38064 Iustin Pop
  , fromJVal
37 77cab679 Agata Murawska
  , jsonHead
38 318853ab Iustin Pop
  , getMaybeJsonHead
39 06fb92cf Bernardo Dal Seno
  , getMaybeJsonElem
40 ebf38064 Iustin Pop
  , asJSObject
41 ebf38064 Iustin Pop
  , asObjectList
42 f3f76ccc Iustin Pop
  , tryFromObj
43 0ec8cce2 Bernardo Dal Seno
  , arrayMaybeFromJVal
44 a4f35477 Bernardo Dal Seno
  , tryArrayMaybeFromObj
45 3ad57194 Iustin Pop
  , toArray
46 3c8e6d09 Michele Tartara
  , optionalJSField
47 3c8e6d09 Michele Tartara
  , optFieldsToObj
48 edc1acde Iustin Pop
  , HasStringRepr(..)
49 edc1acde Iustin Pop
  , GenericContainer(..)
50 edc1acde Iustin Pop
  , Container
51 88b58ed6 Hrvoje Ribicic
  , MaybeForJSON(..)
52 ebf38064 Iustin Pop
  )
53 ebf38064 Iustin Pop
  where
54 f047f90f Iustin Pop
55 daa79414 Iustin Pop
import Control.DeepSeq
56 f047f90f Iustin Pop
import Control.Monad (liftM)
57 3c8e6d09 Michele Tartara
import Data.Maybe (fromMaybe, catMaybes)
58 84835174 Iustin Pop
import qualified Data.Map as Map
59 f047f90f Iustin Pop
import Text.Printf (printf)
60 f047f90f Iustin Pop
61 f047f90f Iustin Pop
import qualified Text.JSON as J
62 c12a68e2 Iustin Pop
import Text.JSON.Pretty (pp_value)
63 f047f90f Iustin Pop
64 32a569fe Iustin Pop
-- Note: this module should not import any Ganeti-specific modules
65 32a569fe Iustin Pop
-- beside BasicTypes, since it's used in THH which is used itself to
66 32a569fe Iustin Pop
-- build many other modules.
67 32a569fe Iustin Pop
68 f3f76ccc Iustin Pop
import Ganeti.BasicTypes
69 f3f76ccc Iustin Pop
70 f047f90f Iustin Pop
-- * JSON-related functions
71 f047f90f Iustin Pop
72 daa79414 Iustin Pop
instance NFData J.JSValue where
73 daa79414 Iustin Pop
  rnf J.JSNull           = ()
74 daa79414 Iustin Pop
  rnf (J.JSBool b)       = rnf b
75 daa79414 Iustin Pop
  rnf (J.JSRational b r) = rnf b `seq` rnf r
76 daa79414 Iustin Pop
  rnf (J.JSString s)     = rnf $ J.fromJSString s
77 daa79414 Iustin Pop
  rnf (J.JSArray a)      = rnf a
78 daa79414 Iustin Pop
  rnf (J.JSObject o)     = rnf o
79 daa79414 Iustin Pop
80 daa79414 Iustin Pop
instance (NFData a) => NFData (J.JSObject a) where
81 daa79414 Iustin Pop
  rnf = rnf . J.fromJSObject
82 daa79414 Iustin Pop
83 3c8e6d09 Michele Tartara
-- | A type alias for a field of a JSRecord.
84 3c8e6d09 Michele Tartara
type JSField = (String, J.JSValue)
85 3c8e6d09 Michele Tartara
86 f047f90f Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
87 3c8e6d09 Michele Tartara
type JSRecord = [JSField]
88 f047f90f Iustin Pop
89 f047f90f Iustin Pop
-- | Converts a JSON Result into a monadic value.
90 f047f90f Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
91 f047f90f Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
92 f047f90f Iustin Pop
fromJResult _ (J.Ok x) = return x
93 f047f90f Iustin Pop
94 f047f90f Iustin Pop
-- | Tries to read a string from a JSON value.
95 f047f90f Iustin Pop
--
96 f047f90f Iustin Pop
-- In case the value was not a string, we fail the read (in the
97 f047f90f Iustin Pop
-- context of the current monad.
98 f047f90f Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
99 f047f90f Iustin Pop
readEitherString v =
100 ebf38064 Iustin Pop
  case v of
101 ebf38064 Iustin Pop
    J.JSString s -> return $ J.fromJSString s
102 ebf38064 Iustin Pop
    _ -> fail "Wrong JSON type"
103 f047f90f Iustin Pop
104 f047f90f Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
105 f047f90f Iustin Pop
loadJSArray :: (Monad m)
106 f047f90f Iustin Pop
               => String -- ^ Operation description (for error reporting)
107 f047f90f Iustin Pop
               -> String -- ^ Input message
108 f047f90f Iustin Pop
               -> m [J.JSObject J.JSValue]
109 f047f90f Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
110 f047f90f Iustin Pop
111 a4f35477 Bernardo Dal Seno
-- | Helper function for missing-key errors
112 a4f35477 Bernardo Dal Seno
buildNoKeyError :: JSRecord -> String -> String
113 a4f35477 Bernardo Dal Seno
buildNoKeyError o k =
114 a4f35477 Bernardo Dal Seno
  printf "key '%s' not found, object contains only %s" k (show (map fst o))
115 a4f35477 Bernardo Dal Seno
116 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object.
117 f047f90f Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
118 f047f90f Iustin Pop
fromObj o k =
119 ebf38064 Iustin Pop
  case lookup k o of
120 a4f35477 Bernardo Dal Seno
    Nothing -> fail $ buildNoKeyError o k
121 ebf38064 Iustin Pop
    Just val -> fromKeyValue k val
122 f047f90f Iustin Pop
123 f2f06e2e Iustin Pop
-- | Reads the value of an optional key in a JSON object. Missing
124 f2f06e2e Iustin Pop
-- keys, or keys that have a \'null\' value, will be returned as
125 f2f06e2e Iustin Pop
-- 'Nothing', otherwise we attempt deserialisation and return a 'Just'
126 f2f06e2e Iustin Pop
-- value.
127 f047f90f Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
128 f047f90f Iustin Pop
                JSRecord -> String -> m (Maybe a)
129 f047f90f Iustin Pop
maybeFromObj o k =
130 ebf38064 Iustin Pop
  case lookup k o of
131 ebf38064 Iustin Pop
    Nothing -> return Nothing
132 f2f06e2e Iustin Pop
    -- a optional key with value JSNull is the same as missing, since
133 f2f06e2e Iustin Pop
    -- we can't convert it meaningfully anyway to a Haskell type, and
134 f2f06e2e Iustin Pop
    -- the Python code can emit 'null' for optional values (depending
135 f2f06e2e Iustin Pop
    -- on usage), and finally our encoding rules treat 'null' values
136 f2f06e2e Iustin Pop
    -- as 'missing'
137 f2f06e2e Iustin Pop
    Just J.JSNull -> return Nothing
138 ebf38064 Iustin Pop
    Just val -> liftM Just (fromKeyValue k val)
139 f047f90f Iustin Pop
140 f2f06e2e Iustin Pop
-- | Reads the value of a key in a JSON object with a default if
141 f2f06e2e Iustin Pop
-- missing. Note that both missing keys and keys with value \'null\'
142 2f3d7a50 Jose A. Lopes
-- will cause the default value to be returned.
143 f047f90f Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
144 f047f90f Iustin Pop
                      JSRecord -> String -> a -> m a
145 f047f90f Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
146 f047f90f Iustin Pop
147 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal :: (J.JSON a, Monad m) => J.JSValue -> m [Maybe a]
148 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal (J.JSArray xs) =
149 0ec8cce2 Bernardo Dal Seno
  mapM parse xs
150 0ec8cce2 Bernardo Dal Seno
    where
151 0ec8cce2 Bernardo Dal Seno
      parse J.JSNull = return Nothing
152 0ec8cce2 Bernardo Dal Seno
      parse x = liftM Just $ fromJVal x
153 0ec8cce2 Bernardo Dal Seno
arrayMaybeFromJVal v =
154 0ec8cce2 Bernardo Dal Seno
  fail $ "Expecting array, got '" ++ show (pp_value v) ++ "'"
155 0ec8cce2 Bernardo Dal Seno
156 a4f35477 Bernardo Dal Seno
-- | Reads an array of optional items
157 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj :: (J.JSON a, Monad m) =>
158 a4f35477 Bernardo Dal Seno
                     JSRecord -> String -> m [Maybe a]
159 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj o k =
160 a4f35477 Bernardo Dal Seno
  case lookup k o of
161 0ec8cce2 Bernardo Dal Seno
    Just a -> arrayMaybeFromJVal a
162 a4f35477 Bernardo Dal Seno
    _ -> fail $ buildNoKeyError o k
163 a4f35477 Bernardo Dal Seno
164 a4f35477 Bernardo Dal Seno
-- | Wrapper for arrayMaybeFromObj with better diagnostic
165 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj :: (J.JSON a)
166 a4f35477 Bernardo Dal Seno
                     => String     -- ^ Textual "owner" in error messages
167 a4f35477 Bernardo Dal Seno
                     -> JSRecord   -- ^ The object array
168 a4f35477 Bernardo Dal Seno
                     -> String     -- ^ The desired key from the object
169 a4f35477 Bernardo Dal Seno
                     -> Result [Maybe a]
170 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj t o = annotateResult t . arrayMaybeFromObj o
171 a4f35477 Bernardo Dal Seno
172 f047f90f Iustin Pop
-- | Reads a JValue, that originated from an object key.
173 f047f90f Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
174 f047f90f Iustin Pop
              => String     -- ^ The key name
175 f047f90f Iustin Pop
              -> J.JSValue  -- ^ The value to read
176 f047f90f Iustin Pop
              -> m a
177 f047f90f Iustin Pop
fromKeyValue k val =
178 706f7f51 Iustin Pop
  fromJResult (printf "key '%s'" k) (J.readJSON val)
179 f047f90f Iustin Pop
180 f047f90f Iustin Pop
-- | Small wrapper over readJSON.
181 f047f90f Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
182 f047f90f Iustin Pop
fromJVal v =
183 ebf38064 Iustin Pop
  case J.readJSON v of
184 c12a68e2 Iustin Pop
    J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++
185 ebf38064 Iustin Pop
                       "', error: " ++ s)
186 ebf38064 Iustin Pop
    J.Ok x -> return x
187 f047f90f Iustin Pop
188 77cab679 Agata Murawska
-- | Helper function that returns Null or first element of the list.
189 77cab679 Agata Murawska
jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue
190 77cab679 Agata Murawska
jsonHead [] _ = J.JSNull
191 77cab679 Agata Murawska
jsonHead (x:_) f = J.showJSON $ f x
192 77cab679 Agata Murawska
193 318853ab Iustin Pop
-- | Helper for extracting Maybe values from a possibly empty list.
194 318853ab Iustin Pop
getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue
195 318853ab Iustin Pop
getMaybeJsonHead [] _ = J.JSNull
196 318853ab Iustin Pop
getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x)
197 318853ab Iustin Pop
198 06fb92cf Bernardo Dal Seno
-- | Helper for extracting Maybe values from a list that might be too short.
199 06fb92cf Bernardo Dal Seno
getMaybeJsonElem :: (J.JSON b) => [a] -> Int -> (a -> Maybe b) -> J.JSValue
200 06fb92cf Bernardo Dal Seno
getMaybeJsonElem [] _ _ = J.JSNull
201 06fb92cf Bernardo Dal Seno
getMaybeJsonElem xs 0 f = getMaybeJsonHead xs f
202 06fb92cf Bernardo Dal Seno
getMaybeJsonElem (_:xs) n f
203 06fb92cf Bernardo Dal Seno
  | n < 0 = J.JSNull
204 06fb92cf Bernardo Dal Seno
  | otherwise = getMaybeJsonElem xs (n - 1) f
205 06fb92cf Bernardo Dal Seno
206 f047f90f Iustin Pop
-- | Converts a JSON value into a JSON object.
207 f047f90f Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
208 f047f90f Iustin Pop
asJSObject (J.JSObject a) = return a
209 f047f90f Iustin Pop
asJSObject _ = fail "not an object"
210 f047f90f Iustin Pop
211 f047f90f Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
212 f047f90f Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
213 f047f90f Iustin Pop
asObjectList = mapM asJSObject
214 f3f76ccc Iustin Pop
215 7209d304 Klaus Aehlig
-- | Try to extract a key from an object with better error reporting
216 f3f76ccc Iustin Pop
-- than fromObj.
217 f3f76ccc Iustin Pop
tryFromObj :: (J.JSON a) =>
218 f3f76ccc Iustin Pop
              String     -- ^ Textual "owner" in error messages
219 f3f76ccc Iustin Pop
           -> JSRecord   -- ^ The object array
220 f3f76ccc Iustin Pop
           -> String     -- ^ The desired key from the object
221 f3f76ccc Iustin Pop
           -> Result a
222 f3f76ccc Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
223 3ad57194 Iustin Pop
224 3ad57194 Iustin Pop
-- | Ensure a given JSValue is actually a JSArray.
225 3ad57194 Iustin Pop
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
226 3ad57194 Iustin Pop
toArray (J.JSArray arr) = return arr
227 c12a68e2 Iustin Pop
toArray o =
228 c12a68e2 Iustin Pop
  fail $ "Invalid input, expected array but got " ++ show (pp_value o)
229 84835174 Iustin Pop
230 3c8e6d09 Michele Tartara
-- | Creates a Maybe JSField. If the value string is Nothing, the JSField
231 3c8e6d09 Michele Tartara
-- will be Nothing as well.
232 3c8e6d09 Michele Tartara
optionalJSField :: (J.JSON a) => String -> Maybe a -> Maybe JSField
233 3c8e6d09 Michele Tartara
optionalJSField name (Just value) = Just (name, J.showJSON value)
234 3c8e6d09 Michele Tartara
optionalJSField _ Nothing = Nothing
235 3c8e6d09 Michele Tartara
236 3c8e6d09 Michele Tartara
-- | Creates an object with all the non-Nothing fields of the given list.
237 3c8e6d09 Michele Tartara
optFieldsToObj :: [Maybe JSField] -> J.JSValue
238 3c8e6d09 Michele Tartara
optFieldsToObj = J.makeObj . catMaybes
239 3c8e6d09 Michele Tartara
240 84835174 Iustin Pop
-- * Container type (special type for JSON serialisation)
241 84835174 Iustin Pop
242 edc1acde Iustin Pop
-- | Class of types that can be converted from Strings. This is
243 edc1acde Iustin Pop
-- similar to the 'Read' class, but it's using a different
244 edc1acde Iustin Pop
-- serialisation format, so we have to define a separate class. Mostly
245 edc1acde Iustin Pop
-- useful for custom key types in JSON dictionaries, which have to be
246 edc1acde Iustin Pop
-- backed by strings.
247 edc1acde Iustin Pop
class HasStringRepr a where
248 edc1acde Iustin Pop
  fromStringRepr :: (Monad m) => String -> m a
249 edc1acde Iustin Pop
  toStringRepr :: a -> String
250 edc1acde Iustin Pop
251 edc1acde Iustin Pop
-- | Trivial instance 'HasStringRepr' for 'String'.
252 edc1acde Iustin Pop
instance HasStringRepr String where
253 edc1acde Iustin Pop
  fromStringRepr = return
254 edc1acde Iustin Pop
  toStringRepr = id
255 edc1acde Iustin Pop
256 84835174 Iustin Pop
-- | The container type, a wrapper over Data.Map
257 edc1acde Iustin Pop
newtype GenericContainer a b =
258 edc1acde Iustin Pop
  GenericContainer { fromContainer :: Map.Map a b }
259 139c0683 Iustin Pop
  deriving (Show, Eq)
260 84835174 Iustin Pop
261 daa79414 Iustin Pop
instance (NFData a, NFData b) => NFData (GenericContainer a b) where
262 daa79414 Iustin Pop
  rnf = rnf . Map.toList . fromContainer
263 daa79414 Iustin Pop
264 edc1acde Iustin Pop
-- | Type alias for string keys.
265 edc1acde Iustin Pop
type Container = GenericContainer String
266 edc1acde Iustin Pop
267 84835174 Iustin Pop
-- | Container loader.
268 edc1acde Iustin Pop
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
269 edc1acde Iustin Pop
                 J.JSObject J.JSValue -> m (GenericContainer a b)
270 84835174 Iustin Pop
readContainer obj = do
271 84835174 Iustin Pop
  let kjvlist = J.fromJSObject obj
272 edc1acde Iustin Pop
  kalist <- mapM (\(k, v) -> do
273 edc1acde Iustin Pop
                    k' <- fromStringRepr k
274 edc1acde Iustin Pop
                    v' <- fromKeyValue k v
275 edc1acde Iustin Pop
                    return (k', v')) kjvlist
276 edc1acde Iustin Pop
  return $ GenericContainer (Map.fromList kalist)
277 84835174 Iustin Pop
278 417ab39c Iustin Pop
{-# ANN showContainer "HLint: ignore Use ***" #-}
279 84835174 Iustin Pop
-- | Container dumper.
280 edc1acde Iustin Pop
showContainer :: (HasStringRepr a, J.JSON b) =>
281 edc1acde Iustin Pop
                 GenericContainer a b -> J.JSValue
282 84835174 Iustin Pop
showContainer =
283 edc1acde Iustin Pop
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
284 edc1acde Iustin Pop
  Map.toList . fromContainer
285 84835174 Iustin Pop
286 edc1acde Iustin Pop
instance (HasStringRepr a, Ord a, J.JSON b) =>
287 edc1acde Iustin Pop
         J.JSON (GenericContainer a b) where
288 84835174 Iustin Pop
  showJSON = showContainer
289 84835174 Iustin Pop
  readJSON (J.JSObject o) = readContainer o
290 84835174 Iustin Pop
  readJSON v = fail $ "Failed to load container, expected object but got "
291 c12a68e2 Iustin Pop
               ++ show (pp_value v)
292 88b58ed6 Hrvoje Ribicic
293 88b58ed6 Hrvoje Ribicic
-- | A Maybe newtype that allows for serialization more appropriate to the
294 88b58ed6 Hrvoje Ribicic
-- semantics of Maybe and JSON in our calls. Does not produce needless
295 88b58ed6 Hrvoje Ribicic
-- and confusing dictionaries.
296 88b58ed6 Hrvoje Ribicic
newtype MaybeForJSON a = MaybeForJSON { unMaybeForJSON :: Maybe a }
297 88b58ed6 Hrvoje Ribicic
instance (J.JSON a) => J.JSON (MaybeForJSON a) where
298 88b58ed6 Hrvoje Ribicic
  readJSON = J.readJSON
299 88b58ed6 Hrvoje Ribicic
  showJSON (MaybeForJSON (Just x)) = J.showJSON x
300 88b58ed6 Hrvoje Ribicic
  showJSON (MaybeForJSON Nothing)  = J.JSNull