Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ ef8b6bcf

History | View | Annotate | Download (19.9 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
  , parseUnitAssumeBinary
40
  , plural
41
  , niceSort
42
  , niceSortKey
43
  , exitIfBad
44
  , exitErr
45
  , exitWhen
46
  , exitUnless
47
  , logWarningIfBad
48
  , rStripSpace
49
  , newUUID
50
  , getCurrentTime
51
  , getCurrentTimeUSec
52
  , clockTimeToString
53
  , chompPrefix
54
  , warn
55
  , wrap
56
  , trim
57
  , defaultHead
58
  , exitIfEmpty
59
  , splitEithers
60
  , recombineEithers
61
  , resolveAddr
62
  , monadicThe
63
  , setOwnerAndGroupFromNames
64
  , formatOrdinal
65
  , atomicWriteFile
66
  , tryAndLogIOError
67
  , lockFile
68
  , FStat
69
  , nullFStat
70
  , needsReload
71
  ) where
72

    
73
import Control.Exception (try)
74
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
75
import Data.Function (on)
76
import Data.List
77
import qualified Data.Map as M
78
import Control.Monad (foldM, liftM)
79
import System.Directory (renameFile)
80
import System.FilePath.Posix (takeDirectory, takeBaseName)
81
import System.Posix.Types
82

    
83
import Debug.Trace
84
import Network.Socket
85

    
86
import Ganeti.BasicTypes
87
import qualified Ganeti.ConstantUtils as ConstantUtils
88
import Ganeti.Logging
89
import Ganeti.Runtime
90
import System.IO
91
import System.Exit
92
import System.Posix.Files
93
import System.Posix.IO
94
import System.Time
95

    
96
-- * Debug functions
97

    
98
-- | To be used only for debugging, breaks referential integrity.
99
debug :: Show a => a -> a
100
debug x = trace (show x) x
101

    
102
-- | Displays a modified form of the second parameter before returning
103
-- it.
104
debugFn :: Show b => (a -> b) -> a -> a
105
debugFn fn x = debug (fn x) `seq` x
106

    
107
-- | Show the first parameter before returning the second one.
108
debugXy :: Show a => a -> b -> b
109
debugXy = seq . debug
110

    
111
-- * Miscellaneous
112

    
113
-- | Apply the function if condition holds, otherwise use default value.
114
applyIf :: Bool -> (a -> a) -> a -> a
115
applyIf b f x = if b then f x else x
116

    
117
-- | Comma-join a string list.
118
commaJoin :: [String] -> String
119
commaJoin = intercalate ","
120

    
121
-- | Split a list on a separator and return an array.
122
sepSplit :: Eq a => a -> [a] -> [[a]]
123
sepSplit sep s
124
  | null s    = []
125
  | null xs   = [x]
126
  | null ys   = [x,[]]
127
  | otherwise = x:sepSplit sep ys
128
  where (x, xs) = break (== sep) s
129
        ys = drop 1 xs
130

    
131
-- | Simple pluralize helper
132
plural :: Int -> String -> String -> String
133
plural 1 s _ = s
134
plural _ _ p = p
135

    
136
-- | Ensure a value is quoted if needed.
137
ensureQuoted :: String -> String
138
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
139
                 then '\'':v ++ "'"
140
                 else v
141

    
142
-- * Mathematical functions
143

    
144
-- Simple and slow statistical functions, please replace with better
145
-- versions
146

    
147
-- | Standard deviation function.
148
stdDev :: [Double] -> Double
149
stdDev lst =
150
  -- first, calculate the list length and sum lst in a single step,
151
  -- for performance reasons
152
  let (ll', sx) = foldl' (\(rl, rs) e ->
153
                           let rl' = rl + 1
154
                               rs' = rs + e
155
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
156
      ll = fromIntegral ll'::Double
157
      mv = sx / ll
158
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
159
  in sqrt (av / ll) -- stddev
160

    
161
-- *  Logical functions
162

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

    
168
-- | \"if\" as a function, rather than as syntactic sugar.
169
if' :: Bool -- ^ condition
170
    -> a    -- ^ \"then\" result
171
    -> a    -- ^ \"else\" result
172
    -> a    -- ^ \"then\" or "else" result depending on the condition
173
if' True x _ = x
174
if' _    _ y = y
175

    
176
-- * Parsing utility functions
177

    
178
-- | Parse results from readsPrec.
179
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
180
parseChoices _ _ ((v, ""):[]) = return v
181
parseChoices name s ((_, e):[]) =
182
    fail $ name ++ ": leftover characters when parsing '"
183
           ++ s ++ "': '" ++ e ++ "'"
184
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
185

    
186
-- | Safe 'read' function returning data encapsulated in a Result.
187
tryRead :: (Monad m, Read a) => String -> String -> m a
188
tryRead name s = parseChoices name s $ reads s
189

    
190
-- | Format a table of strings to maintain consistent length.
191
formatTable :: [[String]] -> [Bool] -> [[String]]
192
formatTable vals numpos =
193
    let vtrans = transpose vals  -- transpose, so that we work on rows
194
                                 -- rather than columns
195
        mlens = map (maximum . map length) vtrans
196
        expnd = map (\(flds, isnum, ml) ->
197
                         map (\val ->
198
                                  let delta = ml - length val
199
                                      filler = replicate delta ' '
200
                                  in if delta > 0
201
                                     then if isnum
202
                                          then filler ++ val
203
                                          else val ++ filler
204
                                     else val
205
                             ) flds
206
                    ) (zip3 vtrans numpos mlens)
207
   in transpose expnd
208

    
209
-- | Constructs a printable table from given header and rows
210
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
211
printTable lp header rows isnum =
212
  unlines . map ((++) lp . (:) ' ' . unwords) $
213
  formatTable (header:rows) isnum
214

    
215
-- | Converts a unit (e.g. m or GB) into a scaling factor.
216
parseUnitValue :: (Monad m) => Bool -> String -> m Rational
217
parseUnitValue noDecimal unit
218
  -- binary conversions first
219
  | null unit                     = return 1
220
  | unit == "m" || upper == "MIB" = return 1
221
  | unit == "g" || upper == "GIB" = return kbBinary
222
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
223
  -- SI conversions
224
  | unit == "M" || upper == "MB"  = return mbFactor
225
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
226
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
227
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
228
  where upper = map toUpper unit
229
        kbBinary = 1024 :: Rational
230
        kbDecimal = if noDecimal then kbBinary else 1000
231
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
232
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
233

    
234
-- | Tries to extract number and scale from the given string.
235
--
236
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
237
-- specified, it defaults to MiB. Return value is always an integral
238
-- value in MiB; if the first argument is True, all kilos are binary.
239
parseUnitEx :: (Monad m, Integral a, Read a) => Bool -> String -> m a
240
parseUnitEx noDecimal str =
241
  -- TODO: enhance this by splitting the unit parsing code out and
242
  -- accepting floating-point numbers
243
  case (reads str::[(Int, String)]) of
244
    [(v, suffix)] ->
245
      let unit = dropWhile (== ' ') suffix
246
      in do
247
        scaling <- parseUnitValue noDecimal unit
248
        return $ truncate (fromIntegral v * scaling)
249
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
250

    
251
-- | Tries to extract number and scale from the given string.
252
--
253
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
254
-- specified, it defaults to MiB. Return value is always an integral
255
-- value in MiB.
256
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
257
parseUnit = parseUnitEx False
258

    
259
-- | Tries to extract a number and scale from a given string, taking
260
-- all kilos to be binary.
261
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
262
parseUnitAssumeBinary = parseUnitEx True
263

    
264
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
265
-- otherwise returning the actual contained value.
266
exitIfBad :: String -> Result a -> IO a
267
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
268
exitIfBad _ (Ok v) = return v
269

    
270
-- | Exits immediately with an error message.
271
exitErr :: String -> IO a
272
exitErr errmsg = do
273
  hPutStrLn stderr $ "Error: " ++ errmsg
274
  exitWith (ExitFailure 1)
275

    
276
-- | Exits with an error message if the given boolean condition if true.
277
exitWhen :: Bool -> String -> IO ()
278
exitWhen True msg = exitErr msg
279
exitWhen False _  = return ()
280

    
281
-- | Exits with an error message /unless/ the given boolean condition
282
-- if true, the opposite of 'exitWhen'.
283
exitUnless :: Bool -> String -> IO ()
284
exitUnless cond = exitWhen (not cond)
285

    
286
-- | Unwraps a 'Result', logging a warning message and then returning a default
287
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
288
logWarningIfBad :: String -> a -> Result a -> IO a
289
logWarningIfBad msg defVal (Bad s) = do
290
  logWarning $ msg ++ ": " ++ s
291
  return defVal
292
logWarningIfBad _ _ (Ok v) = return v
293

    
294
-- | Try an IO interaction, log errors and unfold as a 'Result'.
295
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b)
296
tryAndLogIOError io msg okfn =
297
 try io >>= either
298
   (\ e -> do
299
       let combinedmsg = msg ++ ": " ++ show (e :: IOError)
300
       logError combinedmsg
301
       return . Bad $ combinedmsg)
302
   (return . okfn)
303

    
304
-- | Print a warning, but do not exit.
305
warn :: String -> IO ()
306
warn = hPutStrLn stderr . (++) "Warning: "
307

    
308
-- | Helper for 'niceSort'. Computes the key element for a given string.
309
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
310
           -> String                   -- ^ Remaining string
311
           -> ([Either Integer String], String)
312
extractKey ek [] = (reverse ek, [])
313
extractKey ek xs@(x:_) =
314
  let (span_fn, conv_fn) = if isDigit x
315
                             then (isDigit, Left . read)
316
                             else (not . isDigit, Right)
317
      (k, rest) = span span_fn xs
318
  in extractKey (conv_fn k:ek) rest
319

    
320
{-| Sort a list of strings based on digit and non-digit groupings.
321

    
322
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
323
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
324

    
325
The sort algorithm breaks each name in groups of either only-digits or
326
no-digits, and sorts based on each group.
327

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

    
335
-}
336
niceSort :: [String] -> [String]
337
niceSort = niceSortKey id
338

    
339
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
340
-- since we don't want to add an ordering constraint on the /a/ type,
341
-- hence the need to only compare the first element of the /(key, a)/
342
-- tuple.
343
niceSortKey :: (a -> String) -> [a] -> [a]
344
niceSortKey keyfn =
345
  map snd . sortBy (compare `on` fst) .
346
  map (\s -> (fst . extractKey [] $ keyfn s, s))
347

    
348
-- | Strip space characthers (including newline). As this is
349
-- expensive, should only be run on small strings.
350
rStripSpace :: String -> String
351
rStripSpace = reverse . dropWhile isSpace . reverse
352

    
353
-- | Returns a random UUID.
354
-- This is a Linux-specific method as it uses the /proc filesystem.
355
newUUID :: IO String
356
newUUID = do
357
  contents <- readFile ConstantUtils.randomUuidFile
358
  return $! rStripSpace $ take 128 contents
359

    
360
-- | Returns the current time as an 'Integer' representing the number
361
-- of seconds from the Unix epoch.
362
getCurrentTime :: IO Integer
363
getCurrentTime = do
364
  TOD ctime _ <- getClockTime
365
  return ctime
366

    
367
-- | Returns the current time as an 'Integer' representing the number
368
-- of microseconds from the Unix epoch (hence the need for 'Integer').
369
getCurrentTimeUSec :: IO Integer
370
getCurrentTimeUSec = do
371
  TOD ctime pico <- getClockTime
372
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
373
  -- picoseconds right
374
  return $ ctime * 1000000 + pico `div` 1000000
375

    
376
-- | Convert a ClockTime into a (seconds-only) timestamp.
377
clockTimeToString :: ClockTime -> String
378
clockTimeToString (TOD t _) = show t
379

    
380
{-| Strip a prefix from a string, allowing the last character of the prefix
381
(which is assumed to be a separator) to be absent from the string if the string
382
terminates there.
383

    
384
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
385
Nothing
386

    
387
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
388
Just \"baz\"
389

    
390
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
391
Just \"\"
392

    
393
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
394
Just \"\"
395

    
396
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
397
Nothing
398
-}
399
chompPrefix :: String -> String -> Maybe String
400
chompPrefix pfx str =
401
  if pfx `isPrefixOf` str || str == init pfx
402
    then Just $ drop (length pfx) str
403
    else Nothing
404

    
405
-- | Breaks a string in lines with length \<= maxWidth.
406
--
407
-- NOTE: The split is OK if:
408
--
409
-- * It doesn't break a word, i.e. the next line begins with space
410
--   (@isSpace . head $ rest@) or the current line ends with space
411
--   (@null revExtra@);
412
--
413
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
414
wrap :: Int      -- ^ maxWidth
415
     -> String   -- ^ string that needs wrapping
416
     -> [String] -- ^ string \"broken\" in lines
417
wrap maxWidth = filter (not . null) . map trim . wrap0
418
  where wrap0 :: String -> [String]
419
        wrap0 text
420
          | length text <= maxWidth = [text]
421
          | isSplitOK               = line : wrap0 rest
422
          | otherwise               = line' : wrap0 rest'
423
          where (line, rest) = splitAt maxWidth text
424
                (revExtra, revLine) = break isSpace . reverse $ line
425
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
426
                isSplitOK =
427
                  null revLine || null revExtra || startsWithSpace rest
428
                startsWithSpace (x:_) = isSpace x
429
                startsWithSpace _     = False
430

    
431
-- | Removes surrounding whitespace. Should only be used in small
432
-- strings.
433
trim :: String -> String
434
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
435

    
436
-- | A safer head version, with a default value.
437
defaultHead :: a -> [a] -> a
438
defaultHead def []    = def
439
defaultHead _   (x:_) = x
440

    
441
-- | A 'head' version in the I/O monad, for validating parameters
442
-- without which we cannot continue.
443
exitIfEmpty :: String -> [a] -> IO a
444
exitIfEmpty _ (x:_) = return x
445
exitIfEmpty s []    = exitErr s
446

    
447
-- | Obtain the unique element of a list in an arbitrary monad.
448
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
449
monadicThe s [] = fail s
450
monadicThe s (x:xs)
451
  | all (x ==) xs = return x
452
  | otherwise = fail s
453

    
454
-- | Split an 'Either' list into two separate lists (containing the
455
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
456
-- recombination later.
457
--
458
-- This is splitter; for recombination, look at 'recombineEithers'.
459
-- The sum of \"left\" and \"right\" lists should be equal to the
460
-- original list length, and the trail list should be the same length
461
-- as well. The entries in the resulting lists are reversed in
462
-- comparison with the original list.
463
splitEithers :: [Either a b] -> ([a], [b], [Bool])
464
splitEithers = foldl' splitter ([], [], [])
465
  where splitter (l, r, t) e =
466
          case e of
467
            Left  v -> (v:l, r, False:t)
468
            Right v -> (l, v:r, True:t)
469

    
470
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
471
-- list into a single 'Either' list.
472
--
473
-- This is the counterpart to 'splitEithers'. It does the opposite
474
-- transformation, and the output list will be the reverse of the
475
-- input lists. Since 'splitEithers' also reverses the lists, calling
476
-- these together will result in the original list.
477
--
478
-- Mismatches in the structure of the lists (e.g. inconsistent
479
-- lengths) are represented via 'Bad'; normally this function should
480
-- not fail, if lists are passed as generated by 'splitEithers'.
481
recombineEithers :: (Show a, Show b) =>
482
                    [a] -> [b] -> [Bool] -> Result [Either a b]
483
recombineEithers lefts rights trail =
484
  foldM recombiner ([], lefts, rights) trail >>= checker
485
    where checker (eithers, [], []) = Ok eithers
486
          checker (_, lefts', rights') =
487
            Bad $ "Inconsistent results after recombination, l'=" ++
488
                show lefts' ++ ", r'=" ++ show rights'
489
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
490
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
491
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
492
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
493
                                      show t
494

    
495
-- | Default hints for the resolver
496
resolveAddrHints :: Maybe AddrInfo
497
resolveAddrHints =
498
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
499

    
500
-- | Resolves a numeric address.
501
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
502
resolveAddr port str = do
503
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
504
  return $ case resolved of
505
             [] -> Bad "Invalid results from lookup?"
506
             best:_ -> Ok (addrFamily best, addrAddress best)
507

    
508
-- | Set the owner and the group of a file (given as names, not numeric id).
509
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
510
setOwnerAndGroupFromNames filename daemon dGroup = do
511
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
512
  -- is read only once per daemon startup, and then cached for further usage.
513
  runtimeEnts <- getEnts
514
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
515
  -- note: we use directly ! as lookup failures shouldn't happen, due
516
  -- to the map construction
517
  let uid = fst ents M.! daemon
518
  let gid = snd ents M.! dGroup
519
  setOwnerAndGroup filename uid gid
520

    
521
-- | Formats an integral number, appending a suffix.
522
formatOrdinal :: (Integral a, Show a) => a -> String
523
formatOrdinal num
524
  | num > 10 && num < 20 = suffix "th"
525
  | tens == 1            = suffix "st"
526
  | tens == 2            = suffix "nd"
527
  | tens == 3            = suffix "rd"
528
  | otherwise            = suffix "th"
529
  where tens     = num `mod` 10
530
        suffix s = show num ++ s
531

    
532
-- | Atomically write a file, by first writing the contents into a temporary
533
-- file and then renaming it to the old position.
534
atomicWriteFile :: FilePath -> String -> IO ()
535
atomicWriteFile path contents = do
536
  (tmppath, tmphandle) <- openTempFile (takeDirectory path) (takeBaseName path)
537
  hPutStr tmphandle contents
538
  hClose tmphandle
539
  renameFile tmppath path
540

    
541
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
542
-- back success.
543
lockFile :: FilePath -> IO (Result ())
544
lockFile path = do
545
  handle <- openFile path WriteMode
546
  fd <- handleToFd handle
547
  Control.Monad.liftM (either (Bad . show) Ok)
548
    (try (setLock fd (WriteLock, AbsoluteSeek, 0, 0)) :: IO (Either IOError ()))
549

    
550
-- | File stat identifier.
551
type FStat = (EpochTime, FileID, FileOffset)
552

    
553
-- | Null 'FStat' value.
554
nullFStat :: FStat
555
nullFStat = (-1, -1, -1)
556

    
557
-- | Computes the file cache data from a FileStatus structure.
558
buildFileStatus :: FileStatus -> FStat
559
buildFileStatus ofs =
560
    let modt = modificationTime ofs
561
        inum = fileID ofs
562
        fsize = fileSize ofs
563
    in (modt, inum, fsize)
564

    
565
-- | Wrapper over 'buildFileStatus'. This reads the data from the
566
-- filesystem and then builds our cache structure.
567
getFStat :: FilePath -> IO FStat
568
getFStat p = liftM buildFileStatus (getFileStatus p)
569

    
570
-- | Check if the file needs reloading
571
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
572
needsReload oldstat path = do
573
  newstat <- getFStat path
574
  return $ if newstat /= oldstat
575
             then Just newstat
576
             else Nothing