Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ b6aeda4a

History | View | Annotate | Download (9.9 kB)

1
{-| Utility functions. -}
2

    
3
{-
4

    
5
Copyright (C) 2009, 2010, 2011, 2012 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
  , clockTimeToString
49
  ) where
50

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

    
55
import Debug.Trace
56

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

    
63
-- * Debug functions
64

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

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

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

    
78
-- * Miscellaneous
79

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

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

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

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

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

    
109
-- * Mathematical functions
110

    
111
-- Simple and slow statistical functions, please replace with better
112
-- versions
113

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

    
128
-- *  Logical functions
129

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

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

    
143
-- * Parsing utility functions
144

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

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

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

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

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

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

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

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

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

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

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

    
252
{-| Sort a list of strings based on digit and non-digit groupings.
253

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

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

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

    
267
-}
268
niceSort :: [String] -> [String]
269
niceSort = map snd . sort . map (\s -> (fst $ extractKey [] s, s))
270

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

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

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

    
292
-- | Convert a ClockTime into a (seconds-only) timestamp.
293
clockTimeToString :: ClockTime -> String
294
clockTimeToString (TOD t _) = show t