Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 11e90588

History | View | Annotate | Download (17.2 kB)

1 525bfb36 Iustin Pop
{-| Utility functions. -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 a7f0953a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 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 26d62e4c Iustin Pop
module Ganeti.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 79eef90b Agata Murawska
  , ensureQuoted
35 ebf38064 Iustin Pop
  , tryRead
36 ebf38064 Iustin Pop
  , formatTable
37 c3024b7e René Nussbaumer
  , printTable
38 ebf38064 Iustin Pop
  , parseUnit
39 19e310cc René Nussbaumer
  , plural
40 04edfc99 Iustin Pop
  , niceSort
41 04edfc99 Iustin Pop
  , niceSortKey
42 88a10df5 Iustin Pop
  , exitIfBad
43 88a10df5 Iustin Pop
  , exitErr
44 88a10df5 Iustin Pop
  , exitWhen
45 88a10df5 Iustin Pop
  , exitUnless
46 838393d1 Michele Tartara
  , logWarningIfBad
47 256e28c4 Iustin Pop
  , rStripSpace
48 80a0546b Michele Tartara
  , newUUID
49 ace37e24 Michele Tartara
  , getCurrentTime
50 a6e054a8 Iustin Pop
  , getCurrentTimeUSec
51 b6aeda4a Dato Simó
  , clockTimeToString
52 b009f682 Dato Simó
  , chompPrefix
53 7dbe4c72 Klaus Aehlig
  , warn
54 9fb621af Yiannis Tsiouris
  , wrap
55 9fb621af Yiannis Tsiouris
  , trim
56 72747d91 Iustin Pop
  , defaultHead
57 72747d91 Iustin Pop
  , exitIfEmpty
58 da9e2aff Iustin Pop
  , splitEithers
59 da9e2aff Iustin Pop
  , recombineEithers
60 a39cd547 Michele Tartara
  , setOwnerAndGroupFromNames
61 11e90588 Dimitris Aragiorgis
  , b64StringToBitString
62 11e90588 Dimitris Aragiorgis
  , bitStringToB64String
63 ebf38064 Iustin Pop
  ) where
64 e4f08c46 Iustin Pop
65 256e28c4 Iustin Pop
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
66 04edfc99 Iustin Pop
import Data.Function (on)
67 29ac5975 Iustin Pop
import Data.List
68 a39cd547 Michele Tartara
import qualified Data.Map as M
69 da9e2aff Iustin Pop
import Control.Monad (foldM)
70 e4f08c46 Iustin Pop
71 e4f08c46 Iustin Pop
import Debug.Trace
72 e4f08c46 Iustin Pop
73 88a10df5 Iustin Pop
import Ganeti.BasicTypes
74 80a0546b Michele Tartara
import qualified Ganeti.Constants as C
75 838393d1 Michele Tartara
import Ganeti.Logging
76 a39cd547 Michele Tartara
import Ganeti.Runtime
77 88a10df5 Iustin Pop
import System.IO
78 88a10df5 Iustin Pop
import System.Exit
79 a39cd547 Michele Tartara
import System.Posix.Files
80 b6aeda4a Dato Simó
import System.Time
81 88a10df5 Iustin Pop
82 11e90588 Dimitris Aragiorgis
import qualified Data.ByteString as BS
83 11e90588 Dimitris Aragiorgis
import Data.ByteString.Base64 (decodeLenient, encode)
84 11e90588 Dimitris Aragiorgis
import qualified Data.ByteString.Char8 as BSC
85 11e90588 Dimitris Aragiorgis
import Data.Word (Word8)
86 11e90588 Dimitris Aragiorgis
import Data.Char (intToDigit, digitToInt)
87 11e90588 Dimitris Aragiorgis
import Numeric (showIntAtBase, readInt)
88 11e90588 Dimitris Aragiorgis
89 9188aeef Iustin Pop
-- * Debug functions
90 9188aeef Iustin Pop
91 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
92 e4f08c46 Iustin Pop
debug :: Show a => a -> a
93 e4f08c46 Iustin Pop
debug x = trace (show x) x
94 e4f08c46 Iustin Pop
95 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
96 525bfb36 Iustin Pop
-- it.
97 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
98 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
99 adc5c176 Iustin Pop
100 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
101 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
102 05ff7a00 Agata Murawska
debugXy = seq . debug
103 adc5c176 Iustin Pop
104 525bfb36 Iustin Pop
-- * Miscellaneous
105 1b7cf8ca Iustin Pop
106 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
107 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
108 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
109 61bbbed7 Agata Murawska
110 e4f08c46 Iustin Pop
-- | Comma-join a string list.
111 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
112 e4f08c46 Iustin Pop
commaJoin = intercalate ","
113 e4f08c46 Iustin Pop
114 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
115 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
116 e4f08c46 Iustin Pop
sepSplit sep s
117 ebf38064 Iustin Pop
  | null s    = []
118 ebf38064 Iustin Pop
  | null xs   = [x]
119 ebf38064 Iustin Pop
  | null ys   = [x,[]]
120 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
121 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
122 ebf38064 Iustin Pop
        ys = drop 1 xs
123 e4f08c46 Iustin Pop
124 19e310cc René Nussbaumer
-- | Simple pluralize helper
125 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
126 19e310cc René Nussbaumer
plural 1 s _ = s
127 19e310cc René Nussbaumer
plural _ _ p = p
128 19e310cc René Nussbaumer
129 79eef90b Agata Murawska
-- | Ensure a value is quoted if needed.
130 79eef90b Agata Murawska
ensureQuoted :: String -> String
131 79eef90b Agata Murawska
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
132 79eef90b Agata Murawska
                 then '\'':v ++ "'"
133 79eef90b Agata Murawska
                 else v
134 79eef90b Agata Murawska
135 9188aeef Iustin Pop
-- * Mathematical functions
136 9188aeef Iustin Pop
137 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
138 185297fa Iustin Pop
-- versions
139 e4f08c46 Iustin Pop
140 525bfb36 Iustin Pop
-- | Standard deviation function.
141 4715711d Iustin Pop
stdDev :: [Double] -> Double
142 4715711d Iustin Pop
stdDev lst =
143 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
144 7570569e Iustin Pop
  -- for performance reasons
145 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
146 7570569e Iustin Pop
                           let rl' = rl + 1
147 7570569e Iustin Pop
                               rs' = rs + e
148 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
149 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
150 7570569e Iustin Pop
      mv = sx / ll
151 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
152 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
153 dd4c56ed Iustin Pop
154 bfe6c954 Guido Trotter
-- *  Logical functions
155 bfe6c954 Guido Trotter
156 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
157 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
158 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
159 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
160 bfe6c954 Guido Trotter
161 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
162 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
163 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
164 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
165 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
166 bfe6c954 Guido Trotter
if' True x _ = x
167 bfe6c954 Guido Trotter
if' _    _ y = y
168 bfe6c954 Guido Trotter
169 5b763470 Iustin Pop
-- * Parsing utility functions
170 5b763470 Iustin Pop
171 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
172 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
173 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
174 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
175 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
176 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
177 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
178 5b763470 Iustin Pop
179 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
180 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
181 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
182 c5f7412e Iustin Pop
183 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
184 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
185 c5f7412e Iustin Pop
formatTable vals numpos =
186 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
187 c5f7412e Iustin Pop
                                 -- rather than columns
188 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
189 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
190 c5f7412e Iustin Pop
                         map (\val ->
191 c5f7412e Iustin Pop
                                  let delta = ml - length val
192 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
193 c5f7412e Iustin Pop
                                  in if delta > 0
194 c5f7412e Iustin Pop
                                     then if isnum
195 c5f7412e Iustin Pop
                                          then filler ++ val
196 c5f7412e Iustin Pop
                                          else val ++ filler
197 c5f7412e Iustin Pop
                                     else val
198 c5f7412e Iustin Pop
                             ) flds
199 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
200 c5f7412e Iustin Pop
   in transpose expnd
201 9b9da389 Iustin Pop
202 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
203 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
204 c3024b7e René Nussbaumer
printTable lp header rows isnum =
205 2cdaf225 Iustin Pop
  unlines . map ((++) lp . (:) ' ' . unwords) $
206 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
207 c3024b7e René Nussbaumer
208 1cdcf8f3 Iustin Pop
-- | Converts a unit (e.g. m or GB) into a scaling factor.
209 1cdcf8f3 Iustin Pop
parseUnitValue :: (Monad m) => String -> m Rational
210 1cdcf8f3 Iustin Pop
parseUnitValue unit
211 1cdcf8f3 Iustin Pop
  -- binary conversions first
212 1cdcf8f3 Iustin Pop
  | null unit                     = return 1
213 1cdcf8f3 Iustin Pop
  | unit == "m" || upper == "MIB" = return 1
214 1cdcf8f3 Iustin Pop
  | unit == "g" || upper == "GIB" = return kbBinary
215 1cdcf8f3 Iustin Pop
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
216 1cdcf8f3 Iustin Pop
  -- SI conversions
217 1cdcf8f3 Iustin Pop
  | unit == "M" || upper == "MB"  = return mbFactor
218 1cdcf8f3 Iustin Pop
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
219 1cdcf8f3 Iustin Pop
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
220 1cdcf8f3 Iustin Pop
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
221 1cdcf8f3 Iustin Pop
  where upper = map toUpper unit
222 5850e990 Iustin Pop
        kbBinary = 1024 :: Rational
223 5850e990 Iustin Pop
        kbDecimal = 1000 :: Rational
224 1cdcf8f3 Iustin Pop
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
225 1cdcf8f3 Iustin Pop
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
226 1cdcf8f3 Iustin Pop
227 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
228 1cb92fac Iustin Pop
--
229 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
230 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
231 1cb92fac Iustin Pop
-- value in MiB.
232 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
233 1cb92fac Iustin Pop
parseUnit str =
234 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
235 ebf38064 Iustin Pop
  -- accepting floating-point numbers
236 1cdcf8f3 Iustin Pop
  case (reads str::[(Int, String)]) of
237 ebf38064 Iustin Pop
    [(v, suffix)] ->
238 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
239 1cdcf8f3 Iustin Pop
      in do
240 1cdcf8f3 Iustin Pop
        scaling <- parseUnitValue unit
241 1cdcf8f3 Iustin Pop
        return $ truncate (fromIntegral v * scaling)
242 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
243 88a10df5 Iustin Pop
244 88a10df5 Iustin Pop
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
245 88a10df5 Iustin Pop
-- otherwise returning the actual contained value.
246 88a10df5 Iustin Pop
exitIfBad :: String -> Result a -> IO a
247 707cd3d7 Helga Velroyen
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
248 88a10df5 Iustin Pop
exitIfBad _ (Ok v) = return v
249 88a10df5 Iustin Pop
250 88a10df5 Iustin Pop
-- | Exits immediately with an error message.
251 88a10df5 Iustin Pop
exitErr :: String -> IO a
252 88a10df5 Iustin Pop
exitErr errmsg = do
253 707cd3d7 Helga Velroyen
  hPutStrLn stderr $ "Error: " ++ errmsg
254 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
255 88a10df5 Iustin Pop
256 88a10df5 Iustin Pop
-- | Exits with an error message if the given boolean condition if true.
257 88a10df5 Iustin Pop
exitWhen :: Bool -> String -> IO ()
258 88a10df5 Iustin Pop
exitWhen True msg = exitErr msg
259 88a10df5 Iustin Pop
exitWhen False _  = return ()
260 88a10df5 Iustin Pop
261 88a10df5 Iustin Pop
-- | Exits with an error message /unless/ the given boolean condition
262 88a10df5 Iustin Pop
-- if true, the opposite of 'exitWhen'.
263 88a10df5 Iustin Pop
exitUnless :: Bool -> String -> IO ()
264 88a10df5 Iustin Pop
exitUnless cond = exitWhen (not cond)
265 04edfc99 Iustin Pop
266 838393d1 Michele Tartara
-- | Unwraps a 'Result', logging a warning message and then returning a default
267 838393d1 Michele Tartara
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
268 838393d1 Michele Tartara
logWarningIfBad :: String -> a -> Result a -> IO a
269 838393d1 Michele Tartara
logWarningIfBad msg defVal (Bad s) = do
270 838393d1 Michele Tartara
  logWarning $ msg ++ ": " ++ s
271 838393d1 Michele Tartara
  return defVal
272 838393d1 Michele Tartara
logWarningIfBad _ _ (Ok v) = return v
273 838393d1 Michele Tartara
274 7dbe4c72 Klaus Aehlig
-- | Print a warning, but do not exit.
275 7dbe4c72 Klaus Aehlig
warn :: String -> IO ()
276 7dbe4c72 Klaus Aehlig
warn = hPutStrLn stderr . (++) "Warning: "
277 7dbe4c72 Klaus Aehlig
278 04edfc99 Iustin Pop
-- | Helper for 'niceSort'. Computes the key element for a given string.
279 04edfc99 Iustin Pop
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
280 04edfc99 Iustin Pop
           -> String                   -- ^ Remaining string
281 04edfc99 Iustin Pop
           -> ([Either Integer String], String)
282 04edfc99 Iustin Pop
extractKey ek [] = (reverse ek, [])
283 04edfc99 Iustin Pop
extractKey ek xs@(x:_) =
284 04edfc99 Iustin Pop
  let (span_fn, conv_fn) = if isDigit x
285 04edfc99 Iustin Pop
                             then (isDigit, Left . read)
286 04edfc99 Iustin Pop
                             else (not . isDigit, Right)
287 04edfc99 Iustin Pop
      (k, rest) = span span_fn xs
288 04edfc99 Iustin Pop
  in extractKey (conv_fn k:ek) rest
289 04edfc99 Iustin Pop
290 04edfc99 Iustin Pop
{-| Sort a list of strings based on digit and non-digit groupings.
291 04edfc99 Iustin Pop
292 04edfc99 Iustin Pop
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
293 04edfc99 Iustin Pop
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
294 04edfc99 Iustin Pop
295 04edfc99 Iustin Pop
The sort algorithm breaks each name in groups of either only-digits or
296 04edfc99 Iustin Pop
no-digits, and sorts based on each group.
297 04edfc99 Iustin Pop
298 04edfc99 Iustin Pop
Internally, this is not implemented via regexes (like the Python
299 04edfc99 Iustin Pop
version), but via actual splitting of the string in sequences of
300 04edfc99 Iustin Pop
either digits or everything else, and converting the digit sequences
301 04edfc99 Iustin Pop
in /Left Integer/ and the non-digit ones in /Right String/, at which
302 04edfc99 Iustin Pop
point sorting becomes trivial due to the built-in 'Either' ordering;
303 04edfc99 Iustin Pop
we only need one extra step of dropping the key at the end.
304 04edfc99 Iustin Pop
305 04edfc99 Iustin Pop
-}
306 04edfc99 Iustin Pop
niceSort :: [String] -> [String]
307 a7f0953a Iustin Pop
niceSort = niceSortKey id
308 04edfc99 Iustin Pop
309 04edfc99 Iustin Pop
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
310 04edfc99 Iustin Pop
-- since we don't want to add an ordering constraint on the /a/ type,
311 04edfc99 Iustin Pop
-- hence the need to only compare the first element of the /(key, a)/
312 04edfc99 Iustin Pop
-- tuple.
313 04edfc99 Iustin Pop
niceSortKey :: (a -> String) -> [a] -> [a]
314 04edfc99 Iustin Pop
niceSortKey keyfn =
315 04edfc99 Iustin Pop
  map snd . sortBy (compare `on` fst) .
316 04edfc99 Iustin Pop
  map (\s -> (fst . extractKey [] $ keyfn s, s))
317 256e28c4 Iustin Pop
318 256e28c4 Iustin Pop
-- | Strip space characthers (including newline). As this is
319 256e28c4 Iustin Pop
-- expensive, should only be run on small strings.
320 256e28c4 Iustin Pop
rStripSpace :: String -> String
321 256e28c4 Iustin Pop
rStripSpace = reverse . dropWhile isSpace . reverse
322 80a0546b Michele Tartara
323 80a0546b Michele Tartara
-- | Returns a random UUID.
324 80a0546b Michele Tartara
-- This is a Linux-specific method as it uses the /proc filesystem.
325 80a0546b Michele Tartara
newUUID :: IO String
326 80a0546b Michele Tartara
newUUID = do
327 80a0546b Michele Tartara
  contents <- readFile C.randomUuidFile
328 37dfcacb Iustin Pop
  return $! rStripSpace $ take 128 contents
329 b6aeda4a Dato Simó
330 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
331 a6e054a8 Iustin Pop
-- of seconds from the Unix epoch.
332 ace37e24 Michele Tartara
getCurrentTime :: IO Integer
333 ace37e24 Michele Tartara
getCurrentTime = do
334 ace37e24 Michele Tartara
  TOD ctime _ <- getClockTime
335 ace37e24 Michele Tartara
  return ctime
336 ace37e24 Michele Tartara
337 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
338 a6e054a8 Iustin Pop
-- of microseconds from the Unix epoch (hence the need for 'Integer').
339 a6e054a8 Iustin Pop
getCurrentTimeUSec :: IO Integer
340 a6e054a8 Iustin Pop
getCurrentTimeUSec = do
341 a6e054a8 Iustin Pop
  TOD ctime pico <- getClockTime
342 a6e054a8 Iustin Pop
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
343 a6e054a8 Iustin Pop
  -- picoseconds right
344 a6e054a8 Iustin Pop
  return $ ctime * 1000000 + pico `div` 1000000
345 a6e054a8 Iustin Pop
346 b6aeda4a Dato Simó
-- | Convert a ClockTime into a (seconds-only) timestamp.
347 b6aeda4a Dato Simó
clockTimeToString :: ClockTime -> String
348 b6aeda4a Dato Simó
clockTimeToString (TOD t _) = show t
349 b009f682 Dato Simó
350 b009f682 Dato Simó
{-| Strip a prefix from a string, allowing the last character of the prefix
351 b009f682 Dato Simó
(which is assumed to be a separator) to be absent from the string if the string
352 b009f682 Dato Simó
terminates there.
353 b009f682 Dato Simó
354 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
355 b009f682 Dato Simó
Nothing
356 b009f682 Dato Simó
357 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
358 94042ae4 Michele Tartara
Just \"baz\"
359 b009f682 Dato Simó
360 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
361 94042ae4 Michele Tartara
Just \"\"
362 b009f682 Dato Simó
363 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
364 94042ae4 Michele Tartara
Just \"\"
365 b009f682 Dato Simó
366 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
367 b009f682 Dato Simó
Nothing
368 b009f682 Dato Simó
-}
369 b009f682 Dato Simó
chompPrefix :: String -> String -> Maybe String
370 b009f682 Dato Simó
chompPrefix pfx str =
371 b009f682 Dato Simó
  if pfx `isPrefixOf` str || str == init pfx
372 b009f682 Dato Simó
    then Just $ drop (length pfx) str
373 b009f682 Dato Simó
    else Nothing
374 9fb621af Yiannis Tsiouris
375 9fb621af Yiannis Tsiouris
-- | Breaks a string in lines with length \<= maxWidth.
376 9fb621af Yiannis Tsiouris
--
377 9fb621af Yiannis Tsiouris
-- NOTE: The split is OK if:
378 9fb621af Yiannis Tsiouris
--
379 9fb621af Yiannis Tsiouris
-- * It doesn't break a word, i.e. the next line begins with space
380 9fb621af Yiannis Tsiouris
--   (@isSpace . head $ rest@) or the current line ends with space
381 9fb621af Yiannis Tsiouris
--   (@null revExtra@);
382 9fb621af Yiannis Tsiouris
--
383 9fb621af Yiannis Tsiouris
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
384 9fb621af Yiannis Tsiouris
wrap :: Int      -- ^ maxWidth
385 9fb621af Yiannis Tsiouris
     -> String   -- ^ string that needs wrapping
386 9fb621af Yiannis Tsiouris
     -> [String] -- ^ string \"broken\" in lines
387 9fb621af Yiannis Tsiouris
wrap maxWidth = filter (not . null) . map trim . wrap0
388 9fb621af Yiannis Tsiouris
  where wrap0 :: String -> [String]
389 9fb621af Yiannis Tsiouris
        wrap0 text
390 9fb621af Yiannis Tsiouris
          | length text <= maxWidth = [text]
391 9fb621af Yiannis Tsiouris
          | isSplitOK               = line : wrap0 rest
392 9fb621af Yiannis Tsiouris
          | otherwise               = line' : wrap0 rest'
393 9fb621af Yiannis Tsiouris
          where (line, rest) = splitAt maxWidth text
394 9fb621af Yiannis Tsiouris
                (revExtra, revLine) = break isSpace . reverse $ line
395 9fb621af Yiannis Tsiouris
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
396 9fb621af Yiannis Tsiouris
                isSplitOK =
397 9fb621af Yiannis Tsiouris
                  null revLine || null revExtra || startsWithSpace rest
398 9fb621af Yiannis Tsiouris
                startsWithSpace (x:_) = isSpace x
399 9fb621af Yiannis Tsiouris
                startsWithSpace _     = False
400 9fb621af Yiannis Tsiouris
401 9fb621af Yiannis Tsiouris
-- | Removes surrounding whitespace. Should only be used in small
402 9fb621af Yiannis Tsiouris
-- strings.
403 9fb621af Yiannis Tsiouris
trim :: String -> String
404 9fb621af Yiannis Tsiouris
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
405 72747d91 Iustin Pop
406 72747d91 Iustin Pop
-- | A safer head version, with a default value.
407 72747d91 Iustin Pop
defaultHead :: a -> [a] -> a
408 72747d91 Iustin Pop
defaultHead def []    = def
409 72747d91 Iustin Pop
defaultHead _   (x:_) = x
410 72747d91 Iustin Pop
411 72747d91 Iustin Pop
-- | A 'head' version in the I/O monad, for validating parameters
412 72747d91 Iustin Pop
-- without which we cannot continue.
413 72747d91 Iustin Pop
exitIfEmpty :: String -> [a] -> IO a
414 72747d91 Iustin Pop
exitIfEmpty _ (x:_) = return x
415 72747d91 Iustin Pop
exitIfEmpty s []    = exitErr s
416 da9e2aff Iustin Pop
417 da9e2aff Iustin Pop
-- | Split an 'Either' list into two separate lists (containing the
418 da9e2aff Iustin Pop
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
419 da9e2aff Iustin Pop
-- recombination later.
420 da9e2aff Iustin Pop
--
421 da9e2aff Iustin Pop
-- This is splitter; for recombination, look at 'recombineEithers'.
422 da9e2aff Iustin Pop
-- The sum of \"left\" and \"right\" lists should be equal to the
423 da9e2aff Iustin Pop
-- original list length, and the trail list should be the same length
424 da9e2aff Iustin Pop
-- as well. The entries in the resulting lists are reversed in
425 da9e2aff Iustin Pop
-- comparison with the original list.
426 da9e2aff Iustin Pop
splitEithers :: [Either a b] -> ([a], [b], [Bool])
427 da9e2aff Iustin Pop
splitEithers = foldl' splitter ([], [], [])
428 da9e2aff Iustin Pop
  where splitter (l, r, t) e =
429 da9e2aff Iustin Pop
          case e of
430 da9e2aff Iustin Pop
            Left  v -> (v:l, r, False:t)
431 da9e2aff Iustin Pop
            Right v -> (l, v:r, True:t)
432 da9e2aff Iustin Pop
433 da9e2aff Iustin Pop
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
434 da9e2aff Iustin Pop
-- list into a single 'Either' list.
435 da9e2aff Iustin Pop
--
436 da9e2aff Iustin Pop
-- This is the counterpart to 'splitEithers'. It does the opposite
437 da9e2aff Iustin Pop
-- transformation, and the output list will be the reverse of the
438 da9e2aff Iustin Pop
-- input lists. Since 'splitEithers' also reverses the lists, calling
439 da9e2aff Iustin Pop
-- these together will result in the original list.
440 da9e2aff Iustin Pop
--
441 da9e2aff Iustin Pop
-- Mismatches in the structure of the lists (e.g. inconsistent
442 da9e2aff Iustin Pop
-- lengths) are represented via 'Bad'; normally this function should
443 da9e2aff Iustin Pop
-- not fail, if lists are passed as generated by 'splitEithers'.
444 da9e2aff Iustin Pop
recombineEithers :: (Show a, Show b) =>
445 da9e2aff Iustin Pop
                    [a] -> [b] -> [Bool] -> Result [Either a b]
446 da9e2aff Iustin Pop
recombineEithers lefts rights trail =
447 da9e2aff Iustin Pop
  foldM recombiner ([], lefts, rights) trail >>= checker
448 da9e2aff Iustin Pop
    where checker (eithers, [], []) = Ok eithers
449 da9e2aff Iustin Pop
          checker (_, lefts', rights') =
450 da9e2aff Iustin Pop
            Bad $ "Inconsistent results after recombination, l'=" ++
451 da9e2aff Iustin Pop
                show lefts' ++ ", r'=" ++ show rights'
452 da9e2aff Iustin Pop
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
453 da9e2aff Iustin Pop
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
454 da9e2aff Iustin Pop
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
455 da9e2aff Iustin Pop
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
456 da9e2aff Iustin Pop
                                      show t
457 a39cd547 Michele Tartara
458 a39cd547 Michele Tartara
-- | Set the owner and the group of a file (given as names, not numeric id).
459 a39cd547 Michele Tartara
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
460 a39cd547 Michele Tartara
setOwnerAndGroupFromNames filename daemon dGroup = do
461 a39cd547 Michele Tartara
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
462 a39cd547 Michele Tartara
  -- is read only once per daemon startup, and then cached for further usage.
463 a39cd547 Michele Tartara
  runtimeEnts <- getEnts
464 a39cd547 Michele Tartara
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
465 a39cd547 Michele Tartara
  -- note: we use directly ! as lookup failures shouldn't happen, due
466 a39cd547 Michele Tartara
  -- to the map construction
467 a39cd547 Michele Tartara
  let uid = fst ents M.! daemon
468 a39cd547 Michele Tartara
  let gid = snd ents M.! dGroup
469 a39cd547 Michele Tartara
  setOwnerAndGroup filename uid gid
470 11e90588 Dimitris Aragiorgis
471 11e90588 Dimitris Aragiorgis
type BitString = String
472 11e90588 Dimitris Aragiorgis
473 11e90588 Dimitris Aragiorgis
-- | Base 64 encoded String to BitString
474 11e90588 Dimitris Aragiorgis
wordsToBitString :: [Word8] -> BitString
475 11e90588 Dimitris Aragiorgis
wordsToBitString =
476 11e90588 Dimitris Aragiorgis
    concatMap (padBits . wordToBits)
477 11e90588 Dimitris Aragiorgis
  where
478 11e90588 Dimitris Aragiorgis
    wordToBits = flip (showIntAtBase 2 intToDigit) ""
479 11e90588 Dimitris Aragiorgis
    padBits bs = replicate (8 - length bs) '0' ++ bs
480 11e90588 Dimitris Aragiorgis
481 11e90588 Dimitris Aragiorgis
decodeB64String :: String -> [Word8]
482 11e90588 Dimitris Aragiorgis
decodeB64String = BS.unpack . decodeLenient . BSC.pack
483 11e90588 Dimitris Aragiorgis
484 11e90588 Dimitris Aragiorgis
b64StringToBitString :: String -> BitString
485 11e90588 Dimitris Aragiorgis
b64StringToBitString = wordsToBitString . decodeB64String
486 11e90588 Dimitris Aragiorgis
487 11e90588 Dimitris Aragiorgis
-- | A BitString to Base 64 encoded String
488 11e90588 Dimitris Aragiorgis
bitStringToWords :: BitString -> [Word8]
489 11e90588 Dimitris Aragiorgis
bitStringToWords [] = []
490 11e90588 Dimitris Aragiorgis
bitStringToWords bs =
491 11e90588 Dimitris Aragiorgis
    bitStringToWord c : bitStringToWords rest
492 11e90588 Dimitris Aragiorgis
  where
493 11e90588 Dimitris Aragiorgis
    bitStringToWord = fst . head . readInt 2 (const True) digitToInt
494 11e90588 Dimitris Aragiorgis
    (c, rest) = splitAt 8 bs
495 11e90588 Dimitris Aragiorgis
496 11e90588 Dimitris Aragiorgis
encodeB64String :: [Word8] -> String
497 11e90588 Dimitris Aragiorgis
encodeB64String = BSC.unpack . encode . BS.pack
498 11e90588 Dimitris Aragiorgis
499 11e90588 Dimitris Aragiorgis
bitStringToB64String :: BitString -> String
500 11e90588 Dimitris Aragiorgis
bitStringToB64String  = encodeB64String . bitStringToWords