Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 3add7574

History | View | Annotate | Download (9.7 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
  , newUUID
48
  ) where
49

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

    
54
import Debug.Trace
55

    
56
import Ganeti.BasicTypes
57
import qualified Ganeti.Constants as C
58
import System.IO
59
import System.Exit
60

    
61
-- * Debug functions
62

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

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

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

    
76
-- * Miscellaneous
77

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

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

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

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

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

    
107
-- * Mathematical functions
108

    
109
-- Simple and slow statistical functions, please replace with better
110
-- versions
111

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

    
126
-- *  Logical functions
127

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

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

    
141
-- * Parsing utility functions
142

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

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

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

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

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

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

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

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

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

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

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

    
250
{-| Sort a list of strings based on digit and non-digit groupings.
251

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

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

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

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

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

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

    
283
-- | Returns a random UUID.
284
-- This is a Linux-specific method as it uses the /proc filesystem.
285
newUUID :: IO String
286
newUUID = do
287
  contents <- readFile C.randomUuidFile
288
  return $! rStripSpace $ take 128 contents