Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Utils.hs @ 0aff2293

History | View | Annotate | Download (7.6 kB)

1 525bfb36 Iustin Pop
{-| Utility functions. -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 5850e990 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 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 ebf38064 Iustin Pop
  ( debug
26 ebf38064 Iustin Pop
  , debugFn
27 ebf38064 Iustin Pop
  , debugXy
28 ebf38064 Iustin Pop
  , sepSplit
29 ebf38064 Iustin Pop
  , stdDev
30 ebf38064 Iustin Pop
  , if'
31 ebf38064 Iustin Pop
  , select
32 ebf38064 Iustin Pop
  , applyIf
33 ebf38064 Iustin Pop
  , commaJoin
34 79eef90b Agata Murawska
  , ensureQuoted
35 ebf38064 Iustin Pop
  , tryRead
36 ebf38064 Iustin Pop
  , formatTable
37 c3024b7e René Nussbaumer
  , printTable
38 ebf38064 Iustin Pop
  , parseUnit
39 19e310cc René Nussbaumer
  , plural
40 88a10df5 Iustin Pop
  , exitIfBad
41 88a10df5 Iustin Pop
  , exitErr
42 88a10df5 Iustin Pop
  , exitWhen
43 88a10df5 Iustin Pop
  , exitUnless
44 ebf38064 Iustin Pop
  ) where
45 e4f08c46 Iustin Pop
46 79eef90b Agata Murawska
import Data.Char (toUpper, isAlphaNum)
47 29ac5975 Iustin Pop
import Data.List
48 e4f08c46 Iustin Pop
49 e4f08c46 Iustin Pop
import Debug.Trace
50 e4f08c46 Iustin Pop
51 88a10df5 Iustin Pop
import Ganeti.BasicTypes
52 88a10df5 Iustin Pop
import System.IO
53 88a10df5 Iustin Pop
import System.Exit
54 88a10df5 Iustin Pop
55 9188aeef Iustin Pop
-- * Debug functions
56 9188aeef Iustin Pop
57 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
58 e4f08c46 Iustin Pop
debug :: Show a => a -> a
59 e4f08c46 Iustin Pop
debug x = trace (show x) x
60 e4f08c46 Iustin Pop
61 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
62 525bfb36 Iustin Pop
-- it.
63 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
64 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
65 adc5c176 Iustin Pop
66 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
67 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
68 05ff7a00 Agata Murawska
debugXy = seq . debug
69 adc5c176 Iustin Pop
70 525bfb36 Iustin Pop
-- * Miscellaneous
71 1b7cf8ca Iustin Pop
72 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
73 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
74 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
75 61bbbed7 Agata Murawska
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 ebf38064 Iustin Pop
  | null s    = []
84 ebf38064 Iustin Pop
  | null xs   = [x]
85 ebf38064 Iustin Pop
  | null ys   = [x,[]]
86 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
87 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
88 ebf38064 Iustin Pop
        ys = drop 1 xs
89 e4f08c46 Iustin Pop
90 19e310cc René Nussbaumer
-- | Simple pluralize helper
91 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
92 19e310cc René Nussbaumer
plural 1 s _ = s
93 19e310cc René Nussbaumer
plural _ _ p = p
94 19e310cc René Nussbaumer
95 79eef90b Agata Murawska
-- | Ensure a value is quoted if needed.
96 79eef90b Agata Murawska
ensureQuoted :: String -> String
97 79eef90b Agata Murawska
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
98 79eef90b Agata Murawska
                 then '\'':v ++ "'"
99 79eef90b Agata Murawska
                 else v
100 79eef90b Agata Murawska
101 9188aeef Iustin Pop
-- * Mathematical functions
102 9188aeef Iustin Pop
103 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
104 185297fa Iustin Pop
-- versions
105 e4f08c46 Iustin Pop
106 525bfb36 Iustin Pop
-- | Standard deviation function.
107 4715711d Iustin Pop
stdDev :: [Double] -> Double
108 4715711d Iustin Pop
stdDev lst =
109 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
110 7570569e Iustin Pop
  -- for performance reasons
111 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
112 7570569e Iustin Pop
                           let rl' = rl + 1
113 7570569e Iustin Pop
                               rs' = rs + e
114 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
115 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
116 7570569e Iustin Pop
      mv = sx / ll
117 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
118 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
119 dd4c56ed Iustin Pop
120 bfe6c954 Guido Trotter
-- *  Logical functions
121 bfe6c954 Guido Trotter
122 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
123 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
124 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
125 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
126 bfe6c954 Guido Trotter
127 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
128 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
129 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
130 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
131 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
132 bfe6c954 Guido Trotter
if' True x _ = x
133 bfe6c954 Guido Trotter
if' _    _ y = y
134 bfe6c954 Guido Trotter
135 5b763470 Iustin Pop
-- * Parsing utility functions
136 5b763470 Iustin Pop
137 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
138 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
139 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
140 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
141 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
142 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
143 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
144 5b763470 Iustin Pop
145 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
146 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
147 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
148 c5f7412e Iustin Pop
149 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
150 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
151 c5f7412e Iustin Pop
formatTable vals numpos =
152 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
153 c5f7412e Iustin Pop
                                 -- rather than columns
154 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
155 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
156 c5f7412e Iustin Pop
                         map (\val ->
157 c5f7412e Iustin Pop
                                  let delta = ml - length val
158 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
159 c5f7412e Iustin Pop
                                  in if delta > 0
160 c5f7412e Iustin Pop
                                     then if isnum
161 c5f7412e Iustin Pop
                                          then filler ++ val
162 c5f7412e Iustin Pop
                                          else val ++ filler
163 c5f7412e Iustin Pop
                                     else val
164 c5f7412e Iustin Pop
                             ) flds
165 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
166 c5f7412e Iustin Pop
   in transpose expnd
167 9b9da389 Iustin Pop
168 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
169 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
170 c3024b7e René Nussbaumer
printTable lp header rows isnum =
171 c3024b7e René Nussbaumer
  unlines . map ((++) lp) . map ((:) ' ' . unwords) $
172 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
173 c3024b7e René Nussbaumer
174 1cdcf8f3 Iustin Pop
-- | Converts a unit (e.g. m or GB) into a scaling factor.
175 1cdcf8f3 Iustin Pop
parseUnitValue :: (Monad m) => String -> m Rational
176 1cdcf8f3 Iustin Pop
parseUnitValue unit
177 1cdcf8f3 Iustin Pop
  -- binary conversions first
178 1cdcf8f3 Iustin Pop
  | null unit                     = return 1
179 1cdcf8f3 Iustin Pop
  | unit == "m" || upper == "MIB" = return 1
180 1cdcf8f3 Iustin Pop
  | unit == "g" || upper == "GIB" = return kbBinary
181 1cdcf8f3 Iustin Pop
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
182 1cdcf8f3 Iustin Pop
  -- SI conversions
183 1cdcf8f3 Iustin Pop
  | unit == "M" || upper == "MB"  = return mbFactor
184 1cdcf8f3 Iustin Pop
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
185 1cdcf8f3 Iustin Pop
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
186 1cdcf8f3 Iustin Pop
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
187 1cdcf8f3 Iustin Pop
  where upper = map toUpper unit
188 5850e990 Iustin Pop
        kbBinary = 1024 :: Rational
189 5850e990 Iustin Pop
        kbDecimal = 1000 :: Rational
190 1cdcf8f3 Iustin Pop
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
191 1cdcf8f3 Iustin Pop
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
192 1cdcf8f3 Iustin Pop
193 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
194 1cb92fac Iustin Pop
--
195 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
196 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
197 1cb92fac Iustin Pop
-- value in MiB.
198 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
199 1cb92fac Iustin Pop
parseUnit str =
200 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
201 ebf38064 Iustin Pop
  -- accepting floating-point numbers
202 1cdcf8f3 Iustin Pop
  case (reads str::[(Int, String)]) of
203 ebf38064 Iustin Pop
    [(v, suffix)] ->
204 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
205 1cdcf8f3 Iustin Pop
      in do
206 1cdcf8f3 Iustin Pop
        scaling <- parseUnitValue unit
207 1cdcf8f3 Iustin Pop
        return $ truncate (fromIntegral v * scaling)
208 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
209 88a10df5 Iustin Pop
210 88a10df5 Iustin Pop
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
211 88a10df5 Iustin Pop
-- otherwise returning the actual contained value.
212 88a10df5 Iustin Pop
exitIfBad :: String -> Result a -> IO a
213 88a10df5 Iustin Pop
exitIfBad msg (Bad s) = do
214 88a10df5 Iustin Pop
  hPutStrLn stderr $ "Error: " ++ msg ++ ": " ++ s
215 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
216 88a10df5 Iustin Pop
exitIfBad _ (Ok v) = return v
217 88a10df5 Iustin Pop
218 88a10df5 Iustin Pop
-- | Exits immediately with an error message.
219 88a10df5 Iustin Pop
exitErr :: String -> IO a
220 88a10df5 Iustin Pop
exitErr errmsg = do
221 88a10df5 Iustin Pop
  hPutStrLn stderr $ "Error: " ++ errmsg ++ "."
222 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
223 88a10df5 Iustin Pop
224 88a10df5 Iustin Pop
-- | Exits with an error message if the given boolean condition if true.
225 88a10df5 Iustin Pop
exitWhen :: Bool -> String -> IO ()
226 88a10df5 Iustin Pop
exitWhen True msg = exitErr msg
227 88a10df5 Iustin Pop
exitWhen False _  = return ()
228 88a10df5 Iustin Pop
229 88a10df5 Iustin Pop
-- | Exits with an error message /unless/ the given boolean condition
230 88a10df5 Iustin Pop
-- if true, the opposite of 'exitWhen'.
231 88a10df5 Iustin Pop
exitUnless :: Bool -> String -> IO ()
232 88a10df5 Iustin Pop
exitUnless cond = exitWhen (not cond)