Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 7ec2f76b

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 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 26d62e4c Iustin Pop
module Ganeti.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 04edfc99 Iustin Pop
  , niceSort
41 04edfc99 Iustin Pop
  , niceSortKey
42 88a10df5 Iustin Pop
  , exitIfBad
43 88a10df5 Iustin Pop
  , exitErr
44 88a10df5 Iustin Pop
  , exitWhen
45 88a10df5 Iustin Pop
  , exitUnless
46 256e28c4 Iustin Pop
  , rStripSpace
47 80a0546b Michele Tartara
  , newUUID
48 ebf38064 Iustin Pop
  ) where
49 e4f08c46 Iustin Pop
50 256e28c4 Iustin Pop
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
51 04edfc99 Iustin Pop
import Data.Function (on)
52 29ac5975 Iustin Pop
import Data.List
53 e4f08c46 Iustin Pop
54 e4f08c46 Iustin Pop
import Debug.Trace
55 e4f08c46 Iustin Pop
56 88a10df5 Iustin Pop
import Ganeti.BasicTypes
57 80a0546b Michele Tartara
import qualified Ganeti.Constants as C
58 88a10df5 Iustin Pop
import System.IO
59 88a10df5 Iustin Pop
import System.Exit
60 88a10df5 Iustin Pop
61 9188aeef Iustin Pop
-- * Debug functions
62 9188aeef Iustin Pop
63 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
64 e4f08c46 Iustin Pop
debug :: Show a => a -> a
65 e4f08c46 Iustin Pop
debug x = trace (show x) x
66 e4f08c46 Iustin Pop
67 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
68 525bfb36 Iustin Pop
-- it.
69 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
70 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
71 adc5c176 Iustin Pop
72 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
73 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
74 05ff7a00 Agata Murawska
debugXy = seq . debug
75 adc5c176 Iustin Pop
76 525bfb36 Iustin Pop
-- * Miscellaneous
77 1b7cf8ca Iustin Pop
78 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
79 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
80 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
81 61bbbed7 Agata Murawska
82 e4f08c46 Iustin Pop
-- | Comma-join a string list.
83 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
84 e4f08c46 Iustin Pop
commaJoin = intercalate ","
85 e4f08c46 Iustin Pop
86 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
87 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
88 e4f08c46 Iustin Pop
sepSplit sep s
89 ebf38064 Iustin Pop
  | null s    = []
90 ebf38064 Iustin Pop
  | null xs   = [x]
91 ebf38064 Iustin Pop
  | null ys   = [x,[]]
92 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
93 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
94 ebf38064 Iustin Pop
        ys = drop 1 xs
95 e4f08c46 Iustin Pop
96 19e310cc René Nussbaumer
-- | Simple pluralize helper
97 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
98 19e310cc René Nussbaumer
plural 1 s _ = s
99 19e310cc René Nussbaumer
plural _ _ p = p
100 19e310cc René Nussbaumer
101 79eef90b Agata Murawska
-- | Ensure a value is quoted if needed.
102 79eef90b Agata Murawska
ensureQuoted :: String -> String
103 79eef90b Agata Murawska
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
104 79eef90b Agata Murawska
                 then '\'':v ++ "'"
105 79eef90b Agata Murawska
                 else v
106 79eef90b Agata Murawska
107 9188aeef Iustin Pop
-- * Mathematical functions
108 9188aeef Iustin Pop
109 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
110 185297fa Iustin Pop
-- versions
111 e4f08c46 Iustin Pop
112 525bfb36 Iustin Pop
-- | Standard deviation function.
113 4715711d Iustin Pop
stdDev :: [Double] -> Double
114 4715711d Iustin Pop
stdDev lst =
115 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
116 7570569e Iustin Pop
  -- for performance reasons
117 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
118 7570569e Iustin Pop
                           let rl' = rl + 1
119 7570569e Iustin Pop
                               rs' = rs + e
120 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
121 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
122 7570569e Iustin Pop
      mv = sx / ll
123 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
124 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
125 dd4c56ed Iustin Pop
126 bfe6c954 Guido Trotter
-- *  Logical functions
127 bfe6c954 Guido Trotter
128 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
129 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
130 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
131 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
132 bfe6c954 Guido Trotter
133 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
134 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
135 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
136 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
137 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
138 bfe6c954 Guido Trotter
if' True x _ = x
139 bfe6c954 Guido Trotter
if' _    _ y = y
140 bfe6c954 Guido Trotter
141 5b763470 Iustin Pop
-- * Parsing utility functions
142 5b763470 Iustin Pop
143 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
144 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
145 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
146 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
147 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
148 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
149 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
150 5b763470 Iustin Pop
151 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
152 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
153 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
154 c5f7412e Iustin Pop
155 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
156 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
157 c5f7412e Iustin Pop
formatTable vals numpos =
158 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
159 c5f7412e Iustin Pop
                                 -- rather than columns
160 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
161 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
162 c5f7412e Iustin Pop
                         map (\val ->
163 c5f7412e Iustin Pop
                                  let delta = ml - length val
164 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
165 c5f7412e Iustin Pop
                                  in if delta > 0
166 c5f7412e Iustin Pop
                                     then if isnum
167 c5f7412e Iustin Pop
                                          then filler ++ val
168 c5f7412e Iustin Pop
                                          else val ++ filler
169 c5f7412e Iustin Pop
                                     else val
170 c5f7412e Iustin Pop
                             ) flds
171 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
172 c5f7412e Iustin Pop
   in transpose expnd
173 9b9da389 Iustin Pop
174 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
175 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
176 c3024b7e René Nussbaumer
printTable lp header rows isnum =
177 2cdaf225 Iustin Pop
  unlines . map ((++) lp . (:) ' ' . unwords) $
178 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
179 c3024b7e René Nussbaumer
180 1cdcf8f3 Iustin Pop
-- | Converts a unit (e.g. m or GB) into a scaling factor.
181 1cdcf8f3 Iustin Pop
parseUnitValue :: (Monad m) => String -> m Rational
182 1cdcf8f3 Iustin Pop
parseUnitValue unit
183 1cdcf8f3 Iustin Pop
  -- binary conversions first
184 1cdcf8f3 Iustin Pop
  | null unit                     = return 1
185 1cdcf8f3 Iustin Pop
  | unit == "m" || upper == "MIB" = return 1
186 1cdcf8f3 Iustin Pop
  | unit == "g" || upper == "GIB" = return kbBinary
187 1cdcf8f3 Iustin Pop
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
188 1cdcf8f3 Iustin Pop
  -- SI conversions
189 1cdcf8f3 Iustin Pop
  | unit == "M" || upper == "MB"  = return mbFactor
190 1cdcf8f3 Iustin Pop
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
191 1cdcf8f3 Iustin Pop
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
192 1cdcf8f3 Iustin Pop
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
193 1cdcf8f3 Iustin Pop
  where upper = map toUpper unit
194 5850e990 Iustin Pop
        kbBinary = 1024 :: Rational
195 5850e990 Iustin Pop
        kbDecimal = 1000 :: Rational
196 1cdcf8f3 Iustin Pop
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
197 1cdcf8f3 Iustin Pop
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
198 1cdcf8f3 Iustin Pop
199 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
200 1cb92fac Iustin Pop
--
201 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
202 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
203 1cb92fac Iustin Pop
-- value in MiB.
204 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
205 1cb92fac Iustin Pop
parseUnit str =
206 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
207 ebf38064 Iustin Pop
  -- accepting floating-point numbers
208 1cdcf8f3 Iustin Pop
  case (reads str::[(Int, String)]) of
209 ebf38064 Iustin Pop
    [(v, suffix)] ->
210 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
211 1cdcf8f3 Iustin Pop
      in do
212 1cdcf8f3 Iustin Pop
        scaling <- parseUnitValue unit
213 1cdcf8f3 Iustin Pop
        return $ truncate (fromIntegral v * scaling)
214 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
215 88a10df5 Iustin Pop
216 88a10df5 Iustin Pop
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
217 88a10df5 Iustin Pop
-- otherwise returning the actual contained value.
218 88a10df5 Iustin Pop
exitIfBad :: String -> Result a -> IO a
219 707cd3d7 Helga Velroyen
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
220 88a10df5 Iustin Pop
exitIfBad _ (Ok v) = return v
221 88a10df5 Iustin Pop
222 88a10df5 Iustin Pop
-- | Exits immediately with an error message.
223 88a10df5 Iustin Pop
exitErr :: String -> IO a
224 88a10df5 Iustin Pop
exitErr errmsg = do
225 707cd3d7 Helga Velroyen
  hPutStrLn stderr $ "Error: " ++ errmsg
226 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
227 88a10df5 Iustin Pop
228 88a10df5 Iustin Pop
-- | Exits with an error message if the given boolean condition if true.
229 88a10df5 Iustin Pop
exitWhen :: Bool -> String -> IO ()
230 88a10df5 Iustin Pop
exitWhen True msg = exitErr msg
231 88a10df5 Iustin Pop
exitWhen False _  = return ()
232 88a10df5 Iustin Pop
233 88a10df5 Iustin Pop
-- | Exits with an error message /unless/ the given boolean condition
234 88a10df5 Iustin Pop
-- if true, the opposite of 'exitWhen'.
235 88a10df5 Iustin Pop
exitUnless :: Bool -> String -> IO ()
236 88a10df5 Iustin Pop
exitUnless cond = exitWhen (not cond)
237 04edfc99 Iustin Pop
238 04edfc99 Iustin Pop
-- | Helper for 'niceSort'. Computes the key element for a given string.
239 04edfc99 Iustin Pop
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
240 04edfc99 Iustin Pop
           -> String                   -- ^ Remaining string
241 04edfc99 Iustin Pop
           -> ([Either Integer String], String)
242 04edfc99 Iustin Pop
extractKey ek [] = (reverse ek, [])
243 04edfc99 Iustin Pop
extractKey ek xs@(x:_) =
244 04edfc99 Iustin Pop
  let (span_fn, conv_fn) = if isDigit x
245 04edfc99 Iustin Pop
                             then (isDigit, Left . read)
246 04edfc99 Iustin Pop
                             else (not . isDigit, Right)
247 04edfc99 Iustin Pop
      (k, rest) = span span_fn xs
248 04edfc99 Iustin Pop
  in extractKey (conv_fn k:ek) rest
249 04edfc99 Iustin Pop
250 04edfc99 Iustin Pop
{-| Sort a list of strings based on digit and non-digit groupings.
251 04edfc99 Iustin Pop
252 04edfc99 Iustin Pop
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
253 04edfc99 Iustin Pop
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
254 04edfc99 Iustin Pop
255 04edfc99 Iustin Pop
The sort algorithm breaks each name in groups of either only-digits or
256 04edfc99 Iustin Pop
no-digits, and sorts based on each group.
257 04edfc99 Iustin Pop
258 04edfc99 Iustin Pop
Internally, this is not implemented via regexes (like the Python
259 04edfc99 Iustin Pop
version), but via actual splitting of the string in sequences of
260 04edfc99 Iustin Pop
either digits or everything else, and converting the digit sequences
261 04edfc99 Iustin Pop
in /Left Integer/ and the non-digit ones in /Right String/, at which
262 04edfc99 Iustin Pop
point sorting becomes trivial due to the built-in 'Either' ordering;
263 04edfc99 Iustin Pop
we only need one extra step of dropping the key at the end.
264 04edfc99 Iustin Pop
265 04edfc99 Iustin Pop
-}
266 04edfc99 Iustin Pop
niceSort :: [String] -> [String]
267 04edfc99 Iustin Pop
niceSort = map snd . sort . map (\s -> (fst $ extractKey [] s, s))
268 04edfc99 Iustin Pop
269 04edfc99 Iustin Pop
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
270 04edfc99 Iustin Pop
-- since we don't want to add an ordering constraint on the /a/ type,
271 04edfc99 Iustin Pop
-- hence the need to only compare the first element of the /(key, a)/
272 04edfc99 Iustin Pop
-- tuple.
273 04edfc99 Iustin Pop
niceSortKey :: (a -> String) -> [a] -> [a]
274 04edfc99 Iustin Pop
niceSortKey keyfn =
275 04edfc99 Iustin Pop
  map snd . sortBy (compare `on` fst) .
276 04edfc99 Iustin Pop
  map (\s -> (fst . extractKey [] $ keyfn s, s))
277 256e28c4 Iustin Pop
278 256e28c4 Iustin Pop
-- | Strip space characthers (including newline). As this is
279 256e28c4 Iustin Pop
-- expensive, should only be run on small strings.
280 256e28c4 Iustin Pop
rStripSpace :: String -> String
281 256e28c4 Iustin Pop
rStripSpace = reverse . dropWhile isSpace . reverse
282 80a0546b Michele Tartara
283 80a0546b Michele Tartara
-- | Returns a random UUID.
284 80a0546b Michele Tartara
-- This is a Linux-specific method as it uses the /proc filesystem.
285 80a0546b Michele Tartara
newUUID :: IO String
286 80a0546b Michele Tartara
newUUID = do
287 80a0546b Michele Tartara
  contents <- readFile C.randomUuidFile
288 37dfcacb Iustin Pop
  return $! rStripSpace $ take 128 contents