Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Utils.hs @ 256e28c4

History | View | Annotate | Download (9.5 kB)

1
{-| Utility functions. -}
2

    
3
{-
4

    
5
Copyright (C) 2009, 2010, 2011, 2012 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.Utils
25
  ( debug
26
  , debugFn
27
  , debugXy
28
  , sepSplit
29
  , stdDev
30
  , if'
31
  , select
32
  , applyIf
33
  , commaJoin
34
  , ensureQuoted
35
  , tryRead
36
  , formatTable
37
  , printTable
38
  , parseUnit
39
  , plural
40
  , niceSort
41
  , niceSortKey
42
  , exitIfBad
43
  , exitErr
44
  , exitWhen
45
  , exitUnless
46
  , rStripSpace
47
  ) where
48

    
49
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
50
import Data.Function (on)
51
import Data.List
52

    
53
import Debug.Trace
54

    
55
import Ganeti.BasicTypes
56
import System.IO
57
import System.Exit
58

    
59
-- * Debug functions
60

    
61
-- | To be used only for debugging, breaks referential integrity.
62
debug :: Show a => a -> a
63
debug x = trace (show x) x
64

    
65
-- | Displays a modified form of the second parameter before returning
66
-- it.
67
debugFn :: Show b => (a -> b) -> a -> a
68
debugFn fn x = debug (fn x) `seq` x
69

    
70
-- | Show the first parameter before returning the second one.
71
debugXy :: Show a => a -> b -> b
72
debugXy = seq . debug
73

    
74
-- * Miscellaneous
75

    
76
-- | Apply the function if condition holds, otherwise use default value.
77
applyIf :: Bool -> (a -> a) -> a -> a
78
applyIf b f x = if b then f x else x
79

    
80
-- | Comma-join a string list.
81
commaJoin :: [String] -> String
82
commaJoin = intercalate ","
83

    
84
-- | Split a list on a separator and return an array.
85
sepSplit :: Eq a => a -> [a] -> [[a]]
86
sepSplit sep s
87
  | null s    = []
88
  | null xs   = [x]
89
  | null ys   = [x,[]]
90
  | otherwise = x:sepSplit sep ys
91
  where (x, xs) = break (== sep) s
92
        ys = drop 1 xs
93

    
94
-- | Simple pluralize helper
95
plural :: Int -> String -> String -> String
96
plural 1 s _ = s
97
plural _ _ p = p
98

    
99
-- | Ensure a value is quoted if needed.
100
ensureQuoted :: String -> String
101
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
102
                 then '\'':v ++ "'"
103
                 else v
104

    
105
-- * Mathematical functions
106

    
107
-- Simple and slow statistical functions, please replace with better
108
-- versions
109

    
110
-- | Standard deviation function.
111
stdDev :: [Double] -> Double
112
stdDev lst =
113
  -- first, calculate the list length and sum lst in a single step,
114
  -- for performance reasons
115
  let (ll', sx) = foldl' (\(rl, rs) e ->
116
                           let rl' = rl + 1
117
                               rs' = rs + e
118
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
119
      ll = fromIntegral ll'::Double
120
      mv = sx / ll
121
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
122
  in sqrt (av / ll) -- stddev
123

    
124
-- *  Logical functions
125

    
126
-- Avoid syntactic sugar and enhance readability. These functions are proposed
127
-- by some for inclusion in the Prelude, and at the moment they are present
128
-- (with various definitions) in the utility-ht package. Some rationale and
129
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
130

    
131
-- | \"if\" as a function, rather than as syntactic sugar.
132
if' :: Bool -- ^ condition
133
    -> a    -- ^ \"then\" result
134
    -> a    -- ^ \"else\" result
135
    -> a    -- ^ \"then\" or "else" result depending on the condition
136
if' True x _ = x
137
if' _    _ y = y
138

    
139
-- * Parsing utility functions
140

    
141
-- | Parse results from readsPrec.
142
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
143
parseChoices _ _ ((v, ""):[]) = return v
144
parseChoices name s ((_, e):[]) =
145
    fail $ name ++ ": leftover characters when parsing '"
146
           ++ s ++ "': '" ++ e ++ "'"
147
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
148

    
149
-- | Safe 'read' function returning data encapsulated in a Result.
150
tryRead :: (Monad m, Read a) => String -> String -> m a
151
tryRead name s = parseChoices name s $ reads s
152

    
153
-- | Format a table of strings to maintain consistent length.
154
formatTable :: [[String]] -> [Bool] -> [[String]]
155
formatTable vals numpos =
156
    let vtrans = transpose vals  -- transpose, so that we work on rows
157
                                 -- rather than columns
158
        mlens = map (maximum . map length) vtrans
159
        expnd = map (\(flds, isnum, ml) ->
160
                         map (\val ->
161
                                  let delta = ml - length val
162
                                      filler = replicate delta ' '
163
                                  in if delta > 0
164
                                     then if isnum
165
                                          then filler ++ val
166
                                          else val ++ filler
167
                                     else val
168
                             ) flds
169
                    ) (zip3 vtrans numpos mlens)
170
   in transpose expnd
171

    
172
-- | Constructs a printable table from given header and rows
173
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
174
printTable lp header rows isnum =
175
  unlines . map ((++) lp . (:) ' ' . unwords) $
176
  formatTable (header:rows) isnum
177

    
178
-- | Converts a unit (e.g. m or GB) into a scaling factor.
179
parseUnitValue :: (Monad m) => String -> m Rational
180
parseUnitValue unit
181
  -- binary conversions first
182
  | null unit                     = return 1
183
  | unit == "m" || upper == "MIB" = return 1
184
  | unit == "g" || upper == "GIB" = return kbBinary
185
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
186
  -- SI conversions
187
  | unit == "M" || upper == "MB"  = return mbFactor
188
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
189
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
190
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
191
  where upper = map toUpper unit
192
        kbBinary = 1024 :: Rational
193
        kbDecimal = 1000 :: Rational
194
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
195
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
196

    
197
-- | Tries to extract number and scale from the given string.
198
--
199
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
200
-- specified, it defaults to MiB. Return value is always an integral
201
-- value in MiB.
202
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
203
parseUnit str =
204
  -- TODO: enhance this by splitting the unit parsing code out and
205
  -- accepting floating-point numbers
206
  case (reads str::[(Int, String)]) of
207
    [(v, suffix)] ->
208
      let unit = dropWhile (== ' ') suffix
209
      in do
210
        scaling <- parseUnitValue unit
211
        return $ truncate (fromIntegral v * scaling)
212
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
213

    
214
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
215
-- otherwise returning the actual contained value.
216
exitIfBad :: String -> Result a -> IO a
217
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
218
exitIfBad _ (Ok v) = return v
219

    
220
-- | Exits immediately with an error message.
221
exitErr :: String -> IO a
222
exitErr errmsg = do
223
  hPutStrLn stderr $ "Error: " ++ errmsg
224
  exitWith (ExitFailure 1)
225

    
226
-- | Exits with an error message if the given boolean condition if true.
227
exitWhen :: Bool -> String -> IO ()
228
exitWhen True msg = exitErr msg
229
exitWhen False _  = return ()
230

    
231
-- | Exits with an error message /unless/ the given boolean condition
232
-- if true, the opposite of 'exitWhen'.
233
exitUnless :: Bool -> String -> IO ()
234
exitUnless cond = exitWhen (not cond)
235

    
236
-- | Helper for 'niceSort'. Computes the key element for a given string.
237
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
238
           -> String                   -- ^ Remaining string
239
           -> ([Either Integer String], String)
240
extractKey ek [] = (reverse ek, [])
241
extractKey ek xs@(x:_) =
242
  let (span_fn, conv_fn) = if isDigit x
243
                             then (isDigit, Left . read)
244
                             else (not . isDigit, Right)
245
      (k, rest) = span span_fn xs
246
  in extractKey (conv_fn k:ek) rest
247

    
248
{-| Sort a list of strings based on digit and non-digit groupings.
249

    
250
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
251
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
252

    
253
The sort algorithm breaks each name in groups of either only-digits or
254
no-digits, and sorts based on each group.
255

    
256
Internally, this is not implemented via regexes (like the Python
257
version), but via actual splitting of the string in sequences of
258
either digits or everything else, and converting the digit sequences
259
in /Left Integer/ and the non-digit ones in /Right String/, at which
260
point sorting becomes trivial due to the built-in 'Either' ordering;
261
we only need one extra step of dropping the key at the end.
262

    
263
-}
264
niceSort :: [String] -> [String]
265
niceSort = map snd . sort . map (\s -> (fst $ extractKey [] s, s))
266

    
267
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
268
-- since we don't want to add an ordering constraint on the /a/ type,
269
-- hence the need to only compare the first element of the /(key, a)/
270
-- tuple.
271
niceSortKey :: (a -> String) -> [a] -> [a]
272
niceSortKey keyfn =
273
  map snd . sortBy (compare `on` fst) .
274
  map (\s -> (fst . extractKey [] $ keyfn s, s))
275

    
276
-- | Strip space characthers (including newline). As this is
277
-- expensive, should only be run on small strings.
278
rStripSpace :: String -> String
279
rStripSpace = reverse . dropWhile isSpace . reverse