Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / JSON.hs @ 3ad57194

History | View | Annotate | Download (4.2 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 f047f90f Iustin Pop
module Ganeti.HTools.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 ebf38064 Iustin Pop
  , asJSObject
35 ebf38064 Iustin Pop
  , asObjectList
36 f3f76ccc Iustin Pop
  , tryFromObj
37 3ad57194 Iustin Pop
  , toArray
38 ebf38064 Iustin Pop
  )
39 ebf38064 Iustin Pop
  where
40 f047f90f Iustin Pop
41 f047f90f Iustin Pop
import Control.Monad (liftM)
42 f047f90f Iustin Pop
import Data.Maybe (fromMaybe)
43 f047f90f Iustin Pop
import Text.Printf (printf)
44 f047f90f Iustin Pop
45 f047f90f Iustin Pop
import qualified Text.JSON as J
46 f047f90f Iustin Pop
47 f3f76ccc Iustin Pop
import Ganeti.BasicTypes
48 f3f76ccc Iustin Pop
49 f047f90f Iustin Pop
-- * JSON-related functions
50 f047f90f Iustin Pop
51 f047f90f Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
52 f047f90f Iustin Pop
type JSRecord = [(String, J.JSValue)]
53 f047f90f Iustin Pop
54 f047f90f Iustin Pop
-- | Converts a JSON Result into a monadic value.
55 f047f90f Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
56 f047f90f Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
57 f047f90f Iustin Pop
fromJResult _ (J.Ok x) = return x
58 f047f90f Iustin Pop
59 f047f90f Iustin Pop
-- | Tries to read a string from a JSON value.
60 f047f90f Iustin Pop
--
61 f047f90f Iustin Pop
-- In case the value was not a string, we fail the read (in the
62 f047f90f Iustin Pop
-- context of the current monad.
63 f047f90f Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
64 f047f90f Iustin Pop
readEitherString v =
65 ebf38064 Iustin Pop
  case v of
66 ebf38064 Iustin Pop
    J.JSString s -> return $ J.fromJSString s
67 ebf38064 Iustin Pop
    _ -> fail "Wrong JSON type"
68 f047f90f Iustin Pop
69 f047f90f Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
70 f047f90f Iustin Pop
loadJSArray :: (Monad m)
71 f047f90f Iustin Pop
               => String -- ^ Operation description (for error reporting)
72 f047f90f Iustin Pop
               -> String -- ^ Input message
73 f047f90f Iustin Pop
               -> m [J.JSObject J.JSValue]
74 f047f90f Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
75 f047f90f Iustin Pop
76 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object.
77 f047f90f Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
78 f047f90f Iustin Pop
fromObj o k =
79 ebf38064 Iustin Pop
  case lookup k o of
80 ebf38064 Iustin Pop
    Nothing -> fail $ printf "key '%s' not found, object contains only %s"
81 ebf38064 Iustin Pop
               k (show (map fst o))
82 ebf38064 Iustin Pop
    Just val -> fromKeyValue k val
83 f047f90f Iustin Pop
84 f047f90f Iustin Pop
-- | Reads the value of an optional key in a JSON object.
85 f047f90f Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
86 f047f90f Iustin Pop
                JSRecord -> String -> m (Maybe a)
87 f047f90f Iustin Pop
maybeFromObj o k =
88 ebf38064 Iustin Pop
  case lookup k o of
89 ebf38064 Iustin Pop
    Nothing -> return Nothing
90 ebf38064 Iustin Pop
    Just val -> liftM Just (fromKeyValue k val)
91 f047f90f Iustin Pop
92 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object with a default if missing.
93 f047f90f Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
94 f047f90f Iustin Pop
                      JSRecord -> String -> a -> m a
95 f047f90f Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
96 f047f90f Iustin Pop
97 f047f90f Iustin Pop
-- | Reads a JValue, that originated from an object key.
98 f047f90f Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
99 f047f90f Iustin Pop
              => String     -- ^ The key name
100 f047f90f Iustin Pop
              -> J.JSValue  -- ^ The value to read
101 f047f90f Iustin Pop
              -> m a
102 f047f90f Iustin Pop
fromKeyValue k val =
103 706f7f51 Iustin Pop
  fromJResult (printf "key '%s'" k) (J.readJSON val)
104 f047f90f Iustin Pop
105 f047f90f Iustin Pop
-- | Small wrapper over readJSON.
106 f047f90f Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
107 f047f90f Iustin Pop
fromJVal v =
108 ebf38064 Iustin Pop
  case J.readJSON v of
109 ebf38064 Iustin Pop
    J.Error s -> fail ("Cannot convert value '" ++ show v ++
110 ebf38064 Iustin Pop
                       "', error: " ++ s)
111 ebf38064 Iustin Pop
    J.Ok x -> return x
112 f047f90f Iustin Pop
113 f047f90f Iustin Pop
-- | Converts a JSON value into a JSON object.
114 f047f90f Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
115 f047f90f Iustin Pop
asJSObject (J.JSObject a) = return a
116 f047f90f Iustin Pop
asJSObject _ = fail "not an object"
117 f047f90f Iustin Pop
118 f047f90f Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
119 f047f90f Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
120 f047f90f Iustin Pop
asObjectList = mapM asJSObject
121 f3f76ccc Iustin Pop
122 f3f76ccc Iustin Pop
-- | Try to extract a key from a object with better error reporting
123 f3f76ccc Iustin Pop
-- than fromObj.
124 f3f76ccc Iustin Pop
tryFromObj :: (J.JSON a) =>
125 f3f76ccc Iustin Pop
              String     -- ^ Textual "owner" in error messages
126 f3f76ccc Iustin Pop
           -> JSRecord   -- ^ The object array
127 f3f76ccc Iustin Pop
           -> String     -- ^ The desired key from the object
128 f3f76ccc Iustin Pop
           -> Result a
129 f3f76ccc Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
130 3ad57194 Iustin Pop
131 3ad57194 Iustin Pop
-- | Ensure a given JSValue is actually a JSArray.
132 3ad57194 Iustin Pop
toArray :: (Monad m) => J.JSValue -> m [J.JSValue]
133 3ad57194 Iustin Pop
toArray (J.JSArray arr) = return arr
134 3ad57194 Iustin Pop
toArray o = fail $ "Invalid input, expected array but got " ++ show o