Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 13d26b66

History | View | Annotate | Download (24.8 kB)

1 a2a1a8ca Petr Pudlak
{-# LANGUAGE FlexibleContexts #-}
2 a2a1a8ca Petr Pudlak
3 525bfb36 Iustin Pop
{-| Utility functions. -}
4 e4f08c46 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 a7f0953a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 26d62e4c Iustin Pop
module Ganeti.Utils
27 ebf38064 Iustin Pop
  ( debug
28 ebf38064 Iustin Pop
  , debugFn
29 ebf38064 Iustin Pop
  , debugXy
30 ebf38064 Iustin Pop
  , sepSplit
31 ebf38064 Iustin Pop
  , stdDev
32 ebf38064 Iustin Pop
  , if'
33 ebf38064 Iustin Pop
  , select
34 ebf38064 Iustin Pop
  , applyIf
35 ebf38064 Iustin Pop
  , commaJoin
36 79eef90b Agata Murawska
  , ensureQuoted
37 ebf38064 Iustin Pop
  , tryRead
38 ebf38064 Iustin Pop
  , formatTable
39 c3024b7e René Nussbaumer
  , printTable
40 ebf38064 Iustin Pop
  , parseUnit
41 ef8b6bcf Klaus Aehlig
  , parseUnitAssumeBinary
42 19e310cc René Nussbaumer
  , plural
43 04edfc99 Iustin Pop
  , niceSort
44 04edfc99 Iustin Pop
  , niceSortKey
45 88a10df5 Iustin Pop
  , exitIfBad
46 88a10df5 Iustin Pop
  , exitErr
47 88a10df5 Iustin Pop
  , exitWhen
48 88a10df5 Iustin Pop
  , exitUnless
49 838393d1 Michele Tartara
  , logWarningIfBad
50 256e28c4 Iustin Pop
  , rStripSpace
51 80a0546b Michele Tartara
  , newUUID
52 ace37e24 Michele Tartara
  , getCurrentTime
53 a6e054a8 Iustin Pop
  , getCurrentTimeUSec
54 b6aeda4a Dato Simó
  , clockTimeToString
55 b009f682 Dato Simó
  , chompPrefix
56 7dbe4c72 Klaus Aehlig
  , warn
57 9fb621af Yiannis Tsiouris
  , wrap
58 9fb621af Yiannis Tsiouris
  , trim
59 72747d91 Iustin Pop
  , defaultHead
60 72747d91 Iustin Pop
  , exitIfEmpty
61 da9e2aff Iustin Pop
  , splitEithers
62 da9e2aff Iustin Pop
  , recombineEithers
63 986a8671 Michele Tartara
  , resolveAddr
64 bf7ee7ad Klaus Aehlig
  , monadicThe
65 a39cd547 Michele Tartara
  , setOwnerAndGroupFromNames
66 a2a1a8ca Petr Pudlak
  , setOwnerWGroupR
67 88b58ed6 Hrvoje Ribicic
  , formatOrdinal
68 5badb3e7 Klaus Aehlig
  , tryAndLogIOError
69 32b07c5f Klaus Aehlig
  , lockFile
70 6fd8ceff Klaus Aehlig
  , FStat
71 6fd8ceff Klaus Aehlig
  , nullFStat
72 a0ee4f12 Klaus Aehlig
  , getFStat
73 751fb9e2 Klaus Aehlig
  , getFStatSafe
74 6fd8ceff Klaus Aehlig
  , needsReload
75 6eeaf385 Klaus Aehlig
  , watchFile
76 b3f95121 Klaus Aehlig
  , safeRenameFile
77 ac81a213 Klaus Aehlig
  , FilePermissions(..)
78 96a4ebb8 Klaus Aehlig
  , ensurePermissions
79 ebf38064 Iustin Pop
  ) where
80 e4f08c46 Iustin Pop
81 6eeaf385 Klaus Aehlig
import Control.Concurrent
82 5badb3e7 Klaus Aehlig
import Control.Exception (try)
83 a2a1a8ca Petr Pudlak
import Control.Monad
84 a2a1a8ca Petr Pudlak
import Control.Monad.Error
85 256e28c4 Iustin Pop
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
86 96a4ebb8 Klaus Aehlig
import qualified Data.Either as E
87 04edfc99 Iustin Pop
import Data.Function (on)
88 6eeaf385 Klaus Aehlig
import Data.IORef
89 29ac5975 Iustin Pop
import Data.List
90 a39cd547 Michele Tartara
import qualified Data.Map as M
91 96a4ebb8 Klaus Aehlig
import Numeric (showOct)
92 b3f95121 Klaus Aehlig
import System.Directory (renameFile, createDirectoryIfMissing)
93 5f6515b6 Petr Pudlak
import System.FilePath.Posix (takeDirectory)
94 6eeaf385 Klaus Aehlig
import System.INotify
95 6fd8ceff Klaus Aehlig
import System.Posix.Types
96 e4f08c46 Iustin Pop
97 e4f08c46 Iustin Pop
import Debug.Trace
98 986a8671 Michele Tartara
import Network.Socket
99 e4f08c46 Iustin Pop
100 88a10df5 Iustin Pop
import Ganeti.BasicTypes
101 06fd57e5 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
102 838393d1 Michele Tartara
import Ganeti.Logging
103 a39cd547 Michele Tartara
import Ganeti.Runtime
104 88a10df5 Iustin Pop
import System.IO
105 88a10df5 Iustin Pop
import System.Exit
106 a39cd547 Michele Tartara
import System.Posix.Files
107 32b07c5f Klaus Aehlig
import System.Posix.IO
108 96a4ebb8 Klaus Aehlig
import System.Posix.User
109 b6aeda4a Dato Simó
import System.Time
110 88a10df5 Iustin Pop
111 9188aeef Iustin Pop
-- * Debug functions
112 9188aeef Iustin Pop
113 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
114 e4f08c46 Iustin Pop
debug :: Show a => a -> a
115 e4f08c46 Iustin Pop
debug x = trace (show x) x
116 e4f08c46 Iustin Pop
117 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
118 525bfb36 Iustin Pop
-- it.
119 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
120 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
121 adc5c176 Iustin Pop
122 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
123 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
124 05ff7a00 Agata Murawska
debugXy = seq . debug
125 adc5c176 Iustin Pop
126 525bfb36 Iustin Pop
-- * Miscellaneous
127 1b7cf8ca Iustin Pop
128 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
129 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
130 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
131 61bbbed7 Agata Murawska
132 e4f08c46 Iustin Pop
-- | Comma-join a string list.
133 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
134 e4f08c46 Iustin Pop
commaJoin = intercalate ","
135 e4f08c46 Iustin Pop
136 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
137 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
138 e4f08c46 Iustin Pop
sepSplit sep s
139 ebf38064 Iustin Pop
  | null s    = []
140 ebf38064 Iustin Pop
  | null xs   = [x]
141 ebf38064 Iustin Pop
  | null ys   = [x,[]]
142 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
143 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
144 ebf38064 Iustin Pop
        ys = drop 1 xs
145 e4f08c46 Iustin Pop
146 19e310cc René Nussbaumer
-- | Simple pluralize helper
147 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
148 19e310cc René Nussbaumer
plural 1 s _ = s
149 19e310cc René Nussbaumer
plural _ _ p = p
150 19e310cc René Nussbaumer
151 79eef90b Agata Murawska
-- | Ensure a value is quoted if needed.
152 79eef90b Agata Murawska
ensureQuoted :: String -> String
153 79eef90b Agata Murawska
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
154 79eef90b Agata Murawska
                 then '\'':v ++ "'"
155 79eef90b Agata Murawska
                 else v
156 79eef90b Agata Murawska
157 9188aeef Iustin Pop
-- * Mathematical functions
158 9188aeef Iustin Pop
159 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
160 185297fa Iustin Pop
-- versions
161 e4f08c46 Iustin Pop
162 525bfb36 Iustin Pop
-- | Standard deviation function.
163 4715711d Iustin Pop
stdDev :: [Double] -> Double
164 4715711d Iustin Pop
stdDev lst =
165 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
166 7570569e Iustin Pop
  -- for performance reasons
167 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
168 7570569e Iustin Pop
                           let rl' = rl + 1
169 7570569e Iustin Pop
                               rs' = rs + e
170 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
171 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
172 7570569e Iustin Pop
      mv = sx / ll
173 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
174 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
175 dd4c56ed Iustin Pop
176 bfe6c954 Guido Trotter
-- *  Logical functions
177 bfe6c954 Guido Trotter
178 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
179 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
180 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
181 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
182 bfe6c954 Guido Trotter
183 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
184 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
185 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
186 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
187 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
188 bfe6c954 Guido Trotter
if' True x _ = x
189 bfe6c954 Guido Trotter
if' _    _ y = y
190 bfe6c954 Guido Trotter
191 5b763470 Iustin Pop
-- * Parsing utility functions
192 5b763470 Iustin Pop
193 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
194 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
195 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
196 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
197 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
198 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
199 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
200 5b763470 Iustin Pop
201 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
202 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
203 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
204 c5f7412e Iustin Pop
205 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
206 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
207 c5f7412e Iustin Pop
formatTable vals numpos =
208 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
209 c5f7412e Iustin Pop
                                 -- rather than columns
210 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
211 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
212 c5f7412e Iustin Pop
                         map (\val ->
213 c5f7412e Iustin Pop
                                  let delta = ml - length val
214 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
215 c5f7412e Iustin Pop
                                  in if delta > 0
216 c5f7412e Iustin Pop
                                     then if isnum
217 c5f7412e Iustin Pop
                                          then filler ++ val
218 c5f7412e Iustin Pop
                                          else val ++ filler
219 c5f7412e Iustin Pop
                                     else val
220 c5f7412e Iustin Pop
                             ) flds
221 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
222 c5f7412e Iustin Pop
   in transpose expnd
223 9b9da389 Iustin Pop
224 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
225 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
226 c3024b7e René Nussbaumer
printTable lp header rows isnum =
227 2cdaf225 Iustin Pop
  unlines . map ((++) lp . (:) ' ' . unwords) $
228 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
229 c3024b7e René Nussbaumer
230 1cdcf8f3 Iustin Pop
-- | Converts a unit (e.g. m or GB) into a scaling factor.
231 ef8b6bcf Klaus Aehlig
parseUnitValue :: (Monad m) => Bool -> String -> m Rational
232 ef8b6bcf Klaus Aehlig
parseUnitValue noDecimal unit
233 1cdcf8f3 Iustin Pop
  -- binary conversions first
234 1cdcf8f3 Iustin Pop
  | null unit                     = return 1
235 1cdcf8f3 Iustin Pop
  | unit == "m" || upper == "MIB" = return 1
236 1cdcf8f3 Iustin Pop
  | unit == "g" || upper == "GIB" = return kbBinary
237 1cdcf8f3 Iustin Pop
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
238 1cdcf8f3 Iustin Pop
  -- SI conversions
239 1cdcf8f3 Iustin Pop
  | unit == "M" || upper == "MB"  = return mbFactor
240 1cdcf8f3 Iustin Pop
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
241 1cdcf8f3 Iustin Pop
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
242 1cdcf8f3 Iustin Pop
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
243 1cdcf8f3 Iustin Pop
  where upper = map toUpper unit
244 5850e990 Iustin Pop
        kbBinary = 1024 :: Rational
245 ef8b6bcf Klaus Aehlig
        kbDecimal = if noDecimal then kbBinary else 1000
246 1cdcf8f3 Iustin Pop
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
247 1cdcf8f3 Iustin Pop
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
248 1cdcf8f3 Iustin Pop
249 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
250 1cb92fac Iustin Pop
--
251 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
252 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
253 ef8b6bcf Klaus Aehlig
-- value in MiB; if the first argument is True, all kilos are binary.
254 ef8b6bcf Klaus Aehlig
parseUnitEx :: (Monad m, Integral a, Read a) => Bool -> String -> m a
255 ef8b6bcf Klaus Aehlig
parseUnitEx noDecimal str =
256 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
257 ebf38064 Iustin Pop
  -- accepting floating-point numbers
258 1cdcf8f3 Iustin Pop
  case (reads str::[(Int, String)]) of
259 ebf38064 Iustin Pop
    [(v, suffix)] ->
260 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
261 1cdcf8f3 Iustin Pop
      in do
262 ef8b6bcf Klaus Aehlig
        scaling <- parseUnitValue noDecimal unit
263 1cdcf8f3 Iustin Pop
        return $ truncate (fromIntegral v * scaling)
264 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
265 88a10df5 Iustin Pop
266 ef8b6bcf Klaus Aehlig
-- | Tries to extract number and scale from the given string.
267 ef8b6bcf Klaus Aehlig
--
268 ef8b6bcf Klaus Aehlig
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
269 ef8b6bcf Klaus Aehlig
-- specified, it defaults to MiB. Return value is always an integral
270 ef8b6bcf Klaus Aehlig
-- value in MiB.
271 ef8b6bcf Klaus Aehlig
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
272 ef8b6bcf Klaus Aehlig
parseUnit = parseUnitEx False
273 ef8b6bcf Klaus Aehlig
274 ef8b6bcf Klaus Aehlig
-- | Tries to extract a number and scale from a given string, taking
275 ef8b6bcf Klaus Aehlig
-- all kilos to be binary.
276 ef8b6bcf Klaus Aehlig
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
277 ef8b6bcf Klaus Aehlig
parseUnitAssumeBinary = parseUnitEx True
278 ef8b6bcf Klaus Aehlig
279 88a10df5 Iustin Pop
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
280 88a10df5 Iustin Pop
-- otherwise returning the actual contained value.
281 88a10df5 Iustin Pop
exitIfBad :: String -> Result a -> IO a
282 707cd3d7 Helga Velroyen
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
283 88a10df5 Iustin Pop
exitIfBad _ (Ok v) = return v
284 88a10df5 Iustin Pop
285 88a10df5 Iustin Pop
-- | Exits immediately with an error message.
286 88a10df5 Iustin Pop
exitErr :: String -> IO a
287 88a10df5 Iustin Pop
exitErr errmsg = do
288 707cd3d7 Helga Velroyen
  hPutStrLn stderr $ "Error: " ++ errmsg
289 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
290 88a10df5 Iustin Pop
291 88a10df5 Iustin Pop
-- | Exits with an error message if the given boolean condition if true.
292 88a10df5 Iustin Pop
exitWhen :: Bool -> String -> IO ()
293 88a10df5 Iustin Pop
exitWhen True msg = exitErr msg
294 88a10df5 Iustin Pop
exitWhen False _  = return ()
295 88a10df5 Iustin Pop
296 88a10df5 Iustin Pop
-- | Exits with an error message /unless/ the given boolean condition
297 88a10df5 Iustin Pop
-- if true, the opposite of 'exitWhen'.
298 88a10df5 Iustin Pop
exitUnless :: Bool -> String -> IO ()
299 88a10df5 Iustin Pop
exitUnless cond = exitWhen (not cond)
300 04edfc99 Iustin Pop
301 838393d1 Michele Tartara
-- | Unwraps a 'Result', logging a warning message and then returning a default
302 838393d1 Michele Tartara
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
303 838393d1 Michele Tartara
logWarningIfBad :: String -> a -> Result a -> IO a
304 838393d1 Michele Tartara
logWarningIfBad msg defVal (Bad s) = do
305 838393d1 Michele Tartara
  logWarning $ msg ++ ": " ++ s
306 838393d1 Michele Tartara
  return defVal
307 838393d1 Michele Tartara
logWarningIfBad _ _ (Ok v) = return v
308 838393d1 Michele Tartara
309 5badb3e7 Klaus Aehlig
-- | Try an IO interaction, log errors and unfold as a 'Result'.
310 5badb3e7 Klaus Aehlig
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b)
311 5badb3e7 Klaus Aehlig
tryAndLogIOError io msg okfn =
312 5badb3e7 Klaus Aehlig
 try io >>= either
313 5badb3e7 Klaus Aehlig
   (\ e -> do
314 5badb3e7 Klaus Aehlig
       let combinedmsg = msg ++ ": " ++ show (e :: IOError)
315 5badb3e7 Klaus Aehlig
       logError combinedmsg
316 5badb3e7 Klaus Aehlig
       return . Bad $ combinedmsg)
317 5badb3e7 Klaus Aehlig
   (return . okfn)
318 5badb3e7 Klaus Aehlig
319 7dbe4c72 Klaus Aehlig
-- | Print a warning, but do not exit.
320 7dbe4c72 Klaus Aehlig
warn :: String -> IO ()
321 7dbe4c72 Klaus Aehlig
warn = hPutStrLn stderr . (++) "Warning: "
322 7dbe4c72 Klaus Aehlig
323 04edfc99 Iustin Pop
-- | Helper for 'niceSort'. Computes the key element for a given string.
324 04edfc99 Iustin Pop
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
325 04edfc99 Iustin Pop
           -> String                   -- ^ Remaining string
326 04edfc99 Iustin Pop
           -> ([Either Integer String], String)
327 04edfc99 Iustin Pop
extractKey ek [] = (reverse ek, [])
328 04edfc99 Iustin Pop
extractKey ek xs@(x:_) =
329 04edfc99 Iustin Pop
  let (span_fn, conv_fn) = if isDigit x
330 04edfc99 Iustin Pop
                             then (isDigit, Left . read)
331 04edfc99 Iustin Pop
                             else (not . isDigit, Right)
332 04edfc99 Iustin Pop
      (k, rest) = span span_fn xs
333 04edfc99 Iustin Pop
  in extractKey (conv_fn k:ek) rest
334 04edfc99 Iustin Pop
335 04edfc99 Iustin Pop
{-| Sort a list of strings based on digit and non-digit groupings.
336 04edfc99 Iustin Pop
337 04edfc99 Iustin Pop
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
338 04edfc99 Iustin Pop
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
339 04edfc99 Iustin Pop
340 04edfc99 Iustin Pop
The sort algorithm breaks each name in groups of either only-digits or
341 04edfc99 Iustin Pop
no-digits, and sorts based on each group.
342 04edfc99 Iustin Pop
343 04edfc99 Iustin Pop
Internally, this is not implemented via regexes (like the Python
344 04edfc99 Iustin Pop
version), but via actual splitting of the string in sequences of
345 04edfc99 Iustin Pop
either digits or everything else, and converting the digit sequences
346 04edfc99 Iustin Pop
in /Left Integer/ and the non-digit ones in /Right String/, at which
347 04edfc99 Iustin Pop
point sorting becomes trivial due to the built-in 'Either' ordering;
348 04edfc99 Iustin Pop
we only need one extra step of dropping the key at the end.
349 04edfc99 Iustin Pop
350 04edfc99 Iustin Pop
-}
351 04edfc99 Iustin Pop
niceSort :: [String] -> [String]
352 a7f0953a Iustin Pop
niceSort = niceSortKey id
353 04edfc99 Iustin Pop
354 04edfc99 Iustin Pop
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
355 04edfc99 Iustin Pop
-- since we don't want to add an ordering constraint on the /a/ type,
356 04edfc99 Iustin Pop
-- hence the need to only compare the first element of the /(key, a)/
357 04edfc99 Iustin Pop
-- tuple.
358 04edfc99 Iustin Pop
niceSortKey :: (a -> String) -> [a] -> [a]
359 04edfc99 Iustin Pop
niceSortKey keyfn =
360 04edfc99 Iustin Pop
  map snd . sortBy (compare `on` fst) .
361 04edfc99 Iustin Pop
  map (\s -> (fst . extractKey [] $ keyfn s, s))
362 256e28c4 Iustin Pop
363 256e28c4 Iustin Pop
-- | Strip space characthers (including newline). As this is
364 256e28c4 Iustin Pop
-- expensive, should only be run on small strings.
365 256e28c4 Iustin Pop
rStripSpace :: String -> String
366 256e28c4 Iustin Pop
rStripSpace = reverse . dropWhile isSpace . reverse
367 80a0546b Michele Tartara
368 80a0546b Michele Tartara
-- | Returns a random UUID.
369 80a0546b Michele Tartara
-- This is a Linux-specific method as it uses the /proc filesystem.
370 80a0546b Michele Tartara
newUUID :: IO String
371 80a0546b Michele Tartara
newUUID = do
372 06fd57e5 Jose A. Lopes
  contents <- readFile ConstantUtils.randomUuidFile
373 37dfcacb Iustin Pop
  return $! rStripSpace $ take 128 contents
374 b6aeda4a Dato Simó
375 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
376 a6e054a8 Iustin Pop
-- of seconds from the Unix epoch.
377 ace37e24 Michele Tartara
getCurrentTime :: IO Integer
378 ace37e24 Michele Tartara
getCurrentTime = do
379 ace37e24 Michele Tartara
  TOD ctime _ <- getClockTime
380 ace37e24 Michele Tartara
  return ctime
381 ace37e24 Michele Tartara
382 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
383 a6e054a8 Iustin Pop
-- of microseconds from the Unix epoch (hence the need for 'Integer').
384 a6e054a8 Iustin Pop
getCurrentTimeUSec :: IO Integer
385 a6e054a8 Iustin Pop
getCurrentTimeUSec = do
386 a6e054a8 Iustin Pop
  TOD ctime pico <- getClockTime
387 a6e054a8 Iustin Pop
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
388 a6e054a8 Iustin Pop
  -- picoseconds right
389 a6e054a8 Iustin Pop
  return $ ctime * 1000000 + pico `div` 1000000
390 a6e054a8 Iustin Pop
391 b6aeda4a Dato Simó
-- | Convert a ClockTime into a (seconds-only) timestamp.
392 b6aeda4a Dato Simó
clockTimeToString :: ClockTime -> String
393 b6aeda4a Dato Simó
clockTimeToString (TOD t _) = show t
394 b009f682 Dato Simó
395 b009f682 Dato Simó
{-| Strip a prefix from a string, allowing the last character of the prefix
396 b009f682 Dato Simó
(which is assumed to be a separator) to be absent from the string if the string
397 b009f682 Dato Simó
terminates there.
398 b009f682 Dato Simó
399 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
400 b009f682 Dato Simó
Nothing
401 b009f682 Dato Simó
402 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
403 94042ae4 Michele Tartara
Just \"baz\"
404 b009f682 Dato Simó
405 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
406 94042ae4 Michele Tartara
Just \"\"
407 b009f682 Dato Simó
408 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
409 94042ae4 Michele Tartara
Just \"\"
410 b009f682 Dato Simó
411 94042ae4 Michele Tartara
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
412 b009f682 Dato Simó
Nothing
413 b009f682 Dato Simó
-}
414 b009f682 Dato Simó
chompPrefix :: String -> String -> Maybe String
415 b009f682 Dato Simó
chompPrefix pfx str =
416 b009f682 Dato Simó
  if pfx `isPrefixOf` str || str == init pfx
417 b009f682 Dato Simó
    then Just $ drop (length pfx) str
418 b009f682 Dato Simó
    else Nothing
419 9fb621af Yiannis Tsiouris
420 9fb621af Yiannis Tsiouris
-- | Breaks a string in lines with length \<= maxWidth.
421 9fb621af Yiannis Tsiouris
--
422 9fb621af Yiannis Tsiouris
-- NOTE: The split is OK if:
423 9fb621af Yiannis Tsiouris
--
424 9fb621af Yiannis Tsiouris
-- * It doesn't break a word, i.e. the next line begins with space
425 9fb621af Yiannis Tsiouris
--   (@isSpace . head $ rest@) or the current line ends with space
426 9fb621af Yiannis Tsiouris
--   (@null revExtra@);
427 9fb621af Yiannis Tsiouris
--
428 9fb621af Yiannis Tsiouris
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
429 9fb621af Yiannis Tsiouris
wrap :: Int      -- ^ maxWidth
430 9fb621af Yiannis Tsiouris
     -> String   -- ^ string that needs wrapping
431 9fb621af Yiannis Tsiouris
     -> [String] -- ^ string \"broken\" in lines
432 9fb621af Yiannis Tsiouris
wrap maxWidth = filter (not . null) . map trim . wrap0
433 9fb621af Yiannis Tsiouris
  where wrap0 :: String -> [String]
434 9fb621af Yiannis Tsiouris
        wrap0 text
435 9fb621af Yiannis Tsiouris
          | length text <= maxWidth = [text]
436 9fb621af Yiannis Tsiouris
          | isSplitOK               = line : wrap0 rest
437 9fb621af Yiannis Tsiouris
          | otherwise               = line' : wrap0 rest'
438 9fb621af Yiannis Tsiouris
          where (line, rest) = splitAt maxWidth text
439 9fb621af Yiannis Tsiouris
                (revExtra, revLine) = break isSpace . reverse $ line
440 9fb621af Yiannis Tsiouris
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
441 9fb621af Yiannis Tsiouris
                isSplitOK =
442 9fb621af Yiannis Tsiouris
                  null revLine || null revExtra || startsWithSpace rest
443 9fb621af Yiannis Tsiouris
                startsWithSpace (x:_) = isSpace x
444 9fb621af Yiannis Tsiouris
                startsWithSpace _     = False
445 9fb621af Yiannis Tsiouris
446 9fb621af Yiannis Tsiouris
-- | Removes surrounding whitespace. Should only be used in small
447 9fb621af Yiannis Tsiouris
-- strings.
448 9fb621af Yiannis Tsiouris
trim :: String -> String
449 9fb621af Yiannis Tsiouris
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
450 72747d91 Iustin Pop
451 72747d91 Iustin Pop
-- | A safer head version, with a default value.
452 72747d91 Iustin Pop
defaultHead :: a -> [a] -> a
453 72747d91 Iustin Pop
defaultHead def []    = def
454 72747d91 Iustin Pop
defaultHead _   (x:_) = x
455 72747d91 Iustin Pop
456 72747d91 Iustin Pop
-- | A 'head' version in the I/O monad, for validating parameters
457 72747d91 Iustin Pop
-- without which we cannot continue.
458 72747d91 Iustin Pop
exitIfEmpty :: String -> [a] -> IO a
459 72747d91 Iustin Pop
exitIfEmpty _ (x:_) = return x
460 72747d91 Iustin Pop
exitIfEmpty s []    = exitErr s
461 da9e2aff Iustin Pop
462 bf7ee7ad Klaus Aehlig
-- | Obtain the unique element of a list in an arbitrary monad.
463 bf7ee7ad Klaus Aehlig
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
464 bf7ee7ad Klaus Aehlig
monadicThe s [] = fail s
465 bf7ee7ad Klaus Aehlig
monadicThe s (x:xs)
466 bf7ee7ad Klaus Aehlig
  | all (x ==) xs = return x
467 bf7ee7ad Klaus Aehlig
  | otherwise = fail s
468 bf7ee7ad Klaus Aehlig
469 da9e2aff Iustin Pop
-- | Split an 'Either' list into two separate lists (containing the
470 da9e2aff Iustin Pop
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
471 da9e2aff Iustin Pop
-- recombination later.
472 da9e2aff Iustin Pop
--
473 da9e2aff Iustin Pop
-- This is splitter; for recombination, look at 'recombineEithers'.
474 da9e2aff Iustin Pop
-- The sum of \"left\" and \"right\" lists should be equal to the
475 da9e2aff Iustin Pop
-- original list length, and the trail list should be the same length
476 da9e2aff Iustin Pop
-- as well. The entries in the resulting lists are reversed in
477 da9e2aff Iustin Pop
-- comparison with the original list.
478 da9e2aff Iustin Pop
splitEithers :: [Either a b] -> ([a], [b], [Bool])
479 da9e2aff Iustin Pop
splitEithers = foldl' splitter ([], [], [])
480 da9e2aff Iustin Pop
  where splitter (l, r, t) e =
481 da9e2aff Iustin Pop
          case e of
482 da9e2aff Iustin Pop
            Left  v -> (v:l, r, False:t)
483 da9e2aff Iustin Pop
            Right v -> (l, v:r, True:t)
484 da9e2aff Iustin Pop
485 da9e2aff Iustin Pop
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
486 da9e2aff Iustin Pop
-- list into a single 'Either' list.
487 da9e2aff Iustin Pop
--
488 da9e2aff Iustin Pop
-- This is the counterpart to 'splitEithers'. It does the opposite
489 da9e2aff Iustin Pop
-- transformation, and the output list will be the reverse of the
490 da9e2aff Iustin Pop
-- input lists. Since 'splitEithers' also reverses the lists, calling
491 da9e2aff Iustin Pop
-- these together will result in the original list.
492 da9e2aff Iustin Pop
--
493 da9e2aff Iustin Pop
-- Mismatches in the structure of the lists (e.g. inconsistent
494 da9e2aff Iustin Pop
-- lengths) are represented via 'Bad'; normally this function should
495 da9e2aff Iustin Pop
-- not fail, if lists are passed as generated by 'splitEithers'.
496 da9e2aff Iustin Pop
recombineEithers :: (Show a, Show b) =>
497 da9e2aff Iustin Pop
                    [a] -> [b] -> [Bool] -> Result [Either a b]
498 da9e2aff Iustin Pop
recombineEithers lefts rights trail =
499 da9e2aff Iustin Pop
  foldM recombiner ([], lefts, rights) trail >>= checker
500 da9e2aff Iustin Pop
    where checker (eithers, [], []) = Ok eithers
501 da9e2aff Iustin Pop
          checker (_, lefts', rights') =
502 da9e2aff Iustin Pop
            Bad $ "Inconsistent results after recombination, l'=" ++
503 da9e2aff Iustin Pop
                show lefts' ++ ", r'=" ++ show rights'
504 da9e2aff Iustin Pop
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
505 da9e2aff Iustin Pop
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
506 da9e2aff Iustin Pop
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
507 da9e2aff Iustin Pop
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
508 da9e2aff Iustin Pop
                                      show t
509 986a8671 Michele Tartara
510 986a8671 Michele Tartara
-- | Default hints for the resolver
511 986a8671 Michele Tartara
resolveAddrHints :: Maybe AddrInfo
512 986a8671 Michele Tartara
resolveAddrHints =
513 986a8671 Michele Tartara
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
514 986a8671 Michele Tartara
515 986a8671 Michele Tartara
-- | Resolves a numeric address.
516 986a8671 Michele Tartara
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
517 986a8671 Michele Tartara
resolveAddr port str = do
518 986a8671 Michele Tartara
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
519 986a8671 Michele Tartara
  return $ case resolved of
520 986a8671 Michele Tartara
             [] -> Bad "Invalid results from lookup?"
521 986a8671 Michele Tartara
             best:_ -> Ok (addrFamily best, addrAddress best)
522 858ecf2b Klaus Aehlig
523 a39cd547 Michele Tartara
-- | Set the owner and the group of a file (given as names, not numeric id).
524 a39cd547 Michele Tartara
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
525 a39cd547 Michele Tartara
setOwnerAndGroupFromNames filename daemon dGroup = do
526 a39cd547 Michele Tartara
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
527 a39cd547 Michele Tartara
  -- is read only once per daemon startup, and then cached for further usage.
528 a39cd547 Michele Tartara
  runtimeEnts <- getEnts
529 a39cd547 Michele Tartara
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
530 a39cd547 Michele Tartara
  -- note: we use directly ! as lookup failures shouldn't happen, due
531 a39cd547 Michele Tartara
  -- to the map construction
532 a39cd547 Michele Tartara
  let uid = fst ents M.! daemon
533 a39cd547 Michele Tartara
  let gid = snd ents M.! dGroup
534 a39cd547 Michele Tartara
  setOwnerAndGroup filename uid gid
535 88b58ed6 Hrvoje Ribicic
536 a2a1a8ca Petr Pudlak
-- | Resets permissions so that the owner can read/write and the group only
537 a2a1a8ca Petr Pudlak
-- read. All other permissions are cleared.
538 a2a1a8ca Petr Pudlak
setOwnerWGroupR :: FilePath -> IO ()
539 a2a1a8ca Petr Pudlak
setOwnerWGroupR path = setFileMode path mode
540 a2a1a8ca Petr Pudlak
  where mode = foldl unionFileModes nullFileMode
541 a2a1a8ca Petr Pudlak
                     [ownerReadMode, ownerWriteMode, groupReadMode]
542 a2a1a8ca Petr Pudlak
543 88b58ed6 Hrvoje Ribicic
-- | Formats an integral number, appending a suffix.
544 88b58ed6 Hrvoje Ribicic
formatOrdinal :: (Integral a, Show a) => a -> String
545 88b58ed6 Hrvoje Ribicic
formatOrdinal num
546 88b58ed6 Hrvoje Ribicic
  | num > 10 && num < 20 = suffix "th"
547 88b58ed6 Hrvoje Ribicic
  | tens == 1            = suffix "st"
548 88b58ed6 Hrvoje Ribicic
  | tens == 2            = suffix "nd"
549 88b58ed6 Hrvoje Ribicic
  | tens == 3            = suffix "rd"
550 88b58ed6 Hrvoje Ribicic
  | otherwise            = suffix "th"
551 88b58ed6 Hrvoje Ribicic
  where tens     = num `mod` 10
552 88b58ed6 Hrvoje Ribicic
        suffix s = show num ++ s
553 710f5ae2 Klaus Aehlig
554 32b07c5f Klaus Aehlig
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
555 32b07c5f Klaus Aehlig
-- back success.
556 32b07c5f Klaus Aehlig
lockFile :: FilePath -> IO (Result ())
557 69bf84e1 Petr Pudlak
lockFile path = runResultT . liftIO $ do
558 32b07c5f Klaus Aehlig
  handle <- openFile path WriteMode
559 32b07c5f Klaus Aehlig
  fd <- handleToFd handle
560 69bf84e1 Petr Pudlak
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
561 6fd8ceff Klaus Aehlig
562 6fd8ceff Klaus Aehlig
-- | File stat identifier.
563 6fd8ceff Klaus Aehlig
type FStat = (EpochTime, FileID, FileOffset)
564 6fd8ceff Klaus Aehlig
565 6fd8ceff Klaus Aehlig
-- | Null 'FStat' value.
566 6fd8ceff Klaus Aehlig
nullFStat :: FStat
567 6fd8ceff Klaus Aehlig
nullFStat = (-1, -1, -1)
568 6fd8ceff Klaus Aehlig
569 6fd8ceff Klaus Aehlig
-- | Computes the file cache data from a FileStatus structure.
570 6fd8ceff Klaus Aehlig
buildFileStatus :: FileStatus -> FStat
571 6fd8ceff Klaus Aehlig
buildFileStatus ofs =
572 6fd8ceff Klaus Aehlig
    let modt = modificationTime ofs
573 6fd8ceff Klaus Aehlig
        inum = fileID ofs
574 6fd8ceff Klaus Aehlig
        fsize = fileSize ofs
575 6fd8ceff Klaus Aehlig
    in (modt, inum, fsize)
576 6fd8ceff Klaus Aehlig
577 6fd8ceff Klaus Aehlig
-- | Wrapper over 'buildFileStatus'. This reads the data from the
578 6fd8ceff Klaus Aehlig
-- filesystem and then builds our cache structure.
579 6fd8ceff Klaus Aehlig
getFStat :: FilePath -> IO FStat
580 6fd8ceff Klaus Aehlig
getFStat p = liftM buildFileStatus (getFileStatus p)
581 6fd8ceff Klaus Aehlig
582 751fb9e2 Klaus Aehlig
-- | Safe version of 'getFStat', that ignores IOErrors.
583 751fb9e2 Klaus Aehlig
getFStatSafe :: FilePath -> IO FStat
584 751fb9e2 Klaus Aehlig
getFStatSafe fpath = liftM (either (const nullFStat) id)
585 751fb9e2 Klaus Aehlig
                       ((try $ getFStat fpath) :: IO (Either IOError FStat))
586 751fb9e2 Klaus Aehlig
587 6fd8ceff Klaus Aehlig
-- | Check if the file needs reloading
588 6fd8ceff Klaus Aehlig
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
589 6fd8ceff Klaus Aehlig
needsReload oldstat path = do
590 6fd8ceff Klaus Aehlig
  newstat <- getFStat path
591 6fd8ceff Klaus Aehlig
  return $ if newstat /= oldstat
592 6fd8ceff Klaus Aehlig
             then Just newstat
593 6fd8ceff Klaus Aehlig
             else Nothing
594 6eeaf385 Klaus Aehlig
595 6eeaf385 Klaus Aehlig
-- | Until the given point in time (useconds since the epoch), wait
596 6eeaf385 Klaus Aehlig
-- for the output of a given method to change and return the new value;
597 6eeaf385 Klaus Aehlig
-- make use of the promise that the output only changes if the reference
598 6eeaf385 Klaus Aehlig
-- has a value different than the given one.
599 6eeaf385 Klaus Aehlig
watchFileEx :: (Eq a, Eq b) => Integer -> b -> IORef b -> a -> IO a -> IO a
600 6eeaf385 Klaus Aehlig
watchFileEx endtime base ref old read_fn = do
601 6eeaf385 Klaus Aehlig
  current <- getCurrentTimeUSec
602 6eeaf385 Klaus Aehlig
  if current > endtime then read_fn else do
603 6eeaf385 Klaus Aehlig
    val <- readIORef ref
604 6eeaf385 Klaus Aehlig
    if val /= base
605 6eeaf385 Klaus Aehlig
      then do
606 6eeaf385 Klaus Aehlig
        new <- read_fn
607 6eeaf385 Klaus Aehlig
        if new /= old then return new else do
608 2f575937 Klaus Aehlig
          logDebug "Observed change not relevant"
609 6eeaf385 Klaus Aehlig
          threadDelay 100000
610 6eeaf385 Klaus Aehlig
          watchFileEx endtime val ref old read_fn
611 6eeaf385 Klaus Aehlig
      else do 
612 6eeaf385 Klaus Aehlig
       threadDelay 100000
613 6eeaf385 Klaus Aehlig
       watchFileEx endtime base ref old read_fn
614 6eeaf385 Klaus Aehlig
615 6eeaf385 Klaus Aehlig
-- | Within the given timeout (in seconds), wait for for the output
616 6eeaf385 Klaus Aehlig
-- of the given method to change and return the new value; make use of
617 6eeaf385 Klaus Aehlig
-- the promise that the method will only change its value, if
618 6eeaf385 Klaus Aehlig
-- the given file changes on disk. If the file does not exist on disk, return
619 6eeaf385 Klaus Aehlig
-- immediately.
620 6eeaf385 Klaus Aehlig
watchFile :: Eq a => FilePath -> Int -> a -> IO a -> IO a
621 6eeaf385 Klaus Aehlig
watchFile fpath timeout old read_fn = do
622 6eeaf385 Klaus Aehlig
  current <- getCurrentTimeUSec
623 6eeaf385 Klaus Aehlig
  let endtime = current + fromIntegral timeout * 1000000
624 6eeaf385 Klaus Aehlig
  fstat <- getFStatSafe fpath
625 6eeaf385 Klaus Aehlig
  ref <- newIORef fstat
626 6eeaf385 Klaus Aehlig
  inotify <- initINotify
627 e97cce9f Klaus Aehlig
  let do_watch e = do
628 e97cce9f Klaus Aehlig
                     logDebug $ "Notified of change in " ++ fpath 
629 e97cce9f Klaus Aehlig
                                  ++ "; event: " ++ show e
630 e97cce9f Klaus Aehlig
                     when (e == Ignored)
631 e97cce9f Klaus Aehlig
                       (addWatch inotify [Modify, Delete] fpath do_watch
632 e97cce9f Klaus Aehlig
                          >> return ())
633 e97cce9f Klaus Aehlig
                     fstat' <- getFStatSafe fpath
634 e97cce9f Klaus Aehlig
                     writeIORef ref fstat'
635 e97cce9f Klaus Aehlig
  _ <- addWatch inotify [Modify, Delete] fpath do_watch
636 f18aaff4 Klaus Aehlig
  newval <- read_fn
637 f18aaff4 Klaus Aehlig
  if newval /= old
638 f18aaff4 Klaus Aehlig
    then do
639 f18aaff4 Klaus Aehlig
      logDebug $ "File " ++ fpath ++ " changed during setup of inotify"
640 f18aaff4 Klaus Aehlig
      killINotify inotify
641 f18aaff4 Klaus Aehlig
      return newval
642 f18aaff4 Klaus Aehlig
    else do
643 f18aaff4 Klaus Aehlig
      result <- watchFileEx endtime fstat ref old read_fn
644 f18aaff4 Klaus Aehlig
      killINotify inotify
645 f18aaff4 Klaus Aehlig
      return result
646 ac81a213 Klaus Aehlig
647 ac81a213 Klaus Aehlig
-- | Type describing ownership and permissions of newly generated
648 ac81a213 Klaus Aehlig
-- directories and files. All parameters are optional, with nothing
649 ac81a213 Klaus Aehlig
-- meaning that the default value should be left untouched.
650 ac81a213 Klaus Aehlig
651 ac81a213 Klaus Aehlig
data FilePermissions = FilePermissions { fpOwner :: Maybe String
652 ac81a213 Klaus Aehlig
                                       , fpGroup :: Maybe String
653 ac81a213 Klaus Aehlig
                                       , fpPermissions :: FileMode
654 ac81a213 Klaus Aehlig
                                       }
655 ac81a213 Klaus Aehlig
656 96a4ebb8 Klaus Aehlig
-- | Ensure that a given file or directory has the permissions, and
657 96a4ebb8 Klaus Aehlig
-- possibly ownerships, as required.
658 96a4ebb8 Klaus Aehlig
ensurePermissions :: FilePath -> FilePermissions -> IO (Result ())
659 96a4ebb8 Klaus Aehlig
ensurePermissions fpath perms = do
660 96a4ebb8 Klaus Aehlig
  eitherFileStatus <- try $ getFileStatus fpath
661 96a4ebb8 Klaus Aehlig
                      :: IO (Either IOError FileStatus)
662 96a4ebb8 Klaus Aehlig
  (flip $ either (return . Bad . show)) eitherFileStatus $ \fstat -> do
663 96a4ebb8 Klaus Aehlig
    ownertry <- case fpOwner perms of
664 96a4ebb8 Klaus Aehlig
      Nothing -> return $ Right ()
665 96a4ebb8 Klaus Aehlig
      Just owner -> try $ do
666 96a4ebb8 Klaus Aehlig
        ownerid <- userID `liftM` getUserEntryForName owner
667 96a4ebb8 Klaus Aehlig
        unless (ownerid == fileOwner fstat) $ do
668 96a4ebb8 Klaus Aehlig
          logDebug $ "Changing owner of " ++ fpath ++ " to " ++ owner
669 96a4ebb8 Klaus Aehlig
          setOwnerAndGroup fpath ownerid (-1)
670 96a4ebb8 Klaus Aehlig
    grouptry <- case fpGroup perms of
671 96a4ebb8 Klaus Aehlig
      Nothing -> return $ Right ()
672 96a4ebb8 Klaus Aehlig
      Just grp -> try $ do
673 96a4ebb8 Klaus Aehlig
        groupid <- groupID `liftM` getGroupEntryForName grp
674 96a4ebb8 Klaus Aehlig
        unless (groupid == fileGroup fstat) $ do
675 96a4ebb8 Klaus Aehlig
          logDebug $ "Changing group of " ++ fpath ++ " to " ++ grp
676 96a4ebb8 Klaus Aehlig
          setOwnerAndGroup fpath (-1) groupid
677 96a4ebb8 Klaus Aehlig
    let fp = fpPermissions perms
678 96a4ebb8 Klaus Aehlig
    permtry <- if fileMode fstat == fp
679 96a4ebb8 Klaus Aehlig
      then return $ Right ()
680 96a4ebb8 Klaus Aehlig
      else try $ do
681 96a4ebb8 Klaus Aehlig
        logInfo $ "Changing permissions of " ++ fpath ++ " to "
682 96a4ebb8 Klaus Aehlig
                    ++ showOct fp ""
683 96a4ebb8 Klaus Aehlig
        setFileMode fpath fp
684 96a4ebb8 Klaus Aehlig
    let errors = E.lefts ([ownertry, grouptry, permtry] :: [Either IOError ()])
685 96a4ebb8 Klaus Aehlig
    if null errors
686 96a4ebb8 Klaus Aehlig
      then return $ Ok ()
687 96a4ebb8 Klaus Aehlig
      else return . Bad $ show errors
688 96a4ebb8 Klaus Aehlig
689 b3f95121 Klaus Aehlig
-- | Safely rename a file, creating the target directory, if needed.
690 0c09ecc2 Klaus Aehlig
safeRenameFile :: FilePermissions -> FilePath -> FilePath -> IO (Result ())
691 0c09ecc2 Klaus Aehlig
safeRenameFile perms from to = do
692 0c09ecc2 Klaus Aehlig
  directtry <- try $ renameFile from to
693 0c09ecc2 Klaus Aehlig
  case (directtry :: Either IOError ()) of
694 0c09ecc2 Klaus Aehlig
    Right () -> return $ Ok ()
695 0c09ecc2 Klaus Aehlig
    Left _ -> do
696 0c09ecc2 Klaus Aehlig
      result <- try $ do
697 0c09ecc2 Klaus Aehlig
        let dir = takeDirectory to
698 0c09ecc2 Klaus Aehlig
        createDirectoryIfMissing True dir
699 0c09ecc2 Klaus Aehlig
        _ <- ensurePermissions dir perms
700 0c09ecc2 Klaus Aehlig
        renameFile from to
701 0c09ecc2 Klaus Aehlig
      return $ either (Bad . show) Ok (result :: Either IOError ())