Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / JSON.hs @ 61bbbed7

History | View | Annotate | Download (3.7 kB)

1 f047f90f Iustin Pop
{-| JSON utility functions. -}
2 f047f90f Iustin Pop
3 f047f90f Iustin Pop
{-
4 f047f90f Iustin Pop
5 f047f90f Iustin Pop
Copyright (C) 2009, 2010, 2011 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 f047f90f Iustin Pop
    ( fromJResult
26 f047f90f Iustin Pop
    , readEitherString
27 f047f90f Iustin Pop
    , JSRecord
28 f047f90f Iustin Pop
    , loadJSArray
29 f047f90f Iustin Pop
    , fromObj
30 f047f90f Iustin Pop
    , maybeFromObj
31 f047f90f Iustin Pop
    , fromObjWithDefault
32 f047f90f Iustin Pop
    , fromJVal
33 f047f90f Iustin Pop
    , asJSObject
34 f047f90f Iustin Pop
    , asObjectList
35 f047f90f Iustin Pop
    )
36 f047f90f Iustin Pop
    where
37 f047f90f Iustin Pop
38 f047f90f Iustin Pop
import Control.Monad (liftM)
39 f047f90f Iustin Pop
import Data.Maybe (fromMaybe)
40 f047f90f Iustin Pop
import Text.Printf (printf)
41 f047f90f Iustin Pop
42 f047f90f Iustin Pop
import qualified Text.JSON as J
43 f047f90f Iustin Pop
44 f047f90f Iustin Pop
-- * JSON-related functions
45 f047f90f Iustin Pop
46 f047f90f Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
47 f047f90f Iustin Pop
type JSRecord = [(String, J.JSValue)]
48 f047f90f Iustin Pop
49 f047f90f Iustin Pop
-- | Converts a JSON Result into a monadic value.
50 f047f90f Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
51 f047f90f Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
52 f047f90f Iustin Pop
fromJResult _ (J.Ok x) = return x
53 f047f90f Iustin Pop
54 f047f90f Iustin Pop
-- | Tries to read a string from a JSON value.
55 f047f90f Iustin Pop
--
56 f047f90f Iustin Pop
-- In case the value was not a string, we fail the read (in the
57 f047f90f Iustin Pop
-- context of the current monad.
58 f047f90f Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
59 f047f90f Iustin Pop
readEitherString v =
60 f047f90f Iustin Pop
    case v of
61 f047f90f Iustin Pop
      J.JSString s -> return $ J.fromJSString s
62 f047f90f Iustin Pop
      _ -> fail "Wrong JSON type"
63 f047f90f Iustin Pop
64 f047f90f Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
65 f047f90f Iustin Pop
loadJSArray :: (Monad m)
66 f047f90f Iustin Pop
               => String -- ^ Operation description (for error reporting)
67 f047f90f Iustin Pop
               -> String -- ^ Input message
68 f047f90f Iustin Pop
               -> m [J.JSObject J.JSValue]
69 f047f90f Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
70 f047f90f Iustin Pop
71 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object.
72 f047f90f Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
73 f047f90f Iustin Pop
fromObj o k =
74 f047f90f Iustin Pop
    case lookup k o of
75 f047f90f Iustin Pop
      Nothing -> fail $ printf "key '%s' not found, object contains only %s"
76 f047f90f Iustin Pop
                 k (show (map fst o))
77 f047f90f Iustin Pop
      Just val -> fromKeyValue k val
78 f047f90f Iustin Pop
79 f047f90f Iustin Pop
-- | Reads the value of an optional key in a JSON object.
80 f047f90f Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
81 f047f90f Iustin Pop
                JSRecord -> String -> m (Maybe a)
82 f047f90f Iustin Pop
maybeFromObj o k =
83 f047f90f Iustin Pop
    case lookup k o of
84 f047f90f Iustin Pop
      Nothing -> return Nothing
85 f047f90f Iustin Pop
      Just val -> liftM Just (fromKeyValue k val)
86 f047f90f Iustin Pop
87 f047f90f Iustin Pop
-- | Reads the value of a key in a JSON object with a default if missing.
88 f047f90f Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
89 f047f90f Iustin Pop
                      JSRecord -> String -> a -> m a
90 f047f90f Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
91 f047f90f Iustin Pop
92 f047f90f Iustin Pop
-- | Reads a JValue, that originated from an object key.
93 f047f90f Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
94 f047f90f Iustin Pop
              => String     -- ^ The key name
95 f047f90f Iustin Pop
              -> J.JSValue  -- ^ The value to read
96 f047f90f Iustin Pop
              -> m a
97 f047f90f Iustin Pop
fromKeyValue k val =
98 f047f90f Iustin Pop
  fromJResult (printf "key '%s', value '%s'" k (show val)) (J.readJSON val)
99 f047f90f Iustin Pop
100 f047f90f Iustin Pop
-- | Small wrapper over readJSON.
101 f047f90f Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
102 f047f90f Iustin Pop
fromJVal v =
103 f047f90f Iustin Pop
    case J.readJSON v of
104 f047f90f Iustin Pop
      J.Error s -> fail ("Cannot convert value '" ++ show v ++
105 f047f90f Iustin Pop
                         "', error: " ++ s)
106 f047f90f Iustin Pop
      J.Ok x -> return x
107 f047f90f Iustin Pop
108 f047f90f Iustin Pop
-- | Converts a JSON value into a JSON object.
109 f047f90f Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
110 f047f90f Iustin Pop
asJSObject (J.JSObject a) = return a
111 f047f90f Iustin Pop
asJSObject _ = fail "not an object"
112 f047f90f Iustin Pop
113 f047f90f Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
114 f047f90f Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
115 f047f90f Iustin Pop
asObjectList = mapM asJSObject