Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ 67ebc173

History | View | Annotate | Download (9.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 3ad57194 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  , asJSObject
40 ebf38064 Iustin Pop
  , asObjectList
41 f3f76ccc Iustin Pop
  , tryFromObj
42 a4f35477 Bernardo Dal Seno
  , tryArrayMaybeFromObj
43 3ad57194 Iustin Pop
  , toArray
44 3c8e6d09 Michele Tartara
  , optionalJSField
45 3c8e6d09 Michele Tartara
  , optFieldsToObj
46 edc1acde Iustin Pop
  , HasStringRepr(..)
47 edc1acde Iustin Pop
  , GenericContainer(..)
48 edc1acde Iustin Pop
  , Container
49 ebf38064 Iustin Pop
  )
50 ebf38064 Iustin Pop
  where
51 f047f90f Iustin Pop
52 daa79414 Iustin Pop
import Control.DeepSeq
53 f047f90f Iustin Pop
import Control.Monad (liftM)
54 3c8e6d09 Michele Tartara
import Data.Maybe (fromMaybe, catMaybes)
55 84835174 Iustin Pop
import qualified Data.Map as Map
56 f047f90f Iustin Pop
import Text.Printf (printf)
57 f047f90f Iustin Pop
58 f047f90f Iustin Pop
import qualified Text.JSON as J
59 c12a68e2 Iustin Pop
import Text.JSON.Pretty (pp_value)
60 f047f90f Iustin Pop
61 32a569fe Iustin Pop
-- Note: this module should not import any Ganeti-specific modules
62 32a569fe Iustin Pop
-- beside BasicTypes, since it's used in THH which is used itself to
63 32a569fe Iustin Pop
-- build many other modules.
64 32a569fe Iustin Pop
65 f3f76ccc Iustin Pop
import Ganeti.BasicTypes
66 f3f76ccc Iustin Pop
67 f047f90f Iustin Pop
-- * JSON-related functions
68 f047f90f Iustin Pop
69 daa79414 Iustin Pop
instance NFData J.JSValue where
70 daa79414 Iustin Pop
  rnf J.JSNull           = ()
71 daa79414 Iustin Pop
  rnf (J.JSBool b)       = rnf b
72 daa79414 Iustin Pop
  rnf (J.JSRational b r) = rnf b `seq` rnf r
73 daa79414 Iustin Pop
  rnf (J.JSString s)     = rnf $ J.fromJSString s
74 daa79414 Iustin Pop
  rnf (J.JSArray a)      = rnf a
75 daa79414 Iustin Pop
  rnf (J.JSObject o)     = rnf o
76 daa79414 Iustin Pop
77 daa79414 Iustin Pop
instance (NFData a) => NFData (J.JSObject a) where
78 daa79414 Iustin Pop
  rnf = rnf . J.fromJSObject
79 daa79414 Iustin Pop
80 3c8e6d09 Michele Tartara
-- | A type alias for a field of a JSRecord.
81 3c8e6d09 Michele Tartara
type JSField = (String, J.JSValue)
82 3c8e6d09 Michele Tartara
83 f047f90f Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
84 3c8e6d09 Michele Tartara
type JSRecord = [JSField]
85 f047f90f Iustin Pop
86 f047f90f Iustin Pop
-- | Converts a JSON Result into a monadic value.
87 f047f90f Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
88 f047f90f Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
89 f047f90f Iustin Pop
fromJResult _ (J.Ok x) = return x
90 f047f90f Iustin Pop
91 f047f90f Iustin Pop
-- | Tries to read a string from a JSON value.
92 f047f90f Iustin Pop
--
93 f047f90f Iustin Pop
-- In case the value was not a string, we fail the read (in the
94 f047f90f Iustin Pop
-- context of the current monad.
95 f047f90f Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
96 f047f90f Iustin Pop
readEitherString v =
97 ebf38064 Iustin Pop
  case v of
98 ebf38064 Iustin Pop
    J.JSString s -> return $ J.fromJSString s
99 ebf38064 Iustin Pop
    _ -> fail "Wrong JSON type"
100 f047f90f Iustin Pop
101 f047f90f Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
102 f047f90f Iustin Pop
loadJSArray :: (Monad m)
103 f047f90f Iustin Pop
               => String -- ^ Operation description (for error reporting)
104 f047f90f Iustin Pop
               -> String -- ^ Input message
105 f047f90f Iustin Pop
               -> m [J.JSObject J.JSValue]
106 f047f90f Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
107 f047f90f Iustin Pop
108 a4f35477 Bernardo Dal Seno
-- | Helper function for missing-key errors
109 a4f35477 Bernardo Dal Seno
buildNoKeyError :: JSRecord -> String -> String
110 a4f35477 Bernardo Dal Seno
buildNoKeyError o k =
111 a4f35477 Bernardo Dal Seno
  printf "key '%s' not found, object contains only %s" k (show (map fst o))
112 a4f35477 Bernardo Dal Seno
113 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object.
114 f047f90f Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
115 f047f90f Iustin Pop
fromObj o k =
116 ebf38064 Iustin Pop
  case lookup k o of
117 a4f35477 Bernardo Dal Seno
    Nothing -> fail $ buildNoKeyError o k
118 ebf38064 Iustin Pop
    Just val -> fromKeyValue k val
119 f047f90f Iustin Pop
120 f2f06e2e Iustin Pop
-- | Reads the value of an optional key in a JSON object. Missing
121 f2f06e2e Iustin Pop
-- keys, or keys that have a \'null\' value, will be returned as
122 f2f06e2e Iustin Pop
-- 'Nothing', otherwise we attempt deserialisation and return a 'Just'
123 f2f06e2e Iustin Pop
-- value.
124 f047f90f Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
125 f047f90f Iustin Pop
                JSRecord -> String -> m (Maybe a)
126 f047f90f Iustin Pop
maybeFromObj o k =
127 ebf38064 Iustin Pop
  case lookup k o of
128 ebf38064 Iustin Pop
    Nothing -> return Nothing
129 f2f06e2e Iustin Pop
    -- a optional key with value JSNull is the same as missing, since
130 f2f06e2e Iustin Pop
    -- we can't convert it meaningfully anyway to a Haskell type, and
131 f2f06e2e Iustin Pop
    -- the Python code can emit 'null' for optional values (depending
132 f2f06e2e Iustin Pop
    -- on usage), and finally our encoding rules treat 'null' values
133 f2f06e2e Iustin Pop
    -- as 'missing'
134 f2f06e2e Iustin Pop
    Just J.JSNull -> return Nothing
135 ebf38064 Iustin Pop
    Just val -> liftM Just (fromKeyValue k val)
136 f047f90f Iustin Pop
137 f2f06e2e Iustin Pop
-- | Reads the value of a key in a JSON object with a default if
138 f2f06e2e Iustin Pop
-- missing. Note that both missing keys and keys with value \'null\'
139 f2f06e2e Iustin Pop
-- will case the default value to be returned.
140 f047f90f Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
141 f047f90f Iustin Pop
                      JSRecord -> String -> a -> m a
142 f047f90f Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
143 f047f90f Iustin Pop
144 a4f35477 Bernardo Dal Seno
-- | Reads an array of optional items
145 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj :: (J.JSON a, Monad m) =>
146 a4f35477 Bernardo Dal Seno
                     JSRecord -> String -> m [Maybe a]
147 a4f35477 Bernardo Dal Seno
arrayMaybeFromObj o k =
148 a4f35477 Bernardo Dal Seno
  case lookup k o of
149 a4f35477 Bernardo Dal Seno
    Just (J.JSArray xs) -> mapM parse xs
150 a4f35477 Bernardo Dal Seno
      where
151 a4f35477 Bernardo Dal Seno
        parse J.JSNull = return Nothing
152 a4f35477 Bernardo Dal Seno
        parse x = liftM Just $ fromJVal x
153 a4f35477 Bernardo Dal Seno
    _ -> fail $ buildNoKeyError o k
154 a4f35477 Bernardo Dal Seno
155 a4f35477 Bernardo Dal Seno
-- | Wrapper for arrayMaybeFromObj with better diagnostic
156 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj :: (J.JSON a)
157 a4f35477 Bernardo Dal Seno
                     => String     -- ^ Textual "owner" in error messages
158 a4f35477 Bernardo Dal Seno
                     -> JSRecord   -- ^ The object array
159 a4f35477 Bernardo Dal Seno
                     -> String     -- ^ The desired key from the object
160 a4f35477 Bernardo Dal Seno
                     -> Result [Maybe a]
161 a4f35477 Bernardo Dal Seno
tryArrayMaybeFromObj t o = annotateResult t . arrayMaybeFromObj o
162 a4f35477 Bernardo Dal Seno
163 f047f90f Iustin Pop
-- | Reads a JValue, that originated from an object key.
164 f047f90f Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
165 f047f90f Iustin Pop
              => String     -- ^ The key name
166 f047f90f Iustin Pop
              -> J.JSValue  -- ^ The value to read
167 f047f90f Iustin Pop
              -> m a
168 f047f90f Iustin Pop
fromKeyValue k val =
169 706f7f51 Iustin Pop
  fromJResult (printf "key '%s'" k) (J.readJSON val)
170 f047f90f Iustin Pop
171 f047f90f Iustin Pop
-- | Small wrapper over readJSON.
172 f047f90f Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
173 f047f90f Iustin Pop
fromJVal v =
174 ebf38064 Iustin Pop
  case J.readJSON v of
175 c12a68e2 Iustin Pop
    J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++
176 ebf38064 Iustin Pop
                       "', error: " ++ s)
177 ebf38064 Iustin Pop
    J.Ok x -> return x
178 f047f90f Iustin Pop
179 77cab679 Agata Murawska
-- | Helper function that returns Null or first element of the list.
180 77cab679 Agata Murawska
jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue
181 77cab679 Agata Murawska
jsonHead [] _ = J.JSNull
182 77cab679 Agata Murawska
jsonHead (x:_) f = J.showJSON $ f x
183 77cab679 Agata Murawska
184 318853ab Iustin Pop
-- | Helper for extracting Maybe values from a possibly empty list.
185 318853ab Iustin Pop
getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue
186 318853ab Iustin Pop
getMaybeJsonHead [] _ = J.JSNull
187 318853ab Iustin Pop
getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x)
188 318853ab Iustin Pop
189 f047f90f Iustin Pop
-- | Converts a JSON value into a JSON object.
190 f047f90f Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
191 f047f90f Iustin Pop
asJSObject (J.JSObject a) = return a
192 f047f90f Iustin Pop
asJSObject _ = fail "not an object"
193 f047f90f Iustin Pop
194 f047f90f Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
195 f047f90f Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
196 f047f90f Iustin Pop
asObjectList = mapM asJSObject
197 f3f76ccc Iustin Pop
198 7209d304 Klaus Aehlig
-- | Try to extract a key from an object with better error reporting
199 f3f76ccc Iustin Pop
-- than fromObj.
200 f3f76ccc Iustin Pop
tryFromObj :: (J.JSON a) =>
201 f3f76ccc Iustin Pop
              String     -- ^ Textual "owner" in error messages
202 f3f76ccc Iustin Pop
           -> JSRecord   -- ^ The object array
203 f3f76ccc Iustin Pop
           -> String     -- ^ The desired key from the object
204 f3f76ccc Iustin Pop
           -> Result a
205 f3f76ccc Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
206 3ad57194 Iustin Pop
207 3ad57194 Iustin Pop
-- | Ensure a given JSValue is actually a JSArray.
208 3ad57194 Iustin Pop
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
209 3ad57194 Iustin Pop
toArray (J.JSArray arr) = return arr
210 c12a68e2 Iustin Pop
toArray o =
211 c12a68e2 Iustin Pop
  fail $ "Invalid input, expected array but got " ++ show (pp_value o)
212 84835174 Iustin Pop
213 3c8e6d09 Michele Tartara
-- | Creates a Maybe JSField. If the value string is Nothing, the JSField
214 3c8e6d09 Michele Tartara
-- will be Nothing as well.
215 3c8e6d09 Michele Tartara
optionalJSField :: (J.JSON a) => String -> Maybe a -> Maybe JSField
216 3c8e6d09 Michele Tartara
optionalJSField name (Just value) = Just (name, J.showJSON value)
217 3c8e6d09 Michele Tartara
optionalJSField _ Nothing = Nothing
218 3c8e6d09 Michele Tartara
219 3c8e6d09 Michele Tartara
-- | Creates an object with all the non-Nothing fields of the given list.
220 3c8e6d09 Michele Tartara
optFieldsToObj :: [Maybe JSField] -> J.JSValue
221 3c8e6d09 Michele Tartara
optFieldsToObj = J.makeObj . catMaybes
222 3c8e6d09 Michele Tartara
223 84835174 Iustin Pop
-- * Container type (special type for JSON serialisation)
224 84835174 Iustin Pop
225 edc1acde Iustin Pop
-- | Class of types that can be converted from Strings. This is
226 edc1acde Iustin Pop
-- similar to the 'Read' class, but it's using a different
227 edc1acde Iustin Pop
-- serialisation format, so we have to define a separate class. Mostly
228 edc1acde Iustin Pop
-- useful for custom key types in JSON dictionaries, which have to be
229 edc1acde Iustin Pop
-- backed by strings.
230 edc1acde Iustin Pop
class HasStringRepr a where
231 edc1acde Iustin Pop
  fromStringRepr :: (Monad m) => String -> m a
232 edc1acde Iustin Pop
  toStringRepr :: a -> String
233 edc1acde Iustin Pop
234 edc1acde Iustin Pop
-- | Trivial instance 'HasStringRepr' for 'String'.
235 edc1acde Iustin Pop
instance HasStringRepr String where
236 edc1acde Iustin Pop
  fromStringRepr = return
237 edc1acde Iustin Pop
  toStringRepr = id
238 edc1acde Iustin Pop
239 84835174 Iustin Pop
-- | The container type, a wrapper over Data.Map
240 edc1acde Iustin Pop
newtype GenericContainer a b =
241 edc1acde Iustin Pop
  GenericContainer { fromContainer :: Map.Map a b }
242 139c0683 Iustin Pop
  deriving (Show, Eq)
243 84835174 Iustin Pop
244 daa79414 Iustin Pop
instance (NFData a, NFData b) => NFData (GenericContainer a b) where
245 daa79414 Iustin Pop
  rnf = rnf . Map.toList . fromContainer
246 daa79414 Iustin Pop
247 edc1acde Iustin Pop
-- | Type alias for string keys.
248 edc1acde Iustin Pop
type Container = GenericContainer String
249 edc1acde Iustin Pop
250 84835174 Iustin Pop
-- | Container loader.
251 edc1acde Iustin Pop
readContainer :: (Monad m, HasStringRepr a, Ord a, J.JSON b) =>
252 edc1acde Iustin Pop
                 J.JSObject J.JSValue -> m (GenericContainer a b)
253 84835174 Iustin Pop
readContainer obj = do
254 84835174 Iustin Pop
  let kjvlist = J.fromJSObject obj
255 edc1acde Iustin Pop
  kalist <- mapM (\(k, v) -> do
256 edc1acde Iustin Pop
                    k' <- fromStringRepr k
257 edc1acde Iustin Pop
                    v' <- fromKeyValue k v
258 edc1acde Iustin Pop
                    return (k', v')) kjvlist
259 edc1acde Iustin Pop
  return $ GenericContainer (Map.fromList kalist)
260 84835174 Iustin Pop
261 417ab39c Iustin Pop
{-# ANN showContainer "HLint: ignore Use ***" #-}
262 84835174 Iustin Pop
-- | Container dumper.
263 edc1acde Iustin Pop
showContainer :: (HasStringRepr a, J.JSON b) =>
264 edc1acde Iustin Pop
                 GenericContainer a b -> J.JSValue
265 84835174 Iustin Pop
showContainer =
266 edc1acde Iustin Pop
  J.makeObj . map (\(k, v) -> (toStringRepr k, J.showJSON v)) .
267 edc1acde Iustin Pop
  Map.toList . fromContainer
268 84835174 Iustin Pop
269 edc1acde Iustin Pop
instance (HasStringRepr a, Ord a, J.JSON b) =>
270 edc1acde Iustin Pop
         J.JSON (GenericContainer a b) where
271 84835174 Iustin Pop
  showJSON = showContainer
272 84835174 Iustin Pop
  readJSON (J.JSObject o) = readContainer o
273 84835174 Iustin Pop
  readJSON v = fail $ "Failed to load container, expected object but got "
274 c12a68e2 Iustin Pop
               ++ show (pp_value v)