Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 72747d91

History | View | Annotate | Download (12.7 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
  , rStripSpace
47
  , newUUID
48
  , getCurrentTime
49
  , getCurrentTimeUSec
50
  , clockTimeToString
51
  , chompPrefix
52
  , wrap
53
  , trim
54
  , defaultHead
55
  , exitIfEmpty
56
  ) where
57

    
58
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
59
import Data.Function (on)
60
import Data.List
61

    
62
import Debug.Trace
63

    
64
import Ganeti.BasicTypes
65
import qualified Ganeti.Constants as C
66
import System.IO
67
import System.Exit
68
import System.Time
69

    
70
-- * Debug functions
71

    
72
-- | To be used only for debugging, breaks referential integrity.
73
debug :: Show a => a -> a
74
debug x = trace (show x) x
75

    
76
-- | Displays a modified form of the second parameter before returning
77
-- it.
78
debugFn :: Show b => (a -> b) -> a -> a
79
debugFn fn x = debug (fn x) `seq` x
80

    
81
-- | Show the first parameter before returning the second one.
82
debugXy :: Show a => a -> b -> b
83
debugXy = seq . debug
84

    
85
-- * Miscellaneous
86

    
87
-- | Apply the function if condition holds, otherwise use default value.
88
applyIf :: Bool -> (a -> a) -> a -> a
89
applyIf b f x = if b then f x else x
90

    
91
-- | Comma-join a string list.
92
commaJoin :: [String] -> String
93
commaJoin = intercalate ","
94

    
95
-- | Split a list on a separator and return an array.
96
sepSplit :: Eq a => a -> [a] -> [[a]]
97
sepSplit sep s
98
  | null s    = []
99
  | null xs   = [x]
100
  | null ys   = [x,[]]
101
  | otherwise = x:sepSplit sep ys
102
  where (x, xs) = break (== sep) s
103
        ys = drop 1 xs
104

    
105
-- | Simple pluralize helper
106
plural :: Int -> String -> String -> String
107
plural 1 s _ = s
108
plural _ _ p = p
109

    
110
-- | Ensure a value is quoted if needed.
111
ensureQuoted :: String -> String
112
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
113
                 then '\'':v ++ "'"
114
                 else v
115

    
116
-- * Mathematical functions
117

    
118
-- Simple and slow statistical functions, please replace with better
119
-- versions
120

    
121
-- | Standard deviation function.
122
stdDev :: [Double] -> Double
123
stdDev lst =
124
  -- first, calculate the list length and sum lst in a single step,
125
  -- for performance reasons
126
  let (ll', sx) = foldl' (\(rl, rs) e ->
127
                           let rl' = rl + 1
128
                               rs' = rs + e
129
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
130
      ll = fromIntegral ll'::Double
131
      mv = sx / ll
132
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
133
  in sqrt (av / ll) -- stddev
134

    
135
-- *  Logical functions
136

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

    
142
-- | \"if\" as a function, rather than as syntactic sugar.
143
if' :: Bool -- ^ condition
144
    -> a    -- ^ \"then\" result
145
    -> a    -- ^ \"else\" result
146
    -> a    -- ^ \"then\" or "else" result depending on the condition
147
if' True x _ = x
148
if' _    _ y = y
149

    
150
-- * Parsing utility functions
151

    
152
-- | Parse results from readsPrec.
153
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
154
parseChoices _ _ ((v, ""):[]) = return v
155
parseChoices name s ((_, e):[]) =
156
    fail $ name ++ ": leftover characters when parsing '"
157
           ++ s ++ "': '" ++ e ++ "'"
158
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
159

    
160
-- | Safe 'read' function returning data encapsulated in a Result.
161
tryRead :: (Monad m, Read a) => String -> String -> m a
162
tryRead name s = parseChoices name s $ reads s
163

    
164
-- | Format a table of strings to maintain consistent length.
165
formatTable :: [[String]] -> [Bool] -> [[String]]
166
formatTable vals numpos =
167
    let vtrans = transpose vals  -- transpose, so that we work on rows
168
                                 -- rather than columns
169
        mlens = map (maximum . map length) vtrans
170
        expnd = map (\(flds, isnum, ml) ->
171
                         map (\val ->
172
                                  let delta = ml - length val
173
                                      filler = replicate delta ' '
174
                                  in if delta > 0
175
                                     then if isnum
176
                                          then filler ++ val
177
                                          else val ++ filler
178
                                     else val
179
                             ) flds
180
                    ) (zip3 vtrans numpos mlens)
181
   in transpose expnd
182

    
183
-- | Constructs a printable table from given header and rows
184
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
185
printTable lp header rows isnum =
186
  unlines . map ((++) lp . (:) ' ' . unwords) $
187
  formatTable (header:rows) isnum
188

    
189
-- | Converts a unit (e.g. m or GB) into a scaling factor.
190
parseUnitValue :: (Monad m) => String -> m Rational
191
parseUnitValue unit
192
  -- binary conversions first
193
  | null unit                     = return 1
194
  | unit == "m" || upper == "MIB" = return 1
195
  | unit == "g" || upper == "GIB" = return kbBinary
196
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
197
  -- SI conversions
198
  | unit == "M" || upper == "MB"  = return mbFactor
199
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
200
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
201
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
202
  where upper = map toUpper unit
203
        kbBinary = 1024 :: Rational
204
        kbDecimal = 1000 :: Rational
205
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
206
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
207

    
208
-- | Tries to extract number and scale from the given string.
209
--
210
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
211
-- specified, it defaults to MiB. Return value is always an integral
212
-- value in MiB.
213
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
214
parseUnit str =
215
  -- TODO: enhance this by splitting the unit parsing code out and
216
  -- accepting floating-point numbers
217
  case (reads str::[(Int, String)]) of
218
    [(v, suffix)] ->
219
      let unit = dropWhile (== ' ') suffix
220
      in do
221
        scaling <- parseUnitValue unit
222
        return $ truncate (fromIntegral v * scaling)
223
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
224

    
225
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
226
-- otherwise returning the actual contained value.
227
exitIfBad :: String -> Result a -> IO a
228
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
229
exitIfBad _ (Ok v) = return v
230

    
231
-- | Exits immediately with an error message.
232
exitErr :: String -> IO a
233
exitErr errmsg = do
234
  hPutStrLn stderr $ "Error: " ++ errmsg
235
  exitWith (ExitFailure 1)
236

    
237
-- | Exits with an error message if the given boolean condition if true.
238
exitWhen :: Bool -> String -> IO ()
239
exitWhen True msg = exitErr msg
240
exitWhen False _  = return ()
241

    
242
-- | Exits with an error message /unless/ the given boolean condition
243
-- if true, the opposite of 'exitWhen'.
244
exitUnless :: Bool -> String -> IO ()
245
exitUnless cond = exitWhen (not cond)
246

    
247
-- | Helper for 'niceSort'. Computes the key element for a given string.
248
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
249
           -> String                   -- ^ Remaining string
250
           -> ([Either Integer String], String)
251
extractKey ek [] = (reverse ek, [])
252
extractKey ek xs@(x:_) =
253
  let (span_fn, conv_fn) = if isDigit x
254
                             then (isDigit, Left . read)
255
                             else (not . isDigit, Right)
256
      (k, rest) = span span_fn xs
257
  in extractKey (conv_fn k:ek) rest
258

    
259
{-| Sort a list of strings based on digit and non-digit groupings.
260

    
261
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
262
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
263

    
264
The sort algorithm breaks each name in groups of either only-digits or
265
no-digits, and sorts based on each group.
266

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

    
274
-}
275
niceSort :: [String] -> [String]
276
niceSort = niceSortKey id
277

    
278
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
279
-- since we don't want to add an ordering constraint on the /a/ type,
280
-- hence the need to only compare the first element of the /(key, a)/
281
-- tuple.
282
niceSortKey :: (a -> String) -> [a] -> [a]
283
niceSortKey keyfn =
284
  map snd . sortBy (compare `on` fst) .
285
  map (\s -> (fst . extractKey [] $ keyfn s, s))
286

    
287
-- | Strip space characthers (including newline). As this is
288
-- expensive, should only be run on small strings.
289
rStripSpace :: String -> String
290
rStripSpace = reverse . dropWhile isSpace . reverse
291

    
292
-- | Returns a random UUID.
293
-- This is a Linux-specific method as it uses the /proc filesystem.
294
newUUID :: IO String
295
newUUID = do
296
  contents <- readFile C.randomUuidFile
297
  return $! rStripSpace $ take 128 contents
298

    
299
-- | Returns the current time as an 'Integer' representing the number
300
-- of seconds from the Unix epoch.
301
getCurrentTime :: IO Integer
302
getCurrentTime = do
303
  TOD ctime _ <- getClockTime
304
  return ctime
305

    
306
-- | Returns the current time as an 'Integer' representing the number
307
-- of microseconds from the Unix epoch (hence the need for 'Integer').
308
getCurrentTimeUSec :: IO Integer
309
getCurrentTimeUSec = do
310
  TOD ctime pico <- getClockTime
311
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
312
  -- picoseconds right
313
  return $ ctime * 1000000 + pico `div` 1000000
314

    
315
-- | Convert a ClockTime into a (seconds-only) timestamp.
316
clockTimeToString :: ClockTime -> String
317
clockTimeToString (TOD t _) = show t
318

    
319
{-| Strip a prefix from a string, allowing the last character of the prefix
320
(which is assumed to be a separator) to be absent from the string if the string
321
terminates there.
322

    
323
>>> chompPrefix "foo:bar:" "a:b:c"
324
Nothing
325

    
326
>>> chompPrefix "foo:bar:" "foo:bar:baz"
327
Just "baz"
328

    
329
>>> chompPrefix "foo:bar:" "foo:bar:"
330
Just ""
331

    
332
>>> chompPrefix "foo:bar:" "foo:bar"
333
Just ""
334

    
335
>>> chompPrefix "foo:bar:" "foo:barbaz"
336
Nothing
337
-}
338
chompPrefix :: String -> String -> Maybe String
339
chompPrefix pfx str =
340
  if pfx `isPrefixOf` str || str == init pfx
341
    then Just $ drop (length pfx) str
342
    else Nothing
343

    
344
-- | Breaks a string in lines with length \<= maxWidth.
345
--
346
-- NOTE: The split is OK if:
347
--
348
-- * It doesn't break a word, i.e. the next line begins with space
349
--   (@isSpace . head $ rest@) or the current line ends with space
350
--   (@null revExtra@);
351
--
352
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
353
wrap :: Int      -- ^ maxWidth
354
     -> String   -- ^ string that needs wrapping
355
     -> [String] -- ^ string \"broken\" in lines
356
wrap maxWidth = filter (not . null) . map trim . wrap0
357
  where wrap0 :: String -> [String]
358
        wrap0 text
359
          | length text <= maxWidth = [text]
360
          | isSplitOK               = line : wrap0 rest
361
          | otherwise               = line' : wrap0 rest'
362
          where (line, rest) = splitAt maxWidth text
363
                (revExtra, revLine) = break isSpace . reverse $ line
364
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
365
                isSplitOK =
366
                  null revLine || null revExtra || startsWithSpace rest
367
                startsWithSpace (x:_) = isSpace x
368
                startsWithSpace _     = False
369

    
370
-- | Removes surrounding whitespace. Should only be used in small
371
-- strings.
372
trim :: String -> String
373
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
374

    
375
-- | A safer head version, with a default value.
376
defaultHead :: a -> [a] -> a
377
defaultHead def []    = def
378
defaultHead _   (x:_) = x
379

    
380
-- | A 'head' version in the I/O monad, for validating parameters
381
-- without which we cannot continue.
382
exitIfEmpty :: String -> [a] -> IO a
383
exitIfEmpty _ (x:_) = return x
384
exitIfEmpty s []    = exitErr s