Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Utils.hs @ 97936d51

History | View | Annotate | Download (9.7 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 bfe6c954 Guido Trotter
    , if'
32 bfe6c954 Guido Trotter
    , select
33 3d7cd10b Iustin Pop
    , commaJoin
34 9ba5c28f Iustin Pop
    , readEitherString
35 28f19313 Iustin Pop
    , JSRecord
36 9ba5c28f Iustin Pop
    , loadJSArray
37 9ba5c28f Iustin Pop
    , fromObj
38 a810ad21 Iustin Pop
    , fromObjWithDefault
39 f36a8028 Iustin Pop
    , maybeFromObj
40 117dc2d8 Iustin Pop
    , tryFromObj
41 117dc2d8 Iustin Pop
    , fromJVal
42 3f6af65c Iustin Pop
    , asJSObject
43 3f6af65c Iustin Pop
    , asObjectList
44 942403e6 Iustin Pop
    , fromJResult
45 5b763470 Iustin Pop
    , tryRead
46 c5f7412e Iustin Pop
    , formatTable
47 117dc2d8 Iustin Pop
    , annotateResult
48 c4d98278 Iustin Pop
    , defaultGroupID
49 1cb92fac Iustin Pop
    , parseUnit
50 209b3711 Iustin Pop
    ) where
51 e4f08c46 Iustin Pop
52 f36a8028 Iustin Pop
import Control.Monad (liftM)
53 1cb92fac Iustin Pop
import Data.Char (toUpper)
54 29ac5975 Iustin Pop
import Data.List
55 a810ad21 Iustin Pop
import Data.Maybe (fromMaybe)
56 942403e6 Iustin Pop
import qualified Text.JSON as J
57 9ba5c28f Iustin Pop
import Text.Printf (printf)
58 e4f08c46 Iustin Pop
59 e4f08c46 Iustin Pop
import Debug.Trace
60 e4f08c46 Iustin Pop
61 117dc2d8 Iustin Pop
import Ganeti.HTools.Types
62 117dc2d8 Iustin Pop
63 9188aeef Iustin Pop
-- * Debug functions
64 9188aeef Iustin Pop
65 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
66 e4f08c46 Iustin Pop
debug :: Show a => a -> a
67 e4f08c46 Iustin Pop
debug x = trace (show x) x
68 e4f08c46 Iustin Pop
69 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
70 525bfb36 Iustin Pop
-- it.
71 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
72 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
73 adc5c176 Iustin Pop
74 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
75 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
76 adc5c176 Iustin Pop
debugXy a b = debug a `seq` b
77 adc5c176 Iustin Pop
78 525bfb36 Iustin Pop
-- * Miscellaneous
79 1b7cf8ca Iustin Pop
80 e4f08c46 Iustin Pop
-- | Comma-join a string list.
81 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
82 e4f08c46 Iustin Pop
commaJoin = intercalate ","
83 e4f08c46 Iustin Pop
84 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
85 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
86 e4f08c46 Iustin Pop
sepSplit sep s
87 748d5d50 Iustin Pop
    | null s    = []
88 748d5d50 Iustin Pop
    | null xs   = [x]
89 748d5d50 Iustin Pop
    | null ys   = [x,[]]
90 748d5d50 Iustin Pop
    | otherwise = x:sepSplit sep ys
91 e4f08c46 Iustin Pop
    where (x, xs) = break (== sep) s
92 e4f08c46 Iustin Pop
          ys = drop 1 xs
93 e4f08c46 Iustin Pop
94 9188aeef Iustin Pop
-- * Mathematical functions
95 9188aeef Iustin Pop
96 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
97 185297fa Iustin Pop
-- versions
98 e4f08c46 Iustin Pop
99 525bfb36 Iustin Pop
-- | Standard deviation function.
100 4715711d Iustin Pop
stdDev :: [Double] -> Double
101 4715711d Iustin Pop
stdDev lst =
102 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
103 7570569e Iustin Pop
  -- for performance reasons
104 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
105 7570569e Iustin Pop
                           let rl' = rl + 1
106 7570569e Iustin Pop
                               rs' = rs + e
107 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
108 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
109 7570569e Iustin Pop
      mv = sx / ll
110 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
111 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
112 dd4c56ed Iustin Pop
113 bfe6c954 Guido Trotter
-- *  Logical functions
114 bfe6c954 Guido Trotter
115 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
116 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
117 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
118 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
119 bfe6c954 Guido Trotter
120 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
121 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
122 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
123 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
124 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
125 bfe6c954 Guido Trotter
if' True x _ = x
126 bfe6c954 Guido Trotter
if' _    _ y = y
127 bfe6c954 Guido Trotter
128 bfe6c954 Guido Trotter
-- | Return the first result with a True condition, or the default otherwise.
129 bfe6c954 Guido Trotter
select :: a            -- ^ default result
130 bfe6c954 Guido Trotter
       -> [(Bool, a)]  -- ^ list of \"condition, result\"
131 bfe6c954 Guido Trotter
       -> a            -- ^ first result which has a True condition, or default
132 bfe6c954 Guido Trotter
select def = maybe def snd . find fst
133 bfe6c954 Guido Trotter
134 9188aeef Iustin Pop
-- * JSON-related functions
135 9188aeef Iustin Pop
136 525bfb36 Iustin Pop
-- | A type alias for the list-based representation of J.JSObject.
137 28f19313 Iustin Pop
type JSRecord = [(String, J.JSValue)]
138 28f19313 Iustin Pop
139 9188aeef Iustin Pop
-- | Converts a JSON Result into a monadic value.
140 c96d44df Iustin Pop
fromJResult :: Monad m => String -> J.Result a -> m a
141 c96d44df Iustin Pop
fromJResult s (J.Error x) = fail (s ++ ": " ++ x)
142 c96d44df Iustin Pop
fromJResult _ (J.Ok x) = return x
143 50d26669 Iustin Pop
144 9188aeef Iustin Pop
-- | Tries to read a string from a JSON value.
145 9188aeef Iustin Pop
--
146 9188aeef Iustin Pop
-- In case the value was not a string, we fail the read (in the
147 9188aeef Iustin Pop
-- context of the current monad.
148 5aa48dbe Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
149 9ba5c28f Iustin Pop
readEitherString v =
150 9ba5c28f Iustin Pop
    case v of
151 5aa48dbe Iustin Pop
      J.JSString s -> return $ J.fromJSString s
152 5aa48dbe Iustin Pop
      _ -> fail "Wrong JSON type"
153 9ba5c28f Iustin Pop
154 9188aeef Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
155 c8b662f1 Iustin Pop
loadJSArray :: (Monad m)
156 c8b662f1 Iustin Pop
               => String -- ^ Operation description (for error reporting)
157 c8b662f1 Iustin Pop
               -> String -- ^ Input message
158 c8b662f1 Iustin Pop
               -> m [J.JSObject J.JSValue]
159 c96d44df Iustin Pop
loadJSArray s = fromJResult s . J.decodeStrict
160 9ba5c28f Iustin Pop
161 f36a8028 Iustin Pop
-- | Reads the value of a key in a JSON object.
162 28f19313 Iustin Pop
fromObj :: (J.JSON a, Monad m) => JSRecord -> String -> m a
163 e8230242 Iustin Pop
fromObj o k =
164 262f3e6c Iustin Pop
    case lookup k o of
165 2befdc14 Iustin Pop
      Nothing -> fail $ printf "key '%s' not found, object contains only %s"
166 2befdc14 Iustin Pop
                 k (show (map fst o))
167 f36a8028 Iustin Pop
      Just val -> fromKeyValue k val
168 f36a8028 Iustin Pop
169 f36a8028 Iustin Pop
-- | Reads the value of an optional key in a JSON object.
170 e8230242 Iustin Pop
maybeFromObj :: (J.JSON a, Monad m) =>
171 28f19313 Iustin Pop
                JSRecord -> String -> m (Maybe a)
172 e8230242 Iustin Pop
maybeFromObj o k =
173 f36a8028 Iustin Pop
    case lookup k o of
174 f36a8028 Iustin Pop
      Nothing -> return Nothing
175 f36a8028 Iustin Pop
      Just val -> liftM Just (fromKeyValue k val)
176 f36a8028 Iustin Pop
177 a810ad21 Iustin Pop
-- | Reads the value of a key in a JSON object with a default if missing.
178 a810ad21 Iustin Pop
fromObjWithDefault :: (J.JSON a, Monad m) =>
179 28f19313 Iustin Pop
                      JSRecord -> String -> a -> m a
180 a810ad21 Iustin Pop
fromObjWithDefault o k d = liftM (fromMaybe d) $ maybeFromObj o k
181 a810ad21 Iustin Pop
182 525bfb36 Iustin Pop
-- | Reads a JValue, that originated from an object key.
183 f36a8028 Iustin Pop
fromKeyValue :: (J.JSON a, Monad m)
184 f36a8028 Iustin Pop
              => String     -- ^ The key name
185 f36a8028 Iustin Pop
              -> J.JSValue  -- ^ The value to read
186 f36a8028 Iustin Pop
              -> m a
187 f36a8028 Iustin Pop
fromKeyValue k val =
188 f36a8028 Iustin Pop
  fromJResult (printf "key '%s', value '%s'" k (show val)) (J.readJSON val)
189 9ba5c28f Iustin Pop
190 525bfb36 Iustin Pop
-- | Annotate a Result with an ownership information.
191 117dc2d8 Iustin Pop
annotateResult :: String -> Result a -> Result a
192 117dc2d8 Iustin Pop
annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s
193 117dc2d8 Iustin Pop
annotateResult _ v = v
194 117dc2d8 Iustin Pop
195 117dc2d8 Iustin Pop
-- | Try to extract a key from a object with better error reporting
196 525bfb36 Iustin Pop
-- than fromObj.
197 117dc2d8 Iustin Pop
tryFromObj :: (J.JSON a) =>
198 28f19313 Iustin Pop
              String     -- ^ Textual "owner" in error messages
199 28f19313 Iustin Pop
           -> JSRecord   -- ^ The object array
200 28f19313 Iustin Pop
           -> String     -- ^ The desired key from the object
201 a083e855 Iustin Pop
           -> Result a
202 e8230242 Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
203 117dc2d8 Iustin Pop
204 117dc2d8 Iustin Pop
-- | Small wrapper over readJSON.
205 117dc2d8 Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
206 117dc2d8 Iustin Pop
fromJVal v =
207 117dc2d8 Iustin Pop
    case J.readJSON v of
208 39420403 Iustin Pop
      J.Error s -> fail ("Cannot convert value '" ++ show v ++
209 39420403 Iustin Pop
                         "', error: " ++ s)
210 117dc2d8 Iustin Pop
      J.Ok x -> return x
211 117dc2d8 Iustin Pop
212 9188aeef Iustin Pop
-- | Converts a JSON value into a JSON object.
213 5aa48dbe Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
214 5aa48dbe Iustin Pop
asJSObject (J.JSObject a) = return a
215 5aa48dbe Iustin Pop
asJSObject _ = fail "not an object"
216 942403e6 Iustin Pop
217 9188aeef Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
218 5aa48dbe Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
219 9f6dcdea Iustin Pop
asObjectList = mapM asJSObject
220 5b763470 Iustin Pop
221 5b763470 Iustin Pop
-- * Parsing utility functions
222 5b763470 Iustin Pop
223 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
224 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
225 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
226 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
227 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
228 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
229 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
230 5b763470 Iustin Pop
231 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
232 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
233 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
234 c5f7412e Iustin Pop
235 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
236 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
237 c5f7412e Iustin Pop
formatTable vals numpos =
238 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
239 c5f7412e Iustin Pop
                                 -- rather than columns
240 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
241 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
242 c5f7412e Iustin Pop
                         map (\val ->
243 c5f7412e Iustin Pop
                                  let delta = ml - length val
244 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
245 c5f7412e Iustin Pop
                                  in if delta > 0
246 c5f7412e Iustin Pop
                                     then if isnum
247 c5f7412e Iustin Pop
                                          then filler ++ val
248 c5f7412e Iustin Pop
                                          else val ++ filler
249 c5f7412e Iustin Pop
                                     else val
250 c5f7412e Iustin Pop
                             ) flds
251 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
252 c5f7412e Iustin Pop
   in transpose expnd
253 9b9da389 Iustin Pop
254 525bfb36 Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
255 c4d98278 Iustin Pop
defaultGroupID :: GroupID
256 c4d98278 Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
257 1cb92fac Iustin Pop
258 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
259 1cb92fac Iustin Pop
--
260 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
261 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
262 1cb92fac Iustin Pop
-- value in MiB.
263 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
264 1cb92fac Iustin Pop
parseUnit str =
265 1cb92fac Iustin Pop
    -- TODO: enhance this by splitting the unit parsing code out and
266 1cb92fac Iustin Pop
    -- accepting floating-point numbers
267 1cb92fac Iustin Pop
    case reads str of
268 1cb92fac Iustin Pop
      [(v, suffix)] ->
269 1cb92fac Iustin Pop
          let unit = dropWhile (== ' ') suffix
270 1cb92fac Iustin Pop
              upper = map toUpper unit
271 1cb92fac Iustin Pop
              siConvert x = x * 1000000 `div` 1048576
272 1cb92fac Iustin Pop
          in case () of
273 1cb92fac Iustin Pop
               _ | null unit -> return v
274 1cb92fac Iustin Pop
                 | unit == "m" || upper == "MIB" -> return v
275 1cb92fac Iustin Pop
                 | unit == "M" || upper == "MB"  -> return $ siConvert v
276 1cb92fac Iustin Pop
                 | unit == "g" || upper == "GIB" -> return $ v * 1024
277 1cb92fac Iustin Pop
                 | unit == "G" || upper == "GB"  -> return $ siConvert
278 1cb92fac Iustin Pop
                                                    (v * 1000)
279 1cb92fac Iustin Pop
                 | unit == "t" || upper == "TIB" -> return $ v * 1048576
280 1cb92fac Iustin Pop
                 | unit == "T" || upper == "TB"  -> return $
281 1cb92fac Iustin Pop
                                                    siConvert (v * 1000000)
282 1cb92fac Iustin Pop
                 | otherwise -> fail $ "Unknown unit '" ++ unit ++ "'"
283 1cb92fac Iustin Pop
      _ -> fail $ "Can't parse string '" ++ str ++ "'"