Expand the tiered alloc unittest to check allocation stats
[ganeti-local] / htools / Ganeti / HTools / Utils.hs
1 {-| Utility functions. -}
2
3 {-
4
5 Copyright (C) 2009, 2010, 2011 Google Inc.
6
7 This program is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2 of the License, or
10 (at your option) any later version.
11
12 This program is distributed in the hope that it will be useful, but
13 WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15 General Public License for more details.
16
17 You should have received a copy of the GNU General Public License
18 along with this program; if not, write to the Free Software
19 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
20 02110-1301, USA.
21
22 -}
23
24 module Ganeti.HTools.Utils
25   ( debug
26   , debugFn
27   , debugXy
28   , sepSplit
29   , stdDev
30   , if'
31   , select
32   , applyIf
33   , commaJoin
34   , tryRead
35   , formatTable
36   , parseUnit
37   ) where
38
39 import Data.Char (toUpper)
40 import Data.List
41
42 import Debug.Trace
43
44 -- * Debug functions
45
46 -- | To be used only for debugging, breaks referential integrity.
47 debug :: Show a => a -> a
48 debug x = trace (show x) x
49
50 -- | Displays a modified form of the second parameter before returning
51 -- it.
52 debugFn :: Show b => (a -> b) -> a -> a
53 debugFn fn x = debug (fn x) `seq` x
54
55 -- | Show the first parameter before returning the second one.
56 debugXy :: Show a => a -> b -> b
57 debugXy = seq . debug
58
59 -- * Miscellaneous
60
61 -- | Apply the function if condition holds, otherwise use default value.
62 applyIf :: Bool -> (a -> a) -> a -> a
63 applyIf b f x = if b then f x else x
64
65 -- | Comma-join a string list.
66 commaJoin :: [String] -> String
67 commaJoin = intercalate ","
68
69 -- | Split a list on a separator and return an array.
70 sepSplit :: Eq a => a -> [a] -> [[a]]
71 sepSplit sep s
72   | null s    = []
73   | null xs   = [x]
74   | null ys   = [x,[]]
75   | otherwise = x:sepSplit sep ys
76   where (x, xs) = break (== sep) s
77         ys = drop 1 xs
78
79 -- * Mathematical functions
80
81 -- Simple and slow statistical functions, please replace with better
82 -- versions
83
84 -- | Standard deviation function.
85 stdDev :: [Double] -> Double
86 stdDev lst =
87   -- first, calculate the list length and sum lst in a single step,
88   -- for performance reasons
89   let (ll', sx) = foldl' (\(rl, rs) e ->
90                            let rl' = rl + 1
91                                rs' = rs + e
92                            in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
93       ll = fromIntegral ll'::Double
94       mv = sx / ll
95       av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
96   in sqrt (av / ll) -- stddev
97
98 -- *  Logical functions
99
100 -- Avoid syntactic sugar and enhance readability. These functions are proposed
101 -- by some for inclusion in the Prelude, and at the moment they are present
102 -- (with various definitions) in the utility-ht package. Some rationale and
103 -- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
104
105 -- | \"if\" as a function, rather than as syntactic sugar.
106 if' :: Bool -- ^ condition
107     -> a    -- ^ \"then\" result
108     -> a    -- ^ \"else\" result
109     -> a    -- ^ \"then\" or "else" result depending on the condition
110 if' True x _ = x
111 if' _    _ y = y
112
113 -- | Return the first result with a True condition, or the default otherwise.
114 select :: a            -- ^ default result
115        -> [(Bool, a)]  -- ^ list of \"condition, result\"
116        -> a            -- ^ first result which has a True condition, or default
117 select def = maybe def snd . find fst
118
119
120 -- * Parsing utility functions
121
122 -- | Parse results from readsPrec.
123 parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
124 parseChoices _ _ ((v, ""):[]) = return v
125 parseChoices name s ((_, e):[]) =
126     fail $ name ++ ": leftover characters when parsing '"
127            ++ s ++ "': '" ++ e ++ "'"
128 parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
129
130 -- | Safe 'read' function returning data encapsulated in a Result.
131 tryRead :: (Monad m, Read a) => String -> String -> m a
132 tryRead name s = parseChoices name s $ reads s
133
134 -- | Format a table of strings to maintain consistent length.
135 formatTable :: [[String]] -> [Bool] -> [[String]]
136 formatTable vals numpos =
137     let vtrans = transpose vals  -- transpose, so that we work on rows
138                                  -- rather than columns
139         mlens = map (maximum . map length) vtrans
140         expnd = map (\(flds, isnum, ml) ->
141                          map (\val ->
142                                   let delta = ml - length val
143                                       filler = replicate delta ' '
144                                   in if delta > 0
145                                      then if isnum
146                                           then filler ++ val
147                                           else val ++ filler
148                                      else val
149                              ) flds
150                     ) (zip3 vtrans numpos mlens)
151    in transpose expnd
152
153 -- | Tries to extract number and scale from the given string.
154 --
155 -- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
156 -- specified, it defaults to MiB. Return value is always an integral
157 -- value in MiB.
158 parseUnit :: (Monad m, Integral a, Read a) => String -> m a
159 parseUnit str =
160   -- TODO: enhance this by splitting the unit parsing code out and
161   -- accepting floating-point numbers
162   case reads str of
163     [(v, suffix)] ->
164       let unit = dropWhile (== ' ') suffix
165           upper = map toUpper unit
166           siConvert x = x * 1000000 `div` 1048576
167       in case () of
168            _ | null unit -> return v
169              | unit == "m" || upper == "MIB" -> return v
170              | unit == "M" || upper == "MB"  -> return $ siConvert v
171              | unit == "g" || upper == "GIB" -> return $ v * 1024
172              | unit == "G" || upper == "GB"  -> return $ siConvert
173                                                 (v * 1000)
174              | unit == "t" || upper == "TIB" -> return $ v * 1048576
175              | unit == "T" || upper == "TB"  -> return $
176                                                 siConvert (v * 1000000)
177              | otherwise -> fail $ "Unknown unit '" ++ unit ++ "'"
178     _ -> fail $ "Can't parse string '" ++ str ++ "'"