Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / JSON.hs @ 3c8e6d09

History | View | Annotate | Download (7.9 kB)

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