Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Utils.hs @ ebf38064

History | View | Annotate | Download (7.1 kB)

1 525bfb36 Iustin Pop
{-| Utility functions. -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 e8230242 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
8 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
9 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
10 e2fa2baf Iustin Pop
(at your option) any later version.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
13 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
14 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15 e2fa2baf Iustin Pop
General Public License for more details.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
18 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
19 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
20 e2fa2baf Iustin Pop
02110-1301, USA.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
-}
23 e2fa2baf Iustin Pop
24 209b3711 Iustin Pop
module Ganeti.HTools.Utils
25 ebf38064 Iustin Pop
  ( debug
26 ebf38064 Iustin Pop
  , debugFn
27 ebf38064 Iustin Pop
  , debugXy
28 ebf38064 Iustin Pop
  , sepSplit
29 ebf38064 Iustin Pop
  , stdDev
30 ebf38064 Iustin Pop
  , if'
31 ebf38064 Iustin Pop
  , select
32 ebf38064 Iustin Pop
  , applyIf
33 ebf38064 Iustin Pop
  , commaJoin
34 ebf38064 Iustin Pop
  , readEitherString
35 ebf38064 Iustin Pop
  , JSRecord
36 ebf38064 Iustin Pop
  , loadJSArray
37 ebf38064 Iustin Pop
  , fromObj
38 ebf38064 Iustin Pop
  , fromObjWithDefault
39 ebf38064 Iustin Pop
  , maybeFromObj
40 ebf38064 Iustin Pop
  , tryFromObj
41 ebf38064 Iustin Pop
  , fromJVal
42 ebf38064 Iustin Pop
  , asJSObject
43 ebf38064 Iustin Pop
  , asObjectList
44 ebf38064 Iustin Pop
  , fromJResult
45 ebf38064 Iustin Pop
  , tryRead
46 ebf38064 Iustin Pop
  , formatTable
47 ebf38064 Iustin Pop
  , annotateResult
48 ebf38064 Iustin Pop
  , defaultGroupID
49 ebf38064 Iustin Pop
  , parseUnit
50 ebf38064 Iustin Pop
  ) where
51 e4f08c46 Iustin Pop
52 1cb92fac Iustin Pop
import Data.Char (toUpper)
53 29ac5975 Iustin Pop
import Data.List
54 942403e6 Iustin Pop
import qualified Text.JSON as J
55 e4f08c46 Iustin Pop
56 e4f08c46 Iustin Pop
import Debug.Trace
57 e4f08c46 Iustin Pop
58 117dc2d8 Iustin Pop
import Ganeti.HTools.Types
59 f047f90f Iustin Pop
-- we will re-export these for our existing users
60 f047f90f Iustin Pop
import Ganeti.HTools.JSON
61 117dc2d8 Iustin Pop
62 9188aeef Iustin Pop
-- * Debug functions
63 9188aeef Iustin Pop
64 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
65 e4f08c46 Iustin Pop
debug :: Show a => a -> a
66 e4f08c46 Iustin Pop
debug x = trace (show x) x
67 e4f08c46 Iustin Pop
68 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
69 525bfb36 Iustin Pop
-- it.
70 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
71 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
72 adc5c176 Iustin Pop
73 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
74 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
75 05ff7a00 Agata Murawska
debugXy = seq . debug
76 adc5c176 Iustin Pop
77 525bfb36 Iustin Pop
-- * Miscellaneous
78 1b7cf8ca Iustin Pop
79 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
80 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
81 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
82 61bbbed7 Agata Murawska
83 e4f08c46 Iustin Pop
-- | Comma-join a string list.
84 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
85 e4f08c46 Iustin Pop
commaJoin = intercalate ","
86 e4f08c46 Iustin Pop
87 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
88 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
89 e4f08c46 Iustin Pop
sepSplit sep s
90 ebf38064 Iustin Pop
  | null s    = []
91 ebf38064 Iustin Pop
  | null xs   = [x]
92 ebf38064 Iustin Pop
  | null ys   = [x,[]]
93 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
94 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
95 ebf38064 Iustin Pop
        ys = drop 1 xs
96 e4f08c46 Iustin Pop
97 9188aeef Iustin Pop
-- * Mathematical functions
98 9188aeef Iustin Pop
99 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
100 185297fa Iustin Pop
-- versions
101 e4f08c46 Iustin Pop
102 525bfb36 Iustin Pop
-- | Standard deviation function.
103 4715711d Iustin Pop
stdDev :: [Double] -> Double
104 4715711d Iustin Pop
stdDev lst =
105 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
106 7570569e Iustin Pop
  -- for performance reasons
107 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
108 7570569e Iustin Pop
                           let rl' = rl + 1
109 7570569e Iustin Pop
                               rs' = rs + e
110 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
111 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
112 7570569e Iustin Pop
      mv = sx / ll
113 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
114 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
115 dd4c56ed Iustin Pop
116 bfe6c954 Guido Trotter
-- *  Logical functions
117 bfe6c954 Guido Trotter
118 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
119 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
120 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
121 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
122 bfe6c954 Guido Trotter
123 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
124 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
125 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
126 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
127 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
128 bfe6c954 Guido Trotter
if' True x _ = x
129 bfe6c954 Guido Trotter
if' _    _ y = y
130 bfe6c954 Guido Trotter
131 bfe6c954 Guido Trotter
-- | Return the first result with a True condition, or the default otherwise.
132 bfe6c954 Guido Trotter
select :: a            -- ^ default result
133 bfe6c954 Guido Trotter
       -> [(Bool, a)]  -- ^ list of \"condition, result\"
134 bfe6c954 Guido Trotter
       -> a            -- ^ first result which has a True condition, or default
135 bfe6c954 Guido Trotter
select def = maybe def snd . find fst
136 bfe6c954 Guido Trotter
137 525bfb36 Iustin Pop
-- | Annotate a Result with an ownership information.
138 117dc2d8 Iustin Pop
annotateResult :: String -> Result a -> Result a
139 117dc2d8 Iustin Pop
annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s
140 117dc2d8 Iustin Pop
annotateResult _ v = v
141 117dc2d8 Iustin Pop
142 117dc2d8 Iustin Pop
-- | Try to extract a key from a object with better error reporting
143 525bfb36 Iustin Pop
-- than fromObj.
144 117dc2d8 Iustin Pop
tryFromObj :: (J.JSON a) =>
145 28f19313 Iustin Pop
              String     -- ^ Textual "owner" in error messages
146 28f19313 Iustin Pop
           -> JSRecord   -- ^ The object array
147 28f19313 Iustin Pop
           -> String     -- ^ The desired key from the object
148 a083e855 Iustin Pop
           -> Result a
149 e8230242 Iustin Pop
tryFromObj t o = annotateResult t . fromObj o
150 117dc2d8 Iustin Pop
151 5b763470 Iustin Pop
152 5b763470 Iustin Pop
-- * Parsing utility functions
153 5b763470 Iustin Pop
154 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
155 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
156 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
157 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
158 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
159 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
160 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
161 5b763470 Iustin Pop
162 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
163 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
164 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
165 c5f7412e Iustin Pop
166 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
167 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
168 c5f7412e Iustin Pop
formatTable vals numpos =
169 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
170 c5f7412e Iustin Pop
                                 -- rather than columns
171 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
172 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
173 c5f7412e Iustin Pop
                         map (\val ->
174 c5f7412e Iustin Pop
                                  let delta = ml - length val
175 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
176 c5f7412e Iustin Pop
                                  in if delta > 0
177 c5f7412e Iustin Pop
                                     then if isnum
178 c5f7412e Iustin Pop
                                          then filler ++ val
179 c5f7412e Iustin Pop
                                          else val ++ filler
180 c5f7412e Iustin Pop
                                     else val
181 c5f7412e Iustin Pop
                             ) flds
182 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
183 c5f7412e Iustin Pop
   in transpose expnd
184 9b9da389 Iustin Pop
185 525bfb36 Iustin Pop
-- | Default group UUID (just a string, not a real UUID).
186 c4d98278 Iustin Pop
defaultGroupID :: GroupID
187 c4d98278 Iustin Pop
defaultGroupID = "00000000-0000-0000-0000-000000000000"
188 1cb92fac Iustin Pop
189 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
190 1cb92fac Iustin Pop
--
191 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
192 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
193 1cb92fac Iustin Pop
-- value in MiB.
194 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
195 1cb92fac Iustin Pop
parseUnit str =
196 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
197 ebf38064 Iustin Pop
  -- accepting floating-point numbers
198 ebf38064 Iustin Pop
  case reads str of
199 ebf38064 Iustin Pop
    [(v, suffix)] ->
200 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
201 ebf38064 Iustin Pop
          upper = map toUpper unit
202 ebf38064 Iustin Pop
          siConvert x = x * 1000000 `div` 1048576
203 ebf38064 Iustin Pop
      in case () of
204 ebf38064 Iustin Pop
           _ | null unit -> return v
205 ebf38064 Iustin Pop
             | unit == "m" || upper == "MIB" -> return v
206 ebf38064 Iustin Pop
             | unit == "M" || upper == "MB"  -> return $ siConvert v
207 ebf38064 Iustin Pop
             | unit == "g" || upper == "GIB" -> return $ v * 1024
208 ebf38064 Iustin Pop
             | unit == "G" || upper == "GB"  -> return $ siConvert
209 ebf38064 Iustin Pop
                                                (v * 1000)
210 ebf38064 Iustin Pop
             | unit == "t" || upper == "TIB" -> return $ v * 1048576
211 ebf38064 Iustin Pop
             | unit == "T" || upper == "TB"  -> return $
212 ebf38064 Iustin Pop
                                                siConvert (v * 1000000)
213 ebf38064 Iustin Pop
             | otherwise -> fail $ "Unknown unit '" ++ unit ++ "'"
214 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"