Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Utils.hs @ 00152519

History | View | Annotate | Download (7.4 kB)

1 525bfb36 Iustin Pop
{-| Utility functions. -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 e8230242 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
8 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
9 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
10 e2fa2baf Iustin Pop
(at your option) any later version.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
13 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
14 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15 e2fa2baf Iustin Pop
General Public License for more details.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
18 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
19 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
20 e2fa2baf Iustin Pop
02110-1301, USA.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
-}
23 e2fa2baf Iustin Pop
24 209b3711 Iustin Pop
module Ganeti.HTools.Utils
25 209b3711 Iustin Pop
    (
26 209b3711 Iustin Pop
      debug
27 adc5c176 Iustin Pop
    , debugFn
28 adc5c176 Iustin Pop
    , debugXy
29 209b3711 Iustin Pop
    , sepSplit
30 4715711d Iustin Pop
    , stdDev
31 3d7cd10b Iustin Pop
    , commaJoin
32 9ba5c28f Iustin Pop
    , readEitherString
33 28f19313 Iustin Pop
    , JSRecord
34 9ba5c28f Iustin Pop
    , loadJSArray
35 9ba5c28f Iustin Pop
    , fromObj
36 a810ad21 Iustin Pop
    , fromObjWithDefault
37 f36a8028 Iustin Pop
    , maybeFromObj
38 117dc2d8 Iustin Pop
    , tryFromObj
39 117dc2d8 Iustin Pop
    , fromJVal
40 3f6af65c Iustin Pop
    , asJSObject
41 3f6af65c Iustin Pop
    , asObjectList
42 942403e6 Iustin Pop
    , fromJResult
43 5b763470 Iustin Pop
    , tryRead
44 c5f7412e Iustin Pop
    , formatTable
45 117dc2d8 Iustin Pop
    , annotateResult
46 c4d98278 Iustin Pop
    , defaultGroupID
47 209b3711 Iustin Pop
    ) where
48 e4f08c46 Iustin Pop
49 f36a8028 Iustin Pop
import Control.Monad (liftM)
50 29ac5975 Iustin Pop
import Data.List
51 a810ad21 Iustin Pop
import Data.Maybe (fromMaybe)
52 942403e6 Iustin Pop
import qualified Text.JSON as J
53 9ba5c28f Iustin Pop
import Text.Printf (printf)
54 e4f08c46 Iustin Pop
55 e4f08c46 Iustin Pop
import Debug.Trace
56 e4f08c46 Iustin Pop
57 117dc2d8 Iustin Pop
import Ganeti.HTools.Types
58 117dc2d8 Iustin Pop
59 9188aeef Iustin Pop
-- * Debug functions
60 9188aeef Iustin Pop
61 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
62 e4f08c46 Iustin Pop
debug :: Show a => a -> a
63 e4f08c46 Iustin Pop
debug x = trace (show x) x
64 e4f08c46 Iustin Pop
65 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
66 525bfb36 Iustin Pop
-- it.
67 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
68 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
69 adc5c176 Iustin Pop
70 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
71 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
72 adc5c176 Iustin Pop
debugXy a b = debug a `seq` b
73 adc5c176 Iustin Pop
74 525bfb36 Iustin Pop
-- * Miscellaneous
75 1b7cf8ca Iustin Pop
76 e4f08c46 Iustin Pop
-- | Comma-join a string list.
77 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
78 e4f08c46 Iustin Pop
commaJoin = intercalate ","
79 e4f08c46 Iustin Pop
80 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
81 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
82 e4f08c46 Iustin Pop
sepSplit sep s
83 748d5d50 Iustin Pop
    | null s    = []
84 748d5d50 Iustin Pop
    | null xs   = [x]
85 748d5d50 Iustin Pop
    | null ys   = [x,[]]
86 748d5d50 Iustin Pop
    | otherwise = x:sepSplit sep ys
87 e4f08c46 Iustin Pop
    where (x, xs) = break (== sep) s
88 e4f08c46 Iustin Pop
          ys = drop 1 xs
89 e4f08c46 Iustin Pop
90 9188aeef Iustin Pop
-- * Mathematical functions
91 9188aeef Iustin Pop
92 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
93 185297fa Iustin Pop
-- versions
94 e4f08c46 Iustin Pop
95 525bfb36 Iustin Pop
-- | Standard deviation function.
96 4715711d Iustin Pop
stdDev :: [Double] -> Double
97 4715711d Iustin Pop
stdDev lst =
98 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
99 7570569e Iustin Pop
  -- for performance reasons
100 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
101 7570569e Iustin Pop
                           let rl' = rl + 1
102 7570569e Iustin Pop
                               rs' = rs + e
103 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
104 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
105 7570569e Iustin Pop
      mv = sx / ll
106 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
107 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
108 dd4c56ed Iustin Pop
109 9188aeef Iustin Pop
-- * JSON-related functions
110 9188aeef Iustin Pop
111 525bfb36 Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
112 28f19313 Iustin Pop
type JSRecord = [(String, J.JSValue)]
113 28f19313 Iustin Pop
114 9188aeef Iustin Pop
-- | Converts a JSON Result into a monadic value.
115 c96d44df Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
116 c96d44df Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
117 c96d44df Iustin Pop
fromJResult _ (J.Ok x) = return x
118 50d26669 Iustin Pop
119 9188aeef Iustin Pop
-- | Tries to read a string from a JSON value.
120 9188aeef Iustin Pop
--
121 9188aeef Iustin Pop
-- In case the value was not a string, we fail the read (in the
122 9188aeef Iustin Pop
-- context of the current monad.
123 5aa48dbe Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
124 9ba5c28f Iustin Pop
readEitherString v =
125 9ba5c28f Iustin Pop
    case v of
126 5aa48dbe Iustin Pop
      J.JSString s -> return $ J.fromJSString s
127 5aa48dbe Iustin Pop
      _ -> fail "Wrong JSON type"
128 9ba5c28f Iustin Pop
129 9188aeef Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
130 c8b662f1 Iustin Pop
loadJSArray :: (Monad m)
131 c8b662f1 Iustin Pop
               => String -- ^ Operation description (for error reporting)
132 c8b662f1 Iustin Pop
               -> String -- ^ Input message
133 c8b662f1 Iustin Pop
               -> m [J.JSObject J.JSValue]
134 c96d44df Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
135 9ba5c28f Iustin Pop
136 f36a8028 Iustin Pop
-- | Reads the value of a key in a JSON object.
137 28f19313 Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
138 e8230242 Iustin Pop
fromObj o k =
139 262f3e6c Iustin Pop
    case lookup k o of
140 2befdc14 Iustin Pop
      Nothing -> fail $ printf "key '%s' not found, object contains only %s"
141 2befdc14 Iustin Pop
                 k (show (map fst o))
142 f36a8028 Iustin Pop
      Just val -> fromKeyValue k val
143 f36a8028 Iustin Pop
144 f36a8028 Iustin Pop
-- | Reads the value of an optional key in a JSON object.
145 e8230242 Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
146 28f19313 Iustin Pop
                JSRecord -> String -> m (Maybe a)
147 e8230242 Iustin Pop
maybeFromObj o k =
148 f36a8028 Iustin Pop
    case lookup k o of
149 f36a8028 Iustin Pop
      Nothing -> return Nothing
150 f36a8028 Iustin Pop
      Just val -> liftM Just (fromKeyValue k val)
151 f36a8028 Iustin Pop
152 a810ad21 Iustin Pop
-- | Reads the value of a key in a JSON object with a default if missing.
153 a810ad21 Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
154 28f19313 Iustin Pop
                      JSRecord -> String -> a -> m a
155 a810ad21 Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
156 a810ad21 Iustin Pop
157 525bfb36 Iustin Pop
-- | Reads a JValue, that originated from an object key.
158 f36a8028 Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
159 f36a8028 Iustin Pop
              => String     -- ^ The key name
160 f36a8028 Iustin Pop
              -> J.JSValue  -- ^ The value to read
161 f36a8028 Iustin Pop
              -> m a
162 f36a8028 Iustin Pop
fromKeyValue k val =
163 f36a8028 Iustin Pop
  fromJResult (printf "key '%s', value '%s'" k (show val)) (J.readJSON val)
164 9ba5c28f Iustin Pop
165 525bfb36 Iustin Pop
-- | Annotate a Result with an ownership information.
166 117dc2d8 Iustin Pop
annotateResult :: String -> Result a -> Result a
167 117dc2d8 Iustin Pop
annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s
168 117dc2d8 Iustin Pop
annotateResult _ v = v
169 117dc2d8 Iustin Pop
170 117dc2d8 Iustin Pop
-- | Try to extract a key from a object with better error reporting
171 525bfb36 Iustin Pop
-- than fromObj.
172 117dc2d8 Iustin Pop
tryFromObj :: (J.JSON a) =>
173 28f19313 Iustin Pop
              String     -- ^ Textual "owner" in error messages
174 28f19313 Iustin Pop
           -> JSRecord   -- ^ The object array
175 28f19313 Iustin Pop
           -> String     -- ^ The desired key from the object
176 a083e855 Iustin Pop
           -> Result a
177 e8230242 Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
178 117dc2d8 Iustin Pop
179 117dc2d8 Iustin Pop
-- | Small wrapper over readJSON.
180 117dc2d8 Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
181 117dc2d8 Iustin Pop
fromJVal v =
182 117dc2d8 Iustin Pop
    case J.readJSON v of
183 39420403 Iustin Pop
      J.Error s -> fail ("Cannot convert value '" ++ show v ++
184 39420403 Iustin Pop
                         "', error: " ++ s)
185 117dc2d8 Iustin Pop
      J.Ok x -> return x
186 117dc2d8 Iustin Pop
187 9188aeef Iustin Pop
-- | Converts a JSON value into a JSON object.
188 5aa48dbe Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
189 5aa48dbe Iustin Pop
asJSObject (J.JSObject a) = return a
190 5aa48dbe Iustin Pop
asJSObject _ = fail "not an object"
191 942403e6 Iustin Pop
192 9188aeef Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
193 5aa48dbe Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
194 9f6dcdea Iustin Pop
asObjectList = mapM asJSObject
195 5b763470 Iustin Pop
196 5b763470 Iustin Pop
-- * Parsing utility functions
197 5b763470 Iustin Pop
198 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
199 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
200 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
201 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
202 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
203 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
204 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
205 5b763470 Iustin Pop
206 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
207 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
208 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
209 c5f7412e Iustin Pop
210 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
211 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
212 c5f7412e Iustin Pop
formatTable vals numpos =
213 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
214 c5f7412e Iustin Pop
                                 -- rather than columns
215 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
216 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
217 c5f7412e Iustin Pop
                         map (\val ->
218 c5f7412e Iustin Pop
                                  let delta = ml - length val
219 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
220 c5f7412e Iustin Pop
                                  in if delta > 0
221 c5f7412e Iustin Pop
                                     then if isnum
222 c5f7412e Iustin Pop
                                          then filler ++ val
223 c5f7412e Iustin Pop
                                          else val ++ filler
224 c5f7412e Iustin Pop
                                     else val
225 c5f7412e Iustin Pop
                             ) flds
226 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
227 c5f7412e Iustin Pop
   in transpose expnd
228 9b9da389 Iustin Pop
229 525bfb36 Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
230 c4d98278 Iustin Pop
defaultGroupID :: GroupID
231 c4d98278 Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"