Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 710f5ae2

History | View | Annotate | Download (17.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
  , logWarningIfBad
47
  , rStripSpace
48
  , newUUID
49
  , getCurrentTime
50
  , getCurrentTimeUSec
51
  , clockTimeToString
52
  , chompPrefix
53
  , warn
54
  , wrap
55
  , trim
56
  , defaultHead
57
  , exitIfEmpty
58
  , splitEithers
59
  , recombineEithers
60
  , resolveAddr
61
  , setOwnerAndGroupFromNames
62
  , formatOrdinal
63
  , atomicWriteFile
64
  ) where
65

    
66
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
67
import Data.Function (on)
68
import Data.List
69
import qualified Data.Map as M
70
import Control.Monad (foldM)
71
import System.Directory (renameFile)
72
import System.FilePath.Posix (takeDirectory, takeBaseName)
73

    
74
import Debug.Trace
75
import Network.Socket
76

    
77
import Ganeti.BasicTypes
78
import qualified Ganeti.ConstantUtils as ConstantUtils
79
import Ganeti.Logging
80
import Ganeti.Runtime
81
import System.IO
82
import System.Exit
83
import System.Posix.Files
84
import System.Time
85

    
86
-- * Debug functions
87

    
88
-- | To be used only for debugging, breaks referential integrity.
89
debug :: Show a => a -> a
90
debug x = trace (show x) x
91

    
92
-- | Displays a modified form of the second parameter before returning
93
-- it.
94
debugFn :: Show b => (a -> b) -> a -> a
95
debugFn fn x = debug (fn x) `seq` x
96

    
97
-- | Show the first parameter before returning the second one.
98
debugXy :: Show a => a -> b -> b
99
debugXy = seq . debug
100

    
101
-- * Miscellaneous
102

    
103
-- | Apply the function if condition holds, otherwise use default value.
104
applyIf :: Bool -> (a -> a) -> a -> a
105
applyIf b f x = if b then f x else x
106

    
107
-- | Comma-join a string list.
108
commaJoin :: [String] -> String
109
commaJoin = intercalate ","
110

    
111
-- | Split a list on a separator and return an array.
112
sepSplit :: Eq a => a -> [a] -> [[a]]
113
sepSplit sep s
114
  | null s    = []
115
  | null xs   = [x]
116
  | null ys   = [x,[]]
117
  | otherwise = x:sepSplit sep ys
118
  where (x, xs) = break (== sep) s
119
        ys = drop 1 xs
120

    
121
-- | Simple pluralize helper
122
plural :: Int -> String -> String -> String
123
plural 1 s _ = s
124
plural _ _ p = p
125

    
126
-- | Ensure a value is quoted if needed.
127
ensureQuoted :: String -> String
128
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
129
                 then '\'':v ++ "'"
130
                 else v
131

    
132
-- * Mathematical functions
133

    
134
-- Simple and slow statistical functions, please replace with better
135
-- versions
136

    
137
-- | Standard deviation function.
138
stdDev :: [Double] -> Double
139
stdDev lst =
140
  -- first, calculate the list length and sum lst in a single step,
141
  -- for performance reasons
142
  let (ll', sx) = foldl' (\(rl, rs) e ->
143
                           let rl' = rl + 1
144
                               rs' = rs + e
145
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
146
      ll = fromIntegral ll'::Double
147
      mv = sx / ll
148
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
149
  in sqrt (av / ll) -- stddev
150

    
151
-- *  Logical functions
152

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

    
158
-- | \"if\" as a function, rather than as syntactic sugar.
159
if' :: Bool -- ^ condition
160
    -> a    -- ^ \"then\" result
161
    -> a    -- ^ \"else\" result
162
    -> a    -- ^ \"then\" or "else" result depending on the condition
163
if' True x _ = x
164
if' _    _ y = y
165

    
166
-- * Parsing utility functions
167

    
168
-- | Parse results from readsPrec.
169
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
170
parseChoices _ _ ((v, ""):[]) = return v
171
parseChoices name s ((_, e):[]) =
172
    fail $ name ++ ": leftover characters when parsing '"
173
           ++ s ++ "': '" ++ e ++ "'"
174
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
175

    
176
-- | Safe 'read' function returning data encapsulated in a Result.
177
tryRead :: (Monad m, Read a) => String -> String -> m a
178
tryRead name s = parseChoices name s $ reads s
179

    
180
-- | Format a table of strings to maintain consistent length.
181
formatTable :: [[String]] -> [Bool] -> [[String]]
182
formatTable vals numpos =
183
    let vtrans = transpose vals  -- transpose, so that we work on rows
184
                                 -- rather than columns
185
        mlens = map (maximum . map length) vtrans
186
        expnd = map (\(flds, isnum, ml) ->
187
                         map (\val ->
188
                                  let delta = ml - length val
189
                                      filler = replicate delta ' '
190
                                  in if delta > 0
191
                                     then if isnum
192
                                          then filler ++ val
193
                                          else val ++ filler
194
                                     else val
195
                             ) flds
196
                    ) (zip3 vtrans numpos mlens)
197
   in transpose expnd
198

    
199
-- | Constructs a printable table from given header and rows
200
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
201
printTable lp header rows isnum =
202
  unlines . map ((++) lp . (:) ' ' . unwords) $
203
  formatTable (header:rows) isnum
204

    
205
-- | Converts a unit (e.g. m or GB) into a scaling factor.
206
parseUnitValue :: (Monad m) => String -> m Rational
207
parseUnitValue unit
208
  -- binary conversions first
209
  | null unit                     = return 1
210
  | unit == "m" || upper == "MIB" = return 1
211
  | unit == "g" || upper == "GIB" = return kbBinary
212
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
213
  -- SI conversions
214
  | unit == "M" || upper == "MB"  = return mbFactor
215
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
216
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
217
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
218
  where upper = map toUpper unit
219
        kbBinary = 1024 :: Rational
220
        kbDecimal = 1000 :: Rational
221
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
222
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
223

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

    
241
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
242
-- otherwise returning the actual contained value.
243
exitIfBad :: String -> Result a -> IO a
244
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
245
exitIfBad _ (Ok v) = return v
246

    
247
-- | Exits immediately with an error message.
248
exitErr :: String -> IO a
249
exitErr errmsg = do
250
  hPutStrLn stderr $ "Error: " ++ errmsg
251
  exitWith (ExitFailure 1)
252

    
253
-- | Exits with an error message if the given boolean condition if true.
254
exitWhen :: Bool -> String -> IO ()
255
exitWhen True msg = exitErr msg
256
exitWhen False _  = return ()
257

    
258
-- | Exits with an error message /unless/ the given boolean condition
259
-- if true, the opposite of 'exitWhen'.
260
exitUnless :: Bool -> String -> IO ()
261
exitUnless cond = exitWhen (not cond)
262

    
263
-- | Unwraps a 'Result', logging a warning message and then returning a default
264
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
265
logWarningIfBad :: String -> a -> Result a -> IO a
266
logWarningIfBad msg defVal (Bad s) = do
267
  logWarning $ msg ++ ": " ++ s
268
  return defVal
269
logWarningIfBad _ _ (Ok v) = return v
270

    
271
-- | Print a warning, but do not exit.
272
warn :: String -> IO ()
273
warn = hPutStrLn stderr . (++) "Warning: "
274

    
275
-- | Helper for 'niceSort'. Computes the key element for a given string.
276
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
277
           -> String                   -- ^ Remaining string
278
           -> ([Either Integer String], String)
279
extractKey ek [] = (reverse ek, [])
280
extractKey ek xs@(x:_) =
281
  let (span_fn, conv_fn) = if isDigit x
282
                             then (isDigit, Left . read)
283
                             else (not . isDigit, Right)
284
      (k, rest) = span span_fn xs
285
  in extractKey (conv_fn k:ek) rest
286

    
287
{-| Sort a list of strings based on digit and non-digit groupings.
288

    
289
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
290
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
291

    
292
The sort algorithm breaks each name in groups of either only-digits or
293
no-digits, and sorts based on each group.
294

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

    
302
-}
303
niceSort :: [String] -> [String]
304
niceSort = niceSortKey id
305

    
306
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
307
-- since we don't want to add an ordering constraint on the /a/ type,
308
-- hence the need to only compare the first element of the /(key, a)/
309
-- tuple.
310
niceSortKey :: (a -> String) -> [a] -> [a]
311
niceSortKey keyfn =
312
  map snd . sortBy (compare `on` fst) .
313
  map (\s -> (fst . extractKey [] $ keyfn s, s))
314

    
315
-- | Strip space characthers (including newline). As this is
316
-- expensive, should only be run on small strings.
317
rStripSpace :: String -> String
318
rStripSpace = reverse . dropWhile isSpace . reverse
319

    
320
-- | Returns a random UUID.
321
-- This is a Linux-specific method as it uses the /proc filesystem.
322
newUUID :: IO String
323
newUUID = do
324
  contents <- readFile ConstantUtils.randomUuidFile
325
  return $! rStripSpace $ take 128 contents
326

    
327
-- | Returns the current time as an 'Integer' representing the number
328
-- of seconds from the Unix epoch.
329
getCurrentTime :: IO Integer
330
getCurrentTime = do
331
  TOD ctime _ <- getClockTime
332
  return ctime
333

    
334
-- | Returns the current time as an 'Integer' representing the number
335
-- of microseconds from the Unix epoch (hence the need for 'Integer').
336
getCurrentTimeUSec :: IO Integer
337
getCurrentTimeUSec = do
338
  TOD ctime pico <- getClockTime
339
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
340
  -- picoseconds right
341
  return $ ctime * 1000000 + pico `div` 1000000
342

    
343
-- | Convert a ClockTime into a (seconds-only) timestamp.
344
clockTimeToString :: ClockTime -> String
345
clockTimeToString (TOD t _) = show t
346

    
347
{-| Strip a prefix from a string, allowing the last character of the prefix
348
(which is assumed to be a separator) to be absent from the string if the string
349
terminates there.
350

    
351
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
352
Nothing
353

    
354
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
355
Just \"baz\"
356

    
357
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
358
Just \"\"
359

    
360
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
361
Just \"\"
362

    
363
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
364
Nothing
365
-}
366
chompPrefix :: String -> String -> Maybe String
367
chompPrefix pfx str =
368
  if pfx `isPrefixOf` str || str == init pfx
369
    then Just $ drop (length pfx) str
370
    else Nothing
371

    
372
-- | Breaks a string in lines with length \<= maxWidth.
373
--
374
-- NOTE: The split is OK if:
375
--
376
-- * It doesn't break a word, i.e. the next line begins with space
377
--   (@isSpace . head $ rest@) or the current line ends with space
378
--   (@null revExtra@);
379
--
380
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
381
wrap :: Int      -- ^ maxWidth
382
     -> String   -- ^ string that needs wrapping
383
     -> [String] -- ^ string \"broken\" in lines
384
wrap maxWidth = filter (not . null) . map trim . wrap0
385
  where wrap0 :: String -> [String]
386
        wrap0 text
387
          | length text <= maxWidth = [text]
388
          | isSplitOK               = line : wrap0 rest
389
          | otherwise               = line' : wrap0 rest'
390
          where (line, rest) = splitAt maxWidth text
391
                (revExtra, revLine) = break isSpace . reverse $ line
392
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
393
                isSplitOK =
394
                  null revLine || null revExtra || startsWithSpace rest
395
                startsWithSpace (x:_) = isSpace x
396
                startsWithSpace _     = False
397

    
398
-- | Removes surrounding whitespace. Should only be used in small
399
-- strings.
400
trim :: String -> String
401
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
402

    
403
-- | A safer head version, with a default value.
404
defaultHead :: a -> [a] -> a
405
defaultHead def []    = def
406
defaultHead _   (x:_) = x
407

    
408
-- | A 'head' version in the I/O monad, for validating parameters
409
-- without which we cannot continue.
410
exitIfEmpty :: String -> [a] -> IO a
411
exitIfEmpty _ (x:_) = return x
412
exitIfEmpty s []    = exitErr s
413

    
414
-- | Split an 'Either' list into two separate lists (containing the
415
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
416
-- recombination later.
417
--
418
-- This is splitter; for recombination, look at 'recombineEithers'.
419
-- The sum of \"left\" and \"right\" lists should be equal to the
420
-- original list length, and the trail list should be the same length
421
-- as well. The entries in the resulting lists are reversed in
422
-- comparison with the original list.
423
splitEithers :: [Either a b] -> ([a], [b], [Bool])
424
splitEithers = foldl' splitter ([], [], [])
425
  where splitter (l, r, t) e =
426
          case e of
427
            Left  v -> (v:l, r, False:t)
428
            Right v -> (l, v:r, True:t)
429

    
430
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
431
-- list into a single 'Either' list.
432
--
433
-- This is the counterpart to 'splitEithers'. It does the opposite
434
-- transformation, and the output list will be the reverse of the
435
-- input lists. Since 'splitEithers' also reverses the lists, calling
436
-- these together will result in the original list.
437
--
438
-- Mismatches in the structure of the lists (e.g. inconsistent
439
-- lengths) are represented via 'Bad'; normally this function should
440
-- not fail, if lists are passed as generated by 'splitEithers'.
441
recombineEithers :: (Show a, Show b) =>
442
                    [a] -> [b] -> [Bool] -> Result [Either a b]
443
recombineEithers lefts rights trail =
444
  foldM recombiner ([], lefts, rights) trail >>= checker
445
    where checker (eithers, [], []) = Ok eithers
446
          checker (_, lefts', rights') =
447
            Bad $ "Inconsistent results after recombination, l'=" ++
448
                show lefts' ++ ", r'=" ++ show rights'
449
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
450
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
451
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
452
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
453
                                      show t
454

    
455
-- | Default hints for the resolver
456
resolveAddrHints :: Maybe AddrInfo
457
resolveAddrHints =
458
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
459

    
460
-- | Resolves a numeric address.
461
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
462
resolveAddr port str = do
463
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
464
  return $ case resolved of
465
             [] -> Bad "Invalid results from lookup?"
466
             best:_ -> Ok (addrFamily best, addrAddress best)
467

    
468
-- | Set the owner and the group of a file (given as names, not numeric id).
469
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
470
setOwnerAndGroupFromNames filename daemon dGroup = do
471
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
472
  -- is read only once per daemon startup, and then cached for further usage.
473
  runtimeEnts <- getEnts
474
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
475
  -- note: we use directly ! as lookup failures shouldn't happen, due
476
  -- to the map construction
477
  let uid = fst ents M.! daemon
478
  let gid = snd ents M.! dGroup
479
  setOwnerAndGroup filename uid gid
480

    
481
-- | Formats an integral number, appending a suffix.
482
formatOrdinal :: (Integral a, Show a) => a -> String
483
formatOrdinal num
484
  | num > 10 && num < 20 = suffix "th"
485
  | tens == 1            = suffix "st"
486
  | tens == 2            = suffix "nd"
487
  | tens == 3            = suffix "rd"
488
  | otherwise            = suffix "th"
489
  where tens     = num `mod` 10
490
        suffix s = show num ++ s
491

    
492
-- | Atomically write a file, by first writing the contents into a temporary
493
-- file and then renaming it to the old position.
494
atomicWriteFile :: FilePath -> String -> IO ()
495
atomicWriteFile path contents = do
496
  (tmppath, tmphandle) <- openTempFile (takeDirectory path) (takeBaseName path)
497
  hPutStr tmphandle contents
498
  hClose tmphandle
499
  renameFile tmppath path