Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 986a8671

History | View | Annotate | Download (15.4 kB)

1
{-| Utility functions. -}
2

    
3
{-
4

    
5
Copyright (C) 2009, 2010, 2011, 2012, 2013 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
  , getCurrentTime
49
  , getCurrentTimeUSec
50
  , clockTimeToString
51
  , chompPrefix
52
  , warn
53
  , wrap
54
  , trim
55
  , defaultHead
56
  , exitIfEmpty
57
  , splitEithers
58
  , recombineEithers
59
  , resolveAddr
60
  ) where
61

    
62
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
63
import Data.Function (on)
64
import Data.List
65
import Control.Monad (foldM)
66

    
67
import Debug.Trace
68
import Network.Socket
69

    
70
import Ganeti.BasicTypes
71
import qualified Ganeti.Constants as C
72
import System.IO
73
import System.Exit
74
import System.Time
75

    
76
-- * Debug functions
77

    
78
-- | To be used only for debugging, breaks referential integrity.
79
debug :: Show a => a -> a
80
debug x = trace (show x) x
81

    
82
-- | Displays a modified form of the second parameter before returning
83
-- it.
84
debugFn :: Show b => (a -> b) -> a -> a
85
debugFn fn x = debug (fn x) `seq` x
86

    
87
-- | Show the first parameter before returning the second one.
88
debugXy :: Show a => a -> b -> b
89
debugXy = seq . debug
90

    
91
-- * Miscellaneous
92

    
93
-- | Apply the function if condition holds, otherwise use default value.
94
applyIf :: Bool -> (a -> a) -> a -> a
95
applyIf b f x = if b then f x else x
96

    
97
-- | Comma-join a string list.
98
commaJoin :: [String] -> String
99
commaJoin = intercalate ","
100

    
101
-- | Split a list on a separator and return an array.
102
sepSplit :: Eq a => a -> [a] -> [[a]]
103
sepSplit sep s
104
  | null s    = []
105
  | null xs   = [x]
106
  | null ys   = [x,[]]
107
  | otherwise = x:sepSplit sep ys
108
  where (x, xs) = break (== sep) s
109
        ys = drop 1 xs
110

    
111
-- | Simple pluralize helper
112
plural :: Int -> String -> String -> String
113
plural 1 s _ = s
114
plural _ _ p = p
115

    
116
-- | Ensure a value is quoted if needed.
117
ensureQuoted :: String -> String
118
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
119
                 then '\'':v ++ "'"
120
                 else v
121

    
122
-- * Mathematical functions
123

    
124
-- Simple and slow statistical functions, please replace with better
125
-- versions
126

    
127
-- | Standard deviation function.
128
stdDev :: [Double] -> Double
129
stdDev lst =
130
  -- first, calculate the list length and sum lst in a single step,
131
  -- for performance reasons
132
  let (ll', sx) = foldl' (\(rl, rs) e ->
133
                           let rl' = rl + 1
134
                               rs' = rs + e
135
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
136
      ll = fromIntegral ll'::Double
137
      mv = sx / ll
138
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
139
  in sqrt (av / ll) -- stddev
140

    
141
-- *  Logical functions
142

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

    
148
-- | \"if\" as a function, rather than as syntactic sugar.
149
if' :: Bool -- ^ condition
150
    -> a    -- ^ \"then\" result
151
    -> a    -- ^ \"else\" result
152
    -> a    -- ^ \"then\" or "else" result depending on the condition
153
if' True x _ = x
154
if' _    _ y = y
155

    
156
-- * Parsing utility functions
157

    
158
-- | Parse results from readsPrec.
159
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
160
parseChoices _ _ ((v, ""):[]) = return v
161
parseChoices name s ((_, e):[]) =
162
    fail $ name ++ ": leftover characters when parsing '"
163
           ++ s ++ "': '" ++ e ++ "'"
164
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
165

    
166
-- | Safe 'read' function returning data encapsulated in a Result.
167
tryRead :: (Monad m, Read a) => String -> String -> m a
168
tryRead name s = parseChoices name s $ reads s
169

    
170
-- | Format a table of strings to maintain consistent length.
171
formatTable :: [[String]] -> [Bool] -> [[String]]
172
formatTable vals numpos =
173
    let vtrans = transpose vals  -- transpose, so that we work on rows
174
                                 -- rather than columns
175
        mlens = map (maximum . map length) vtrans
176
        expnd = map (\(flds, isnum, ml) ->
177
                         map (\val ->
178
                                  let delta = ml - length val
179
                                      filler = replicate delta ' '
180
                                  in if delta > 0
181
                                     then if isnum
182
                                          then filler ++ val
183
                                          else val ++ filler
184
                                     else val
185
                             ) flds
186
                    ) (zip3 vtrans numpos mlens)
187
   in transpose expnd
188

    
189
-- | Constructs a printable table from given header and rows
190
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
191
printTable lp header rows isnum =
192
  unlines . map ((++) lp . (:) ' ' . unwords) $
193
  formatTable (header:rows) isnum
194

    
195
-- | Converts a unit (e.g. m or GB) into a scaling factor.
196
parseUnitValue :: (Monad m) => String -> m Rational
197
parseUnitValue unit
198
  -- binary conversions first
199
  | null unit                     = return 1
200
  | unit == "m" || upper == "MIB" = return 1
201
  | unit == "g" || upper == "GIB" = return kbBinary
202
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
203
  -- SI conversions
204
  | unit == "M" || upper == "MB"  = return mbFactor
205
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
206
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
207
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
208
  where upper = map toUpper unit
209
        kbBinary = 1024 :: Rational
210
        kbDecimal = 1000 :: Rational
211
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
212
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
213

    
214
-- | Tries to extract number and scale from the given string.
215
--
216
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
217
-- specified, it defaults to MiB. Return value is always an integral
218
-- value in MiB.
219
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
220
parseUnit str =
221
  -- TODO: enhance this by splitting the unit parsing code out and
222
  -- accepting floating-point numbers
223
  case (reads str::[(Int, String)]) of
224
    [(v, suffix)] ->
225
      let unit = dropWhile (== ' ') suffix
226
      in do
227
        scaling <- parseUnitValue unit
228
        return $ truncate (fromIntegral v * scaling)
229
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
230

    
231
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
232
-- otherwise returning the actual contained value.
233
exitIfBad :: String -> Result a -> IO a
234
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
235
exitIfBad _ (Ok v) = return v
236

    
237
-- | Exits immediately with an error message.
238
exitErr :: String -> IO a
239
exitErr errmsg = do
240
  hPutStrLn stderr $ "Error: " ++ errmsg
241
  exitWith (ExitFailure 1)
242

    
243
-- | Exits with an error message if the given boolean condition if true.
244
exitWhen :: Bool -> String -> IO ()
245
exitWhen True msg = exitErr msg
246
exitWhen False _  = return ()
247

    
248
-- | Exits with an error message /unless/ the given boolean condition
249
-- if true, the opposite of 'exitWhen'.
250
exitUnless :: Bool -> String -> IO ()
251
exitUnless cond = exitWhen (not cond)
252

    
253
-- | Print a warning, but do not exit.
254
warn :: String -> IO ()
255
warn = hPutStrLn stderr . (++) "Warning: "
256

    
257
-- | Helper for 'niceSort'. Computes the key element for a given string.
258
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
259
           -> String                   -- ^ Remaining string
260
           -> ([Either Integer String], String)
261
extractKey ek [] = (reverse ek, [])
262
extractKey ek xs@(x:_) =
263
  let (span_fn, conv_fn) = if isDigit x
264
                             then (isDigit, Left . read)
265
                             else (not . isDigit, Right)
266
      (k, rest) = span span_fn xs
267
  in extractKey (conv_fn k:ek) rest
268

    
269
{-| Sort a list of strings based on digit and non-digit groupings.
270

    
271
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
272
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
273

    
274
The sort algorithm breaks each name in groups of either only-digits or
275
no-digits, and sorts based on each group.
276

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

    
284
-}
285
niceSort :: [String] -> [String]
286
niceSort = niceSortKey id
287

    
288
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
289
-- since we don't want to add an ordering constraint on the /a/ type,
290
-- hence the need to only compare the first element of the /(key, a)/
291
-- tuple.
292
niceSortKey :: (a -> String) -> [a] -> [a]
293
niceSortKey keyfn =
294
  map snd . sortBy (compare `on` fst) .
295
  map (\s -> (fst . extractKey [] $ keyfn s, s))
296

    
297
-- | Strip space characthers (including newline). As this is
298
-- expensive, should only be run on small strings.
299
rStripSpace :: String -> String
300
rStripSpace = reverse . dropWhile isSpace . reverse
301

    
302
-- | Returns a random UUID.
303
-- This is a Linux-specific method as it uses the /proc filesystem.
304
newUUID :: IO String
305
newUUID = do
306
  contents <- readFile C.randomUuidFile
307
  return $! rStripSpace $ take 128 contents
308

    
309
-- | Returns the current time as an 'Integer' representing the number
310
-- of seconds from the Unix epoch.
311
getCurrentTime :: IO Integer
312
getCurrentTime = do
313
  TOD ctime _ <- getClockTime
314
  return ctime
315

    
316
-- | Returns the current time as an 'Integer' representing the number
317
-- of microseconds from the Unix epoch (hence the need for 'Integer').
318
getCurrentTimeUSec :: IO Integer
319
getCurrentTimeUSec = do
320
  TOD ctime pico <- getClockTime
321
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
322
  -- picoseconds right
323
  return $ ctime * 1000000 + pico `div` 1000000
324

    
325
-- | Convert a ClockTime into a (seconds-only) timestamp.
326
clockTimeToString :: ClockTime -> String
327
clockTimeToString (TOD t _) = show t
328

    
329
{-| Strip a prefix from a string, allowing the last character of the prefix
330
(which is assumed to be a separator) to be absent from the string if the string
331
terminates there.
332

    
333
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
334
Nothing
335

    
336
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
337
Just \"baz\"
338

    
339
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
340
Just \"\"
341

    
342
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
343
Just \"\"
344

    
345
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
346
Nothing
347
-}
348
chompPrefix :: String -> String -> Maybe String
349
chompPrefix pfx str =
350
  if pfx `isPrefixOf` str || str == init pfx
351
    then Just $ drop (length pfx) str
352
    else Nothing
353

    
354
-- | Breaks a string in lines with length \<= maxWidth.
355
--
356
-- NOTE: The split is OK if:
357
--
358
-- * It doesn't break a word, i.e. the next line begins with space
359
--   (@isSpace . head $ rest@) or the current line ends with space
360
--   (@null revExtra@);
361
--
362
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
363
wrap :: Int      -- ^ maxWidth
364
     -> String   -- ^ string that needs wrapping
365
     -> [String] -- ^ string \"broken\" in lines
366
wrap maxWidth = filter (not . null) . map trim . wrap0
367
  where wrap0 :: String -> [String]
368
        wrap0 text
369
          | length text <= maxWidth = [text]
370
          | isSplitOK               = line : wrap0 rest
371
          | otherwise               = line' : wrap0 rest'
372
          where (line, rest) = splitAt maxWidth text
373
                (revExtra, revLine) = break isSpace . reverse $ line
374
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
375
                isSplitOK =
376
                  null revLine || null revExtra || startsWithSpace rest
377
                startsWithSpace (x:_) = isSpace x
378
                startsWithSpace _     = False
379

    
380
-- | Removes surrounding whitespace. Should only be used in small
381
-- strings.
382
trim :: String -> String
383
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
384

    
385
-- | A safer head version, with a default value.
386
defaultHead :: a -> [a] -> a
387
defaultHead def []    = def
388
defaultHead _   (x:_) = x
389

    
390
-- | A 'head' version in the I/O monad, for validating parameters
391
-- without which we cannot continue.
392
exitIfEmpty :: String -> [a] -> IO a
393
exitIfEmpty _ (x:_) = return x
394
exitIfEmpty s []    = exitErr s
395

    
396
-- | Split an 'Either' list into two separate lists (containing the
397
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
398
-- recombination later.
399
--
400
-- This is splitter; for recombination, look at 'recombineEithers'.
401
-- The sum of \"left\" and \"right\" lists should be equal to the
402
-- original list length, and the trail list should be the same length
403
-- as well. The entries in the resulting lists are reversed in
404
-- comparison with the original list.
405
splitEithers :: [Either a b] -> ([a], [b], [Bool])
406
splitEithers = foldl' splitter ([], [], [])
407
  where splitter (l, r, t) e =
408
          case e of
409
            Left  v -> (v:l, r, False:t)
410
            Right v -> (l, v:r, True:t)
411

    
412
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
413
-- list into a single 'Either' list.
414
--
415
-- This is the counterpart to 'splitEithers'. It does the opposite
416
-- transformation, and the output list will be the reverse of the
417
-- input lists. Since 'splitEithers' also reverses the lists, calling
418
-- these together will result in the original list.
419
--
420
-- Mismatches in the structure of the lists (e.g. inconsistent
421
-- lengths) are represented via 'Bad'; normally this function should
422
-- not fail, if lists are passed as generated by 'splitEithers'.
423
recombineEithers :: (Show a, Show b) =>
424
                    [a] -> [b] -> [Bool] -> Result [Either a b]
425
recombineEithers lefts rights trail =
426
  foldM recombiner ([], lefts, rights) trail >>= checker
427
    where checker (eithers, [], []) = Ok eithers
428
          checker (_, lefts', rights') =
429
            Bad $ "Inconsistent results after recombination, l'=" ++
430
                show lefts' ++ ", r'=" ++ show rights'
431
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
432
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
433
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
434
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
435
                                      show t
436

    
437
-- | Default hints for the resolver
438
resolveAddrHints :: Maybe AddrInfo
439
resolveAddrHints =
440
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
441

    
442
-- | Resolves a numeric address.
443
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
444
resolveAddr port str = do
445
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
446
  return $ case resolved of
447
             [] -> Bad "Invalid results from lookup?"
448
             best:_ -> Ok (addrFamily best, addrAddress best)