root / htools / Ganeti / JSON.hs @ 37904802
History | View | Annotate | Download (6.3 kB)
1 | f047f90f | Iustin Pop | {-| JSON utility functions. -} |
---|---|---|---|
2 | f047f90f | Iustin Pop | |
3 | f047f90f | Iustin Pop | {- |
4 | f047f90f | Iustin Pop | |
5 | 3ad57194 | Iustin Pop | Copyright (C) 2009, 2010, 2011, 2012 Google Inc. |
6 | f047f90f | Iustin Pop | |
7 | f047f90f | Iustin Pop | This program is free software; you can redistribute it and/or modify |
8 | f047f90f | Iustin Pop | it under the terms of the GNU General Public License as published by |
9 | f047f90f | Iustin Pop | the Free Software Foundation; either version 2 of the License, or |
10 | f047f90f | Iustin Pop | (at your option) any later version. |
11 | f047f90f | Iustin Pop | |
12 | f047f90f | Iustin Pop | This program is distributed in the hope that it will be useful, but |
13 | f047f90f | Iustin Pop | WITHOUT ANY WARRANTY; without even the implied warranty of |
14 | f047f90f | Iustin Pop | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
15 | f047f90f | Iustin Pop | General Public License for more details. |
16 | f047f90f | Iustin Pop | |
17 | f047f90f | Iustin Pop | You should have received a copy of the GNU General Public License |
18 | f047f90f | Iustin Pop | along with this program; if not, write to the Free Software |
19 | f047f90f | Iustin Pop | Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
20 | f047f90f | Iustin Pop | 02110-1301, USA. |
21 | f047f90f | Iustin Pop | |
22 | f047f90f | Iustin Pop | -} |
23 | f047f90f | Iustin Pop | |
24 | f3baf5ef | Iustin Pop | module Ganeti.JSON |
25 | ebf38064 | Iustin Pop | ( fromJResult |
26 | ebf38064 | Iustin Pop | , readEitherString |
27 | ebf38064 | Iustin Pop | , JSRecord |
28 | ebf38064 | Iustin Pop | , loadJSArray |
29 | ebf38064 | Iustin Pop | , fromObj |
30 | ebf38064 | Iustin Pop | , maybeFromObj |
31 | ebf38064 | Iustin Pop | , fromObjWithDefault |
32 | 706f7f51 | Iustin Pop | , fromKeyValue |
33 | ebf38064 | Iustin Pop | , fromJVal |
34 | 77cab679 | Agata Murawska | , jsonHead |
35 | 318853ab | Iustin Pop | , getMaybeJsonHead |
36 | ebf38064 | Iustin Pop | , asJSObject |
37 | ebf38064 | Iustin Pop | , asObjectList |
38 | f3f76ccc | Iustin Pop | , tryFromObj |
39 | 3ad57194 | Iustin Pop | , toArray |
40 | 84835174 | Iustin Pop | , Container(..) |
41 | ebf38064 | Iustin Pop | ) |
42 | ebf38064 | Iustin Pop | where |
43 | f047f90f | Iustin Pop | |
44 | 84835174 | Iustin Pop | import Control.Arrow (second) |
45 | f047f90f | Iustin Pop | import Control.Monad (liftM) |
46 | f047f90f | Iustin Pop | import Data.Maybe (fromMaybe) |
47 | 84835174 | Iustin Pop | import qualified Data.Map as Map |
48 | f047f90f | Iustin Pop | import Text.Printf (printf) |
49 | f047f90f | Iustin Pop | |
50 | f047f90f | Iustin Pop | import qualified Text.JSON as J |
51 | c12a68e2 | Iustin Pop | import Text.JSON.Pretty (pp_value) |
52 | f047f90f | Iustin Pop | |
53 | f3f76ccc | Iustin Pop | import Ganeti.BasicTypes |
54 | f3f76ccc | Iustin Pop | |
55 | f047f90f | Iustin Pop | -- * JSON-related functions |
56 | f047f90f | Iustin Pop | |
57 | f047f90f | Iustin Pop | -- | A type alias for the list-based representation of J.JSObject. |
58 | f047f90f | Iustin Pop | type JSRecord = [(String, J.JSValue)] |
59 | f047f90f | Iustin Pop | |
60 | f047f90f | Iustin Pop | -- | Converts a JSON Result into a monadic value. |
61 | f047f90f | Iustin Pop | fromJResult :: Monad m => String -> J.Result a -> m a |
62 | f047f90f | Iustin Pop | fromJResult s (J.Error x) = fail (s ++ ": " ++ x) |
63 | f047f90f | Iustin Pop | fromJResult _ (J.Ok x) = return x |
64 | f047f90f | Iustin Pop | |
65 | f047f90f | Iustin Pop | -- | Tries to read a string from a JSON value. |
66 | f047f90f | Iustin Pop | -- |
67 | f047f90f | Iustin Pop | -- In case the value was not a string, we fail the read (in the |
68 | f047f90f | Iustin Pop | -- context of the current monad. |
69 | f047f90f | Iustin Pop | readEitherString :: (Monad m) => J.JSValue -> m String |
70 | f047f90f | Iustin Pop | readEitherString v = |
71 | ebf38064 | Iustin Pop | case v of |
72 | ebf38064 | Iustin Pop | J.JSString s -> return $ J.fromJSString s |
73 | ebf38064 | Iustin Pop | _ -> fail "Wrong JSON type" |
74 | f047f90f | Iustin Pop | |
75 | f047f90f | Iustin Pop | -- | Converts a JSON message into an array of JSON objects. |
76 | f047f90f | Iustin Pop | loadJSArray :: (Monad m) |
77 | f047f90f | Iustin Pop | => String -- ^ Operation description (for error reporting) |
78 | f047f90f | Iustin Pop | -> String -- ^ Input message |
79 | f047f90f | Iustin Pop | -> m [J.JSObject J.JSValue] |
80 | f047f90f | Iustin Pop | loadJSArray s = fromJResult s . J.decodeStrict |
81 | f047f90f | Iustin Pop | |
82 | f047f90f | Iustin Pop | -- | Reads the value of a key in a JSON object. |
83 | f047f90f | Iustin Pop | fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a |
84 | f047f90f | Iustin Pop | fromObj o k = |
85 | ebf38064 | Iustin Pop | case lookup k o of |
86 | ebf38064 | Iustin Pop | Nothing -> fail $ printf "key '%s' not found, object contains only %s" |
87 | ebf38064 | Iustin Pop | k (show (map fst o)) |
88 | ebf38064 | Iustin Pop | Just val -> fromKeyValue k val |
89 | f047f90f | Iustin Pop | |
90 | f2f06e2e | Iustin Pop | -- | Reads the value of an optional key in a JSON object. Missing |
91 | f2f06e2e | Iustin Pop | -- keys, or keys that have a \'null\' value, will be returned as |
92 | f2f06e2e | Iustin Pop | -- 'Nothing', otherwise we attempt deserialisation and return a 'Just' |
93 | f2f06e2e | Iustin Pop | -- value. |
94 | f047f90f | Iustin Pop | maybeFromObj :: (J.JSON a, Monad m) => |
95 | f047f90f | Iustin Pop | JSRecord -> String -> m (Maybe a) |
96 | f047f90f | Iustin Pop | maybeFromObj o k = |
97 | ebf38064 | Iustin Pop | case lookup k o of |
98 | ebf38064 | Iustin Pop | Nothing -> return Nothing |
99 | f2f06e2e | Iustin Pop | -- a optional key with value JSNull is the same as missing, since |
100 | f2f06e2e | Iustin Pop | -- we can't convert it meaningfully anyway to a Haskell type, and |
101 | f2f06e2e | Iustin Pop | -- the Python code can emit 'null' for optional values (depending |
102 | f2f06e2e | Iustin Pop | -- on usage), and finally our encoding rules treat 'null' values |
103 | f2f06e2e | Iustin Pop | -- as 'missing' |
104 | f2f06e2e | Iustin Pop | Just J.JSNull -> return Nothing |
105 | ebf38064 | Iustin Pop | Just val -> liftM Just (fromKeyValue k val) |
106 | f047f90f | Iustin Pop | |
107 | f2f06e2e | Iustin Pop | -- | Reads the value of a key in a JSON object with a default if |
108 | f2f06e2e | Iustin Pop | -- missing. Note that both missing keys and keys with value \'null\' |
109 | f2f06e2e | Iustin Pop | -- will case the default value to be returned. |
110 | f047f90f | Iustin Pop | fromObjWithDefault :: (J.JSON a, Monad m) => |
111 | f047f90f | Iustin Pop | JSRecord -> String -> a -> m a |
112 | f047f90f | Iustin Pop | fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k |
113 | f047f90f | Iustin Pop | |
114 | f047f90f | Iustin Pop | -- | Reads a JValue, that originated from an object key. |
115 | f047f90f | Iustin Pop | fromKeyValue :: (J.JSON a, Monad m) |
116 | f047f90f | Iustin Pop | => String -- ^ The key name |
117 | f047f90f | Iustin Pop | -> J.JSValue -- ^ The value to read |
118 | f047f90f | Iustin Pop | -> m a |
119 | f047f90f | Iustin Pop | fromKeyValue k val = |
120 | 706f7f51 | Iustin Pop | fromJResult (printf "key '%s'" k) (J.readJSON val) |
121 | f047f90f | Iustin Pop | |
122 | f047f90f | Iustin Pop | -- | Small wrapper over readJSON. |
123 | f047f90f | Iustin Pop | fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a |
124 | f047f90f | Iustin Pop | fromJVal v = |
125 | ebf38064 | Iustin Pop | case J.readJSON v of |
126 | c12a68e2 | Iustin Pop | J.Error s -> fail ("Cannot convert value '" ++ show (pp_value v) ++ |
127 | ebf38064 | Iustin Pop | "', error: " ++ s) |
128 | ebf38064 | Iustin Pop | J.Ok x -> return x |
129 | f047f90f | Iustin Pop | |
130 | 77cab679 | Agata Murawska | -- | Helper function that returns Null or first element of the list. |
131 | 77cab679 | Agata Murawska | jsonHead :: (J.JSON b) => [a] -> (a -> b) -> J.JSValue |
132 | 77cab679 | Agata Murawska | jsonHead [] _ = J.JSNull |
133 | 77cab679 | Agata Murawska | jsonHead (x:_) f = J.showJSON $ f x |
134 | 77cab679 | Agata Murawska | |
135 | 318853ab | Iustin Pop | -- | Helper for extracting Maybe values from a possibly empty list. |
136 | 318853ab | Iustin Pop | getMaybeJsonHead :: (J.JSON b) => [a] -> (a -> Maybe b) -> J.JSValue |
137 | 318853ab | Iustin Pop | getMaybeJsonHead [] _ = J.JSNull |
138 | 318853ab | Iustin Pop | getMaybeJsonHead (x:_) f = maybe J.JSNull J.showJSON (f x) |
139 | 318853ab | Iustin Pop | |
140 | f047f90f | Iustin Pop | -- | Converts a JSON value into a JSON object. |
141 | f047f90f | Iustin Pop | asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue) |
142 | f047f90f | Iustin Pop | asJSObject (J.JSObject a) = return a |
143 | f047f90f | Iustin Pop | asJSObject _ = fail "not an object" |
144 | f047f90f | Iustin Pop | |
145 | f047f90f | Iustin Pop | -- | Coneverts a list of JSON values into a list of JSON objects. |
146 | f047f90f | Iustin Pop | asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue] |
147 | f047f90f | Iustin Pop | asObjectList = mapM asJSObject |
148 | f3f76ccc | Iustin Pop | |
149 | f3f76ccc | Iustin Pop | -- | Try to extract a key from a object with better error reporting |
150 | f3f76ccc | Iustin Pop | -- than fromObj. |
151 | f3f76ccc | Iustin Pop | tryFromObj :: (J.JSON a) => |
152 | f3f76ccc | Iustin Pop | String -- ^ Textual "owner" in error messages |
153 | f3f76ccc | Iustin Pop | -> JSRecord -- ^ The object array |
154 | f3f76ccc | Iustin Pop | -> String -- ^ The desired key from the object |
155 | f3f76ccc | Iustin Pop | -> Result a |
156 | f3f76ccc | Iustin Pop | tryFromObj t o = annotateResult t . fromObj o |
157 | 3ad57194 | Iustin Pop | |
158 | 3ad57194 | Iustin Pop | -- | Ensure a given JSValue is actually a JSArray. |
159 | 3ad57194 | Iustin Pop | toArray :: (Monad m) => J.JSValue -> m [J.JSValue] |
160 | 3ad57194 | Iustin Pop | toArray (J.JSArray arr) = return arr |
161 | c12a68e2 | Iustin Pop | toArray o = |
162 | c12a68e2 | Iustin Pop | fail $ "Invalid input, expected array but got " ++ show (pp_value o) |
163 | 84835174 | Iustin Pop | |
164 | 84835174 | Iustin Pop | -- * Container type (special type for JSON serialisation) |
165 | 84835174 | Iustin Pop | |
166 | 84835174 | Iustin Pop | -- | The container type, a wrapper over Data.Map |
167 | 84835174 | Iustin Pop | newtype Container a = Container { fromContainer :: Map.Map String a } |
168 | 84835174 | Iustin Pop | deriving (Show, Read, Eq) |
169 | 84835174 | Iustin Pop | |
170 | 84835174 | Iustin Pop | -- | Container loader. |
171 | 84835174 | Iustin Pop | readContainer :: (Monad m, J.JSON a) => |
172 | 84835174 | Iustin Pop | J.JSObject J.JSValue -> m (Container a) |
173 | 84835174 | Iustin Pop | readContainer obj = do |
174 | 84835174 | Iustin Pop | let kjvlist = J.fromJSObject obj |
175 | 84835174 | Iustin Pop | kalist <- mapM (\(k, v) -> fromKeyValue k v >>= \a -> return (k, a)) kjvlist |
176 | 84835174 | Iustin Pop | return $ Container (Map.fromList kalist) |
177 | 84835174 | Iustin Pop | |
178 | 84835174 | Iustin Pop | -- | Container dumper. |
179 | 84835174 | Iustin Pop | showContainer :: (J.JSON a) => Container a -> J.JSValue |
180 | 84835174 | Iustin Pop | showContainer = |
181 | 84835174 | Iustin Pop | J.makeObj . map (second J.showJSON) . Map.toList . fromContainer |
182 | 84835174 | Iustin Pop | |
183 | 84835174 | Iustin Pop | instance (J.JSON a) => J.JSON (Container a) where |
184 | 84835174 | Iustin Pop | showJSON = showContainer |
185 | 84835174 | Iustin Pop | readJSON (J.JSObject o) = readContainer o |
186 | 84835174 | Iustin Pop | readJSON v = fail $ "Failed to load container, expected object but got " |
187 | c12a68e2 | Iustin Pop | ++ show (pp_value v) |