Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Utils.hs @ b1e81520

History | View | Annotate | Download (6.4 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 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 ebf38064 Iustin Pop
  , tryRead
35 ebf38064 Iustin Pop
  , formatTable
36 c3024b7e René Nussbaumer
  , printTable
37 ebf38064 Iustin Pop
  , parseUnit
38 19e310cc René Nussbaumer
  , plural
39 ebf38064 Iustin Pop
  ) where
40 e4f08c46 Iustin Pop
41 1cb92fac Iustin Pop
import Data.Char (toUpper)
42 29ac5975 Iustin Pop
import Data.List
43 e4f08c46 Iustin Pop
44 e4f08c46 Iustin Pop
import Debug.Trace
45 e4f08c46 Iustin Pop
46 9188aeef Iustin Pop
-- * Debug functions
47 9188aeef Iustin Pop
48 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
49 e4f08c46 Iustin Pop
debug :: Show a => a -> a
50 e4f08c46 Iustin Pop
debug x = trace (show x) x
51 e4f08c46 Iustin Pop
52 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
53 525bfb36 Iustin Pop
-- it.
54 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
55 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
56 adc5c176 Iustin Pop
57 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
58 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
59 05ff7a00 Agata Murawska
debugXy = seq . debug
60 adc5c176 Iustin Pop
61 525bfb36 Iustin Pop
-- * Miscellaneous
62 1b7cf8ca Iustin Pop
63 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
64 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
65 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
66 61bbbed7 Agata Murawska
67 e4f08c46 Iustin Pop
-- | Comma-join a string list.
68 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
69 e4f08c46 Iustin Pop
commaJoin = intercalate ","
70 e4f08c46 Iustin Pop
71 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
72 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
73 e4f08c46 Iustin Pop
sepSplit sep s
74 ebf38064 Iustin Pop
  | null s    = []
75 ebf38064 Iustin Pop
  | null xs   = [x]
76 ebf38064 Iustin Pop
  | null ys   = [x,[]]
77 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
78 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
79 ebf38064 Iustin Pop
        ys = drop 1 xs
80 e4f08c46 Iustin Pop
81 19e310cc René Nussbaumer
-- | Simple pluralize helper
82 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
83 19e310cc René Nussbaumer
plural 1 s _ = s
84 19e310cc René Nussbaumer
plural _ _ p = p
85 19e310cc René Nussbaumer
86 9188aeef Iustin Pop
-- * Mathematical functions
87 9188aeef Iustin Pop
88 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
89 185297fa Iustin Pop
-- versions
90 e4f08c46 Iustin Pop
91 525bfb36 Iustin Pop
-- | Standard deviation function.
92 4715711d Iustin Pop
stdDev :: [Double] -> Double
93 4715711d Iustin Pop
stdDev lst =
94 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
95 7570569e Iustin Pop
  -- for performance reasons
96 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
97 7570569e Iustin Pop
                           let rl' = rl + 1
98 7570569e Iustin Pop
                               rs' = rs + e
99 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
100 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
101 7570569e Iustin Pop
      mv = sx / ll
102 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
103 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
104 dd4c56ed Iustin Pop
105 bfe6c954 Guido Trotter
-- *  Logical functions
106 bfe6c954 Guido Trotter
107 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
108 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
109 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
110 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
111 bfe6c954 Guido Trotter
112 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
113 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
114 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
115 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
116 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
117 bfe6c954 Guido Trotter
if' True x _ = x
118 bfe6c954 Guido Trotter
if' _    _ y = y
119 bfe6c954 Guido Trotter
120 bfe6c954 Guido Trotter
-- | Return the first result with a True condition, or the default otherwise.
121 bfe6c954 Guido Trotter
select :: a            -- ^ default result
122 bfe6c954 Guido Trotter
       -> [(Bool, a)]  -- ^ list of \"condition, result\"
123 bfe6c954 Guido Trotter
       -> a            -- ^ first result which has a True condition, or default
124 bfe6c954 Guido Trotter
select def = maybe def snd . find fst
125 bfe6c954 Guido Trotter
126 5b763470 Iustin Pop
127 5b763470 Iustin Pop
-- * Parsing utility functions
128 5b763470 Iustin Pop
129 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
130 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
131 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
132 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
133 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
134 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
135 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
136 5b763470 Iustin Pop
137 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
138 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
139 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
140 c5f7412e Iustin Pop
141 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
142 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
143 c5f7412e Iustin Pop
formatTable vals numpos =
144 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
145 c5f7412e Iustin Pop
                                 -- rather than columns
146 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
147 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
148 c5f7412e Iustin Pop
                         map (\val ->
149 c5f7412e Iustin Pop
                                  let delta = ml - length val
150 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
151 c5f7412e Iustin Pop
                                  in if delta > 0
152 c5f7412e Iustin Pop
                                     then if isnum
153 c5f7412e Iustin Pop
                                          then filler ++ val
154 c5f7412e Iustin Pop
                                          else val ++ filler
155 c5f7412e Iustin Pop
                                     else val
156 c5f7412e Iustin Pop
                             ) flds
157 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
158 c5f7412e Iustin Pop
   in transpose expnd
159 9b9da389 Iustin Pop
160 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
161 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
162 c3024b7e René Nussbaumer
printTable lp header rows isnum =
163 c3024b7e René Nussbaumer
  unlines . map ((++) lp) . map ((:) ' ' . unwords) $
164 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
165 c3024b7e René Nussbaumer
166 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
167 1cb92fac Iustin Pop
--
168 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
169 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
170 1cb92fac Iustin Pop
-- value in MiB.
171 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
172 1cb92fac Iustin Pop
parseUnit str =
173 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
174 ebf38064 Iustin Pop
  -- accepting floating-point numbers
175 ebf38064 Iustin Pop
  case reads str of
176 ebf38064 Iustin Pop
    [(v, suffix)] ->
177 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
178 ebf38064 Iustin Pop
          upper = map toUpper unit
179 ebf38064 Iustin Pop
          siConvert x = x * 1000000 `div` 1048576
180 ebf38064 Iustin Pop
      in case () of
181 ebf38064 Iustin Pop
           _ | null unit -> return v
182 ebf38064 Iustin Pop
             | unit == "m" || upper == "MIB" -> return v
183 ebf38064 Iustin Pop
             | unit == "M" || upper == "MB"  -> return $ siConvert v
184 ebf38064 Iustin Pop
             | unit == "g" || upper == "GIB" -> return $ v * 1024
185 ebf38064 Iustin Pop
             | unit == "G" || upper == "GB"  -> return $ siConvert
186 ebf38064 Iustin Pop
                                                (v * 1000)
187 ebf38064 Iustin Pop
             | unit == "t" || upper == "TIB" -> return $ v * 1048576
188 ebf38064 Iustin Pop
             | unit == "T" || upper == "TB"  -> return $
189 ebf38064 Iustin Pop
                                                siConvert (v * 1000000)
190 ebf38064 Iustin Pop
             | otherwise -> fail $ "Unknown unit '" ++ unit ++ "'"
191 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"