Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 9fb621af

History | View | Annotate | Download (12 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
  , clockTimeToString
50
  , chompPrefix
51
  , wrap
52
  , trim
53
  ) where
54

    
55
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
56
import Data.Function (on)
57
import Data.List
58

    
59
import Debug.Trace
60

    
61
import Ganeti.BasicTypes
62
import qualified Ganeti.Constants as C
63
import System.IO
64
import System.Exit
65
import System.Time
66

    
67
-- * Debug functions
68

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

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

    
78
-- | Show the first parameter before returning the second one.
79
debugXy :: Show a => a -> b -> b
80
debugXy = seq . debug
81

    
82
-- * Miscellaneous
83

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

    
88
-- | Comma-join a string list.
89
commaJoin :: [String] -> String
90
commaJoin = intercalate ","
91

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

    
102
-- | Simple pluralize helper
103
plural :: Int -> String -> String -> String
104
plural 1 s _ = s
105
plural _ _ p = p
106

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

    
113
-- * Mathematical functions
114

    
115
-- Simple and slow statistical functions, please replace with better
116
-- versions
117

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

    
132
-- *  Logical functions
133

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

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

    
147
-- * Parsing utility functions
148

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

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

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

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

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

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

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

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

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

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

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

    
256
{-| Sort a list of strings based on digit and non-digit groupings.
257

    
258
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
259
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
260

    
261
The sort algorithm breaks each name in groups of either only-digits or
262
no-digits, and sorts based on each group.
263

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

    
271
-}
272
niceSort :: [String] -> [String]
273
niceSort = niceSortKey id
274

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

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

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

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

    
303
-- | Convert a ClockTime into a (seconds-only) timestamp.
304
clockTimeToString :: ClockTime -> String
305
clockTimeToString (TOD t _) = show t
306

    
307
{-| Strip a prefix from a string, allowing the last character of the prefix
308
(which is assumed to be a separator) to be absent from the string if the string
309
terminates there.
310

    
311
>>> chompPrefix "foo:bar:" "a:b:c"
312
Nothing
313

    
314
>>> chompPrefix "foo:bar:" "foo:bar:baz"
315
Just "baz"
316

    
317
>>> chompPrefix "foo:bar:" "foo:bar:"
318
Just ""
319

    
320
>>> chompPrefix "foo:bar:" "foo:bar"
321
Just ""
322

    
323
>>> chompPrefix "foo:bar:" "foo:barbaz"
324
Nothing
325
-}
326
chompPrefix :: String -> String -> Maybe String
327
chompPrefix pfx str =
328
  if pfx `isPrefixOf` str || str == init pfx
329
    then Just $ drop (length pfx) str
330
    else Nothing
331

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

    
358
-- | Removes surrounding whitespace. Should only be used in small
359
-- strings.
360
trim :: String -> String
361
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace