Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ ace37e24

History | View | Annotate | Download (10.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
  , clockTimeToString
50
  , chompPrefix
51
  ) where
52

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

    
57
import Debug.Trace
58

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

    
65
-- * Debug functions
66

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

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

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

    
80
-- * Miscellaneous
81

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

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

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

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

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

    
111
-- * Mathematical functions
112

    
113
-- Simple and slow statistical functions, please replace with better
114
-- versions
115

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

    
130
-- *  Logical functions
131

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

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

    
145
-- * Parsing utility functions
146

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

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

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

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

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

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

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

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

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

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

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

    
254
{-| Sort a list of strings based on digit and non-digit groupings.
255

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

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

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

    
269
-}
270
niceSort :: [String] -> [String]
271
niceSort = niceSortKey id
272

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

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

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

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

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

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

    
309
>>> chompPrefix "foo:bar:" "a:b:c"
310
Nothing
311

    
312
>>> chompPrefix "foo:bar:" "foo:bar:baz"
313
Just "baz"
314

    
315
>>> chompPrefix "foo:bar:" "foo:bar:"
316
Just ""
317

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

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