Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 6fd8ceff

History | View | Annotate | Download (19.3 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
  , monadicThe
62
  , setOwnerAndGroupFromNames
63
  , formatOrdinal
64
  , atomicWriteFile
65
  , tryAndLogIOError
66
  , lockFile
67
  , FStat
68
  , nullFStat
69
  , needsReload
70
  ) where
71

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

    
82
import Debug.Trace
83
import Network.Socket
84

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

    
95
-- * Debug functions
96

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

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

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

    
110
-- * Miscellaneous
111

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

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

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

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

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

    
141
-- * Mathematical functions
142

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

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

    
160
-- *  Logical functions
161

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

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

    
175
-- * Parsing utility functions
176

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

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

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

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

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

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

    
250
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
251
-- otherwise returning the actual contained value.
252
exitIfBad :: String -> Result a -> IO a
253
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
254
exitIfBad _ (Ok v) = return v
255

    
256
-- | Exits immediately with an error message.
257
exitErr :: String -> IO a
258
exitErr errmsg = do
259
  hPutStrLn stderr $ "Error: " ++ errmsg
260
  exitWith (ExitFailure 1)
261

    
262
-- | Exits with an error message if the given boolean condition if true.
263
exitWhen :: Bool -> String -> IO ()
264
exitWhen True msg = exitErr msg
265
exitWhen False _  = return ()
266

    
267
-- | Exits with an error message /unless/ the given boolean condition
268
-- if true, the opposite of 'exitWhen'.
269
exitUnless :: Bool -> String -> IO ()
270
exitUnless cond = exitWhen (not cond)
271

    
272
-- | Unwraps a 'Result', logging a warning message and then returning a default
273
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
274
logWarningIfBad :: String -> a -> Result a -> IO a
275
logWarningIfBad msg defVal (Bad s) = do
276
  logWarning $ msg ++ ": " ++ s
277
  return defVal
278
logWarningIfBad _ _ (Ok v) = return v
279

    
280
-- | Try an IO interaction, log errors and unfold as a 'Result'.
281
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b)
282
tryAndLogIOError io msg okfn =
283
 try io >>= either
284
   (\ e -> do
285
       let combinedmsg = msg ++ ": " ++ show (e :: IOError)
286
       logError combinedmsg
287
       return . Bad $ combinedmsg)
288
   (return . okfn)
289

    
290
-- | Print a warning, but do not exit.
291
warn :: String -> IO ()
292
warn = hPutStrLn stderr . (++) "Warning: "
293

    
294
-- | Helper for 'niceSort'. Computes the key element for a given string.
295
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
296
           -> String                   -- ^ Remaining string
297
           -> ([Either Integer String], String)
298
extractKey ek [] = (reverse ek, [])
299
extractKey ek xs@(x:_) =
300
  let (span_fn, conv_fn) = if isDigit x
301
                             then (isDigit, Left . read)
302
                             else (not . isDigit, Right)
303
      (k, rest) = span span_fn xs
304
  in extractKey (conv_fn k:ek) rest
305

    
306
{-| Sort a list of strings based on digit and non-digit groupings.
307

    
308
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
309
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
310

    
311
The sort algorithm breaks each name in groups of either only-digits or
312
no-digits, and sorts based on each group.
313

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

    
321
-}
322
niceSort :: [String] -> [String]
323
niceSort = niceSortKey id
324

    
325
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
326
-- since we don't want to add an ordering constraint on the /a/ type,
327
-- hence the need to only compare the first element of the /(key, a)/
328
-- tuple.
329
niceSortKey :: (a -> String) -> [a] -> [a]
330
niceSortKey keyfn =
331
  map snd . sortBy (compare `on` fst) .
332
  map (\s -> (fst . extractKey [] $ keyfn s, s))
333

    
334
-- | Strip space characthers (including newline). As this is
335
-- expensive, should only be run on small strings.
336
rStripSpace :: String -> String
337
rStripSpace = reverse . dropWhile isSpace . reverse
338

    
339
-- | Returns a random UUID.
340
-- This is a Linux-specific method as it uses the /proc filesystem.
341
newUUID :: IO String
342
newUUID = do
343
  contents <- readFile ConstantUtils.randomUuidFile
344
  return $! rStripSpace $ take 128 contents
345

    
346
-- | Returns the current time as an 'Integer' representing the number
347
-- of seconds from the Unix epoch.
348
getCurrentTime :: IO Integer
349
getCurrentTime = do
350
  TOD ctime _ <- getClockTime
351
  return ctime
352

    
353
-- | Returns the current time as an 'Integer' representing the number
354
-- of microseconds from the Unix epoch (hence the need for 'Integer').
355
getCurrentTimeUSec :: IO Integer
356
getCurrentTimeUSec = do
357
  TOD ctime pico <- getClockTime
358
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
359
  -- picoseconds right
360
  return $ ctime * 1000000 + pico `div` 1000000
361

    
362
-- | Convert a ClockTime into a (seconds-only) timestamp.
363
clockTimeToString :: ClockTime -> String
364
clockTimeToString (TOD t _) = show t
365

    
366
{-| Strip a prefix from a string, allowing the last character of the prefix
367
(which is assumed to be a separator) to be absent from the string if the string
368
terminates there.
369

    
370
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
371
Nothing
372

    
373
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
374
Just \"baz\"
375

    
376
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
377
Just \"\"
378

    
379
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
380
Just \"\"
381

    
382
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
383
Nothing
384
-}
385
chompPrefix :: String -> String -> Maybe String
386
chompPrefix pfx str =
387
  if pfx `isPrefixOf` str || str == init pfx
388
    then Just $ drop (length pfx) str
389
    else Nothing
390

    
391
-- | Breaks a string in lines with length \<= maxWidth.
392
--
393
-- NOTE: The split is OK if:
394
--
395
-- * It doesn't break a word, i.e. the next line begins with space
396
--   (@isSpace . head $ rest@) or the current line ends with space
397
--   (@null revExtra@);
398
--
399
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
400
wrap :: Int      -- ^ maxWidth
401
     -> String   -- ^ string that needs wrapping
402
     -> [String] -- ^ string \"broken\" in lines
403
wrap maxWidth = filter (not . null) . map trim . wrap0
404
  where wrap0 :: String -> [String]
405
        wrap0 text
406
          | length text <= maxWidth = [text]
407
          | isSplitOK               = line : wrap0 rest
408
          | otherwise               = line' : wrap0 rest'
409
          where (line, rest) = splitAt maxWidth text
410
                (revExtra, revLine) = break isSpace . reverse $ line
411
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
412
                isSplitOK =
413
                  null revLine || null revExtra || startsWithSpace rest
414
                startsWithSpace (x:_) = isSpace x
415
                startsWithSpace _     = False
416

    
417
-- | Removes surrounding whitespace. Should only be used in small
418
-- strings.
419
trim :: String -> String
420
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
421

    
422
-- | A safer head version, with a default value.
423
defaultHead :: a -> [a] -> a
424
defaultHead def []    = def
425
defaultHead _   (x:_) = x
426

    
427
-- | A 'head' version in the I/O monad, for validating parameters
428
-- without which we cannot continue.
429
exitIfEmpty :: String -> [a] -> IO a
430
exitIfEmpty _ (x:_) = return x
431
exitIfEmpty s []    = exitErr s
432

    
433
-- | Obtain the unique element of a list in an arbitrary monad.
434
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
435
monadicThe s [] = fail s
436
monadicThe s (x:xs)
437
  | all (x ==) xs = return x
438
  | otherwise = fail s
439

    
440
-- | Split an 'Either' list into two separate lists (containing the
441
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
442
-- recombination later.
443
--
444
-- This is splitter; for recombination, look at 'recombineEithers'.
445
-- The sum of \"left\" and \"right\" lists should be equal to the
446
-- original list length, and the trail list should be the same length
447
-- as well. The entries in the resulting lists are reversed in
448
-- comparison with the original list.
449
splitEithers :: [Either a b] -> ([a], [b], [Bool])
450
splitEithers = foldl' splitter ([], [], [])
451
  where splitter (l, r, t) e =
452
          case e of
453
            Left  v -> (v:l, r, False:t)
454
            Right v -> (l, v:r, True:t)
455

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

    
481
-- | Default hints for the resolver
482
resolveAddrHints :: Maybe AddrInfo
483
resolveAddrHints =
484
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
485

    
486
-- | Resolves a numeric address.
487
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
488
resolveAddr port str = do
489
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
490
  return $ case resolved of
491
             [] -> Bad "Invalid results from lookup?"
492
             best:_ -> Ok (addrFamily best, addrAddress best)
493

    
494
-- | Set the owner and the group of a file (given as names, not numeric id).
495
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
496
setOwnerAndGroupFromNames filename daemon dGroup = do
497
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
498
  -- is read only once per daemon startup, and then cached for further usage.
499
  runtimeEnts <- getEnts
500
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
501
  -- note: we use directly ! as lookup failures shouldn't happen, due
502
  -- to the map construction
503
  let uid = fst ents M.! daemon
504
  let gid = snd ents M.! dGroup
505
  setOwnerAndGroup filename uid gid
506

    
507
-- | Formats an integral number, appending a suffix.
508
formatOrdinal :: (Integral a, Show a) => a -> String
509
formatOrdinal num
510
  | num > 10 && num < 20 = suffix "th"
511
  | tens == 1            = suffix "st"
512
  | tens == 2            = suffix "nd"
513
  | tens == 3            = suffix "rd"
514
  | otherwise            = suffix "th"
515
  where tens     = num `mod` 10
516
        suffix s = show num ++ s
517

    
518
-- | Atomically write a file, by first writing the contents into a temporary
519
-- file and then renaming it to the old position.
520
atomicWriteFile :: FilePath -> String -> IO ()
521
atomicWriteFile path contents = do
522
  (tmppath, tmphandle) <- openTempFile (takeDirectory path) (takeBaseName path)
523
  hPutStr tmphandle contents
524
  hClose tmphandle
525
  renameFile tmppath path
526

    
527
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
528
-- back success.
529
lockFile :: FilePath -> IO (Result ())
530
lockFile path = do
531
  handle <- openFile path WriteMode
532
  fd <- handleToFd handle
533
  Control.Monad.liftM (either (Bad . show) Ok)
534
    (try (setLock fd (WriteLock, AbsoluteSeek, 0, 0)) :: IO (Either IOError ()))
535

    
536
-- | File stat identifier.
537
type FStat = (EpochTime, FileID, FileOffset)
538

    
539
-- | Null 'FStat' value.
540
nullFStat :: FStat
541
nullFStat = (-1, -1, -1)
542

    
543
-- | Computes the file cache data from a FileStatus structure.
544
buildFileStatus :: FileStatus -> FStat
545
buildFileStatus ofs =
546
    let modt = modificationTime ofs
547
        inum = fileID ofs
548
        fsize = fileSize ofs
549
    in (modt, inum, fsize)
550

    
551
-- | Wrapper over 'buildFileStatus'. This reads the data from the
552
-- filesystem and then builds our cache structure.
553
getFStat :: FilePath -> IO FStat
554
getFStat p = liftM buildFileStatus (getFileStatus p)
555

    
556
-- | Check if the file needs reloading
557
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
558
needsReload oldstat path = do
559
  newstat <- getFStat path
560
  return $ if newstat /= oldstat
561
             then Just newstat
562
             else Nothing