Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Utils.hs @ 8bcdde0c

History | View | Annotate | Download (5.6 kB)

1 e4f08c46 Iustin Pop
{-| Utility functions -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 e2fa2baf Iustin Pop
Copyright (C) 2009 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 209b3711 Iustin Pop
    (
26 209b3711 Iustin Pop
      debug
27 209b3711 Iustin Pop
    , sepSplit
28 a80bf544 Iustin Pop
    , fst3
29 209b3711 Iustin Pop
    , varianceCoeff
30 3d7cd10b Iustin Pop
    , commaJoin
31 9ba5c28f Iustin Pop
    , readEitherString
32 9ba5c28f Iustin Pop
    , loadJSArray
33 9ba5c28f Iustin Pop
    , fromObj
34 117dc2d8 Iustin Pop
    , tryFromObj
35 117dc2d8 Iustin Pop
    , fromJVal
36 3f6af65c Iustin Pop
    , asJSObject
37 3f6af65c Iustin Pop
    , asObjectList
38 942403e6 Iustin Pop
    , fromJResult
39 5b763470 Iustin Pop
    , tryRead
40 c5f7412e Iustin Pop
    , formatTable
41 117dc2d8 Iustin Pop
    , annotateResult
42 209b3711 Iustin Pop
    ) where
43 e4f08c46 Iustin Pop
44 29ac5975 Iustin Pop
import Data.List
45 942403e6 Iustin Pop
import qualified Text.JSON as J
46 9ba5c28f Iustin Pop
import Text.Printf (printf)
47 e4f08c46 Iustin Pop
48 e4f08c46 Iustin Pop
import Debug.Trace
49 e4f08c46 Iustin Pop
50 117dc2d8 Iustin Pop
import Ganeti.HTools.Types
51 117dc2d8 Iustin Pop
52 9188aeef Iustin Pop
-- * Debug functions
53 9188aeef Iustin Pop
54 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
55 e4f08c46 Iustin Pop
debug :: Show a => a -> a
56 e4f08c46 Iustin Pop
debug x = trace (show x) x
57 e4f08c46 Iustin Pop
58 9188aeef Iustin Pop
-- * Miscelaneous
59 1b7cf8ca Iustin Pop
60 e4f08c46 Iustin Pop
-- | Comma-join a string list.
61 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
62 e4f08c46 Iustin Pop
commaJoin = intercalate ","
63 e4f08c46 Iustin Pop
64 e4f08c46 Iustin Pop
-- | Split a string on a separator and return an array.
65 e4f08c46 Iustin Pop
sepSplit :: Char -> String -> [String]
66 e4f08c46 Iustin Pop
sepSplit sep s
67 e4f08c46 Iustin Pop
    | x == "" && xs == [] = []
68 e4f08c46 Iustin Pop
    | xs == []            = [x]
69 9f6dcdea Iustin Pop
    | ys == []            = [x,""]
70 9f6dcdea Iustin Pop
    | otherwise           = x:sepSplit sep ys
71 e4f08c46 Iustin Pop
    where (x, xs) = break (== sep) s
72 e4f08c46 Iustin Pop
          ys = drop 1 xs
73 e4f08c46 Iustin Pop
74 a80bf544 Iustin Pop
-- | Simple version of 'fst' for a triple
75 a80bf544 Iustin Pop
fst3 :: (a, b, c) -> a
76 a80bf544 Iustin Pop
fst3 (a, _, _) = a
77 a80bf544 Iustin Pop
78 9188aeef Iustin Pop
-- * Mathematical functions
79 9188aeef Iustin Pop
80 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
81 185297fa Iustin Pop
-- versions
82 e4f08c46 Iustin Pop
83 185297fa Iustin Pop
-- | The covariance of the list
84 e27eb8ab Iustin Pop
varianceCoeff :: [Double] -> Double
85 185297fa Iustin Pop
varianceCoeff lst =
86 185297fa Iustin Pop
    let ll = fromIntegral (length lst)::Double -- length of list
87 185297fa Iustin Pop
        mv = sum lst / ll   -- mean value
88 185297fa Iustin Pop
        av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
89 185297fa Iustin Pop
        bv = sqrt (av / ll) -- stddev
90 185297fa Iustin Pop
        cv = bv / ll        -- covariance
91 185297fa Iustin Pop
    in cv
92 dd4c56ed Iustin Pop
93 9188aeef Iustin Pop
-- * JSON-related functions
94 9188aeef Iustin Pop
95 9188aeef Iustin Pop
-- | Converts a JSON Result into a monadic value.
96 9188aeef Iustin Pop
fromJResult :: Monad m => J.Result a -> m a
97 9188aeef Iustin Pop
fromJResult (J.Error x) = fail x
98 9188aeef Iustin Pop
fromJResult (J.Ok x) = return x
99 9188aeef Iustin Pop
100 9188aeef Iustin Pop
-- | Tries to read a string from a JSON value.
101 9188aeef Iustin Pop
--
102 9188aeef Iustin Pop
-- In case the value was not a string, we fail the read (in the
103 9188aeef Iustin Pop
-- context of the current monad.
104 5aa48dbe Iustin Pop
readEitherString :: (Monad m) => J.JSValue -> m String
105 9ba5c28f Iustin Pop
readEitherString v =
106 9ba5c28f Iustin Pop
    case v of
107 5aa48dbe Iustin Pop
      J.JSString s -> return $ J.fromJSString s
108 5aa48dbe Iustin Pop
      _ -> fail "Wrong JSON type"
109 9ba5c28f Iustin Pop
110 9188aeef Iustin Pop
-- | Converts a JSON message into an array of JSON objects.
111 5aa48dbe Iustin Pop
loadJSArray :: (Monad m) => String -> m [J.JSObject J.JSValue]
112 9f6dcdea Iustin Pop
loadJSArray = fromJResult . J.decodeStrict
113 9ba5c28f Iustin Pop
114 9188aeef Iustin Pop
-- | Reads a the value of a key in a JSON object.
115 262f3e6c Iustin Pop
fromObj :: (J.JSON a, Monad m) => String -> [(String, J.JSValue)] -> m a
116 9ba5c28f Iustin Pop
fromObj k o =
117 262f3e6c Iustin Pop
    case lookup k o of
118 585d4420 Iustin Pop
      Nothing -> fail $ printf "key '%s' not found in %s" k (show o)
119 942403e6 Iustin Pop
      Just val -> fromJResult $ J.readJSON val
120 9ba5c28f Iustin Pop
121 117dc2d8 Iustin Pop
-- | Annotate a Result with an ownership information
122 117dc2d8 Iustin Pop
annotateResult :: String -> Result a -> Result a
123 117dc2d8 Iustin Pop
annotateResult owner (Bad s) = Bad $ owner ++ ": " ++ s
124 117dc2d8 Iustin Pop
annotateResult _ v = v
125 117dc2d8 Iustin Pop
126 117dc2d8 Iustin Pop
-- | Try to extract a key from a object with better error reporting
127 117dc2d8 Iustin Pop
-- than fromObj
128 117dc2d8 Iustin Pop
tryFromObj :: (J.JSON a) =>
129 117dc2d8 Iustin Pop
              String -> [(String, J.JSValue)] -> String -> Result a
130 117dc2d8 Iustin Pop
tryFromObj t o k = annotateResult (t ++ " key '" ++ k ++ "'") (fromObj k o)
131 117dc2d8 Iustin Pop
132 117dc2d8 Iustin Pop
-- | Small wrapper over readJSON.
133 117dc2d8 Iustin Pop
fromJVal :: (Monad m, J.JSON a) => J.JSValue -> m a
134 117dc2d8 Iustin Pop
fromJVal v =
135 117dc2d8 Iustin Pop
    case J.readJSON v of
136 117dc2d8 Iustin Pop
      J.Error s -> fail ("Cannot convert value " ++ show v ++ ", error: " ++ s)
137 117dc2d8 Iustin Pop
      J.Ok x -> return x
138 117dc2d8 Iustin Pop
139 9188aeef Iustin Pop
-- | Converts a JSON value into a JSON object.
140 5aa48dbe Iustin Pop
asJSObject :: (Monad m) => J.JSValue -> m (J.JSObject J.JSValue)
141 5aa48dbe Iustin Pop
asJSObject (J.JSObject a) = return a
142 5aa48dbe Iustin Pop
asJSObject _ = fail "not an object"
143 942403e6 Iustin Pop
144 9188aeef Iustin Pop
-- | Coneverts a list of JSON values into a list of JSON objects.
145 5aa48dbe Iustin Pop
asObjectList :: (Monad m) => [J.JSValue] -> m [J.JSObject J.JSValue]
146 9f6dcdea Iustin Pop
asObjectList = mapM asJSObject
147 5b763470 Iustin Pop
148 5b763470 Iustin Pop
-- * Parsing utility functions
149 5b763470 Iustin Pop
150 5b763470 Iustin Pop
-- | Parse results from readsPrec
151 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
152 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
153 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
154 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
155 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
156 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
157 5b763470 Iustin Pop
158 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
159 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
160 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
161 c5f7412e Iustin Pop
162 c5f7412e Iustin Pop
-- | Format a table of strings to maintain consistent length
163 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
164 c5f7412e Iustin Pop
formatTable vals numpos =
165 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
166 c5f7412e Iustin Pop
                                 -- rather than columns
167 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
168 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
169 c5f7412e Iustin Pop
                         map (\val ->
170 c5f7412e Iustin Pop
                                  let delta = ml - length val
171 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
172 c5f7412e Iustin Pop
                                  in if delta > 0
173 c5f7412e Iustin Pop
                                     then if isnum
174 c5f7412e Iustin Pop
                                          then filler ++ val
175 c5f7412e Iustin Pop
                                          else val ++ filler
176 c5f7412e Iustin Pop
                                     else val
177 c5f7412e Iustin Pop
                             ) flds
178 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
179 c5f7412e Iustin Pop
   in transpose expnd