Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ a0ee4f12

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
  , getFStat
71
  , needsReload
72
  ) where
73

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

    
84
import Debug.Trace
85
import Network.Socket
86

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

    
97
-- * Debug functions
98

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

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

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

    
112
-- * Miscellaneous
113

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

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

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

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

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

    
143
-- * Mathematical functions
144

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

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

    
162
-- *  Logical functions
163

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

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

    
177
-- * Parsing utility functions
178

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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