Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (7.2 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 61bbbed7 Agata Murawska
    , applyIf
34 3d7cd10b Iustin Pop
    , commaJoin
35 9ba5c28f Iustin Pop
    , readEitherString
36 28f19313 Iustin Pop
    , JSRecord
37 9ba5c28f Iustin Pop
    , loadJSArray
38 9ba5c28f Iustin Pop
    , fromObj
39 a810ad21 Iustin Pop
    , fromObjWithDefault
40 f36a8028 Iustin Pop
    , maybeFromObj
41 117dc2d8 Iustin Pop
    , tryFromObj
42 117dc2d8 Iustin Pop
    , fromJVal
43 3f6af65c Iustin Pop
    , asJSObject
44 3f6af65c Iustin Pop
    , asObjectList
45 942403e6 Iustin Pop
    , fromJResult
46 5b763470 Iustin Pop
    , tryRead
47 c5f7412e Iustin Pop
    , formatTable
48 117dc2d8 Iustin Pop
    , annotateResult
49 c4d98278 Iustin Pop
    , defaultGroupID
50 1cb92fac Iustin Pop
    , parseUnit
51 209b3711 Iustin Pop
    ) where
52 e4f08c46 Iustin Pop
53 1cb92fac Iustin Pop
import Data.Char (toUpper)
54 29ac5975 Iustin Pop
import Data.List
55 942403e6 Iustin Pop
import qualified Text.JSON as J
56 e4f08c46 Iustin Pop
57 e4f08c46 Iustin Pop
import Debug.Trace
58 e4f08c46 Iustin Pop
59 117dc2d8 Iustin Pop
import Ganeti.HTools.Types
60 f047f90f Iustin Pop
-- we will re-export these for our existing users
61 f047f90f Iustin Pop
import Ganeti.HTools.JSON
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 05ff7a00 Agata Murawska
debugXy = seq . debug
77 adc5c176 Iustin Pop
78 525bfb36 Iustin Pop
-- * Miscellaneous
79 1b7cf8ca Iustin Pop
80 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
81 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
82 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
83 61bbbed7 Agata Murawska
84 e4f08c46 Iustin Pop
-- | Comma-join a string list.
85 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
86 e4f08c46 Iustin Pop
commaJoin = intercalate ","
87 e4f08c46 Iustin Pop
88 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
89 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
90 e4f08c46 Iustin Pop
sepSplit sep s
91 748d5d50 Iustin Pop
    | null s    = []
92 748d5d50 Iustin Pop
    | null xs   = [x]
93 748d5d50 Iustin Pop
    | null ys   = [x,[]]
94 748d5d50 Iustin Pop
    | otherwise = x:sepSplit sep ys
95 e4f08c46 Iustin Pop
    where (x, xs) = break (== sep) s
96 e4f08c46 Iustin Pop
          ys = drop 1 xs
97 e4f08c46 Iustin Pop
98 9188aeef Iustin Pop
-- * Mathematical functions
99 9188aeef Iustin Pop
100 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
101 185297fa Iustin Pop
-- versions
102 e4f08c46 Iustin Pop
103 525bfb36 Iustin Pop
-- | Standard deviation function.
104 4715711d Iustin Pop
stdDev :: [Double] -> Double
105 4715711d Iustin Pop
stdDev lst =
106 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
107 7570569e Iustin Pop
  -- for performance reasons
108 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
109 7570569e Iustin Pop
                           let rl' = rl + 1
110 7570569e Iustin Pop
                               rs' = rs + e
111 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
112 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
113 7570569e Iustin Pop
      mv = sx / ll
114 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
115 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
116 dd4c56ed Iustin Pop
117 bfe6c954 Guido Trotter
-- *  Logical functions
118 bfe6c954 Guido Trotter
119 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
120 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
121 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
122 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
123 bfe6c954 Guido Trotter
124 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
125 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
126 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
127 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
128 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
129 bfe6c954 Guido Trotter
if' True x _ = x
130 bfe6c954 Guido Trotter
if' _    _ y = y
131 bfe6c954 Guido Trotter
132 bfe6c954 Guido Trotter
-- | Return the first result with a True condition, or the default otherwise.
133 bfe6c954 Guido Trotter
select :: a            -- ^ default result
134 bfe6c954 Guido Trotter
       -> [(Bool, a)]  -- ^ list of \"condition, result\"
135 bfe6c954 Guido Trotter
       -> a            -- ^ first result which has a True condition, or default
136 bfe6c954 Guido Trotter
select def = maybe def snd . find fst
137 bfe6c954 Guido Trotter
138 9ba5c28f Iustin Pop
139 525bfb36 Iustin Pop
-- | Annotate a Result with an ownership information.
140 117dc2d8 Iustin Pop
annotateResult :: String -> Result a -> Result a
141 117dc2d8 Iustin Pop
annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s
142 117dc2d8 Iustin Pop
annotateResult _ v = v
143 117dc2d8 Iustin Pop
144 117dc2d8 Iustin Pop
-- | Try to extract a key from a object with better error reporting
145 525bfb36 Iustin Pop
-- than fromObj.
146 117dc2d8 Iustin Pop
tryFromObj :: (J.JSON a) =>
147 28f19313 Iustin Pop
              String     -- ^ Textual "owner" in error messages
148 28f19313 Iustin Pop
           -> JSRecord   -- ^ The object array
149 28f19313 Iustin Pop
           -> String     -- ^ The desired key from the object
150 a083e855 Iustin Pop
           -> Result a
151 e8230242 Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
152 117dc2d8 Iustin Pop
153 5b763470 Iustin Pop
154 5b763470 Iustin Pop
-- * Parsing utility functions
155 5b763470 Iustin Pop
156 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
157 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
158 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
159 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
160 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
161 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
162 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
163 5b763470 Iustin Pop
164 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
165 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
166 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
167 c5f7412e Iustin Pop
168 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
169 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
170 c5f7412e Iustin Pop
formatTable vals numpos =
171 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
172 c5f7412e Iustin Pop
                                 -- rather than columns
173 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
174 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
175 c5f7412e Iustin Pop
                         map (\val ->
176 c5f7412e Iustin Pop
                                  let delta = ml - length val
177 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
178 c5f7412e Iustin Pop
                                  in if delta > 0
179 c5f7412e Iustin Pop
                                     then if isnum
180 c5f7412e Iustin Pop
                                          then filler ++ val
181 c5f7412e Iustin Pop
                                          else val ++ filler
182 c5f7412e Iustin Pop
                                     else val
183 c5f7412e Iustin Pop
                             ) flds
184 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
185 c5f7412e Iustin Pop
   in transpose expnd
186 9b9da389 Iustin Pop
187 525bfb36 Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
188 c4d98278 Iustin Pop
defaultGroupID :: GroupID
189 c4d98278 Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
190 1cb92fac Iustin Pop
191 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
192 1cb92fac Iustin Pop
--
193 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
194 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
195 1cb92fac Iustin Pop
-- value in MiB.
196 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
197 1cb92fac Iustin Pop
parseUnit str =
198 1cb92fac Iustin Pop
    -- TODO: enhance this by splitting the unit parsing code out and
199 1cb92fac Iustin Pop
    -- accepting floating-point numbers
200 1cb92fac Iustin Pop
    case reads str of
201 1cb92fac Iustin Pop
      [(v, suffix)] ->
202 1cb92fac Iustin Pop
          let unit = dropWhile (== ' ') suffix
203 1cb92fac Iustin Pop
              upper = map toUpper unit
204 1cb92fac Iustin Pop
              siConvert x = x * 1000000 `div` 1048576
205 1cb92fac Iustin Pop
          in case () of
206 1cb92fac Iustin Pop
               _ | null unit -> return v
207 1cb92fac Iustin Pop
                 | unit == "m" || upper == "MIB" -> return v
208 1cb92fac Iustin Pop
                 | unit == "M" || upper == "MB"  -> return $ siConvert v
209 1cb92fac Iustin Pop
                 | unit == "g" || upper == "GIB" -> return $ v * 1024
210 1cb92fac Iustin Pop
                 | unit == "G" || upper == "GB"  -> return $ siConvert
211 1cb92fac Iustin Pop
                                                    (v * 1000)
212 1cb92fac Iustin Pop
                 | unit == "t" || upper == "TIB" -> return $ v * 1048576
213 1cb92fac Iustin Pop
                 | unit == "T" || upper == "TB"  -> return $
214 1cb92fac Iustin Pop
                                                    siConvert (v * 1000000)
215 1cb92fac Iustin Pop
                 | otherwise -> fail $ "Unknown unit '" ++ unit ++ "'"
216 1cb92fac Iustin Pop
      _ -> fail $ "Can't parse string '" ++ str ++ "'"