Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ a5c198eb

History | View | Annotate | Download (17.2 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
  , setOwnerAndGroupFromNames
61
  , b64StringToBitString
62
  , bitStringToB64String
63
  ) where
64

    
65
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
66
import Data.Function (on)
67
import Data.List
68
import qualified Data.Map as M
69
import Control.Monad (foldM)
70

    
71
import Debug.Trace
72

    
73
import Ganeti.BasicTypes
74
import qualified Ganeti.Constants as C
75
import Ganeti.Logging
76
import Ganeti.Runtime
77
import System.IO
78
import System.Exit
79
import System.Posix.Files
80
import System.Time
81

    
82
import qualified Data.ByteString as BS
83
import Data.ByteString.Base64 (decodeLenient, encode)
84
import qualified Data.ByteString.Char8 as BSC
85
import Data.Word (Word8)
86
import Data.Char (intToDigit, digitToInt)
87
import Numeric (showIntAtBase, readInt)
88

    
89
-- * Debug functions
90

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

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

    
100
-- | Show the first parameter before returning the second one.
101
debugXy :: Show a => a -> b -> b
102
debugXy = seq . debug
103

    
104
-- * Miscellaneous
105

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

    
110
-- | Comma-join a string list.
111
commaJoin :: [String] -> String
112
commaJoin = intercalate ","
113

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

    
124
-- | Simple pluralize helper
125
plural :: Int -> String -> String -> String
126
plural 1 s _ = s
127
plural _ _ p = p
128

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

    
135
-- * Mathematical functions
136

    
137
-- Simple and slow statistical functions, please replace with better
138
-- versions
139

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

    
154
-- *  Logical functions
155

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

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

    
169
-- * Parsing utility functions
170

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

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

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

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

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

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

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

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

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

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

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

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

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

    
290
{-| Sort a list of strings based on digit and non-digit groupings.
291

    
292
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
293
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
294

    
295
The sort algorithm breaks each name in groups of either only-digits or
296
no-digits, and sorts based on each group.
297

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

    
305
-}
306
niceSort :: [String] -> [String]
307
niceSort = niceSortKey id
308

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

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

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

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

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

    
346
-- | Convert a ClockTime into a (seconds-only) timestamp.
347
clockTimeToString :: ClockTime -> String
348
clockTimeToString (TOD t _) = show t
349

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

    
354
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
355
Nothing
356

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

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

    
363
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
364
Just \"\"
365

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

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

    
401
-- | Removes surrounding whitespace. Should only be used in small
402
-- strings.
403
trim :: String -> String
404
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
405

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

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

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

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

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

    
471
type BitString = String
472

    
473
-- | Base 64 encoded String to BitString
474
wordsToBitString :: [Word8] -> BitString
475
wordsToBitString =
476
    concatMap (padBits . wordToBits)
477
  where
478
    wordToBits = flip (showIntAtBase 2 intToDigit) ""
479
    padBits bs = replicate (8 - length bs) '0' ++ bs
480

    
481
decodeB64String :: String -> [Word8]
482
decodeB64String = BS.unpack . decodeLenient . BSC.pack
483

    
484
b64StringToBitString :: String -> BitString
485
b64StringToBitString = wordsToBitString . decodeB64String
486

    
487
-- | A BitString to Base 64 encoded String
488
bitStringToWords :: BitString -> [Word8]
489
bitStringToWords [] = []
490
bitStringToWords bs =
491
    bitStringToWord c : bitStringToWords rest
492
  where
493
    bitStringToWord = fst . head . readInt 2 (const True) digitToInt
494
    (c, rest) = splitAt 8 bs
495

    
496
encodeB64String :: [Word8] -> String
497
encodeB64String = BSC.unpack . encode . BS.pack
498

    
499
bitStringToB64String :: BitString -> String
500
bitStringToB64String  = encodeB64String . bitStringToWords