Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / JSON.hs @ a5ec6d88

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