Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 0c09ecc2

History | View | Annotate | Download (24.9 kB)

1
{-| Utility functions. -}
2

    
3
{-
4

    
5
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
6

    
7
This program is free software; you can redistribute it and/or modify
8
it under the terms of the GNU General Public License as published by
9
the Free Software Foundation; either version 2 of the License, or
10
(at your option) any later version.
11

    
12
This program is distributed in the hope that it will be useful, but
13
WITHOUT ANY WARRANTY; without even the implied warranty of
14
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15
General Public License for more details.
16

    
17
You should have received a copy of the GNU General Public License
18
along with this program; if not, write to the Free Software
19
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
20
02110-1301, USA.
21

    
22
-}
23

    
24
module Ganeti.Utils
25
  ( debug
26
  , debugFn
27
  , debugXy
28
  , sepSplit
29
  , stdDev
30
  , if'
31
  , select
32
  , applyIf
33
  , commaJoin
34
  , ensureQuoted
35
  , tryRead
36
  , formatTable
37
  , printTable
38
  , parseUnit
39
  , parseUnitAssumeBinary
40
  , plural
41
  , niceSort
42
  , niceSortKey
43
  , exitIfBad
44
  , exitErr
45
  , exitWhen
46
  , exitUnless
47
  , logWarningIfBad
48
  , rStripSpace
49
  , newUUID
50
  , getCurrentTime
51
  , getCurrentTimeUSec
52
  , clockTimeToString
53
  , chompPrefix
54
  , warn
55
  , wrap
56
  , trim
57
  , defaultHead
58
  , exitIfEmpty
59
  , splitEithers
60
  , recombineEithers
61
  , resolveAddr
62
  , monadicThe
63
  , setOwnerAndGroupFromNames
64
  , formatOrdinal
65
  , atomicWriteFile
66
  , tryAndLogIOError
67
  , lockFile
68
  , FStat
69
  , nullFStat
70
  , getFStat
71
  , getFStatSafe
72
  , needsReload
73
  , watchFile
74
  , safeRenameFile
75
  , FilePermissions(..)
76
  , ensurePermissions
77
  ) where
78

    
79
import Control.Concurrent
80
import Control.Exception (try)
81
import Control.Monad (foldM, liftM, when, unless)
82
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
83
import qualified Data.Either as E
84
import Data.Function (on)
85
import Data.IORef
86
import Data.List
87
import qualified Data.Map as M
88
import Numeric (showOct)
89
import System.Directory (renameFile, createDirectoryIfMissing)
90
import System.FilePath.Posix (takeDirectory, takeBaseName)
91
import System.INotify
92
import System.Posix.Types
93

    
94
import Debug.Trace
95
import Network.Socket
96

    
97
import Ganeti.BasicTypes
98
import qualified Ganeti.ConstantUtils as ConstantUtils
99
import Ganeti.Logging
100
import Ganeti.Runtime
101
import System.IO
102
import System.Exit
103
import System.Posix.Files
104
import System.Posix.IO
105
import System.Posix.User
106
import System.Time
107

    
108
-- * Debug functions
109

    
110
-- | To be used only for debugging, breaks referential integrity.
111
debug :: Show a => a -> a
112
debug x = trace (show x) x
113

    
114
-- | Displays a modified form of the second parameter before returning
115
-- it.
116
debugFn :: Show b => (a -> b) -> a -> a
117
debugFn fn x = debug (fn x) `seq` x
118

    
119
-- | Show the first parameter before returning the second one.
120
debugXy :: Show a => a -> b -> b
121
debugXy = seq . debug
122

    
123
-- * Miscellaneous
124

    
125
-- | Apply the function if condition holds, otherwise use default value.
126
applyIf :: Bool -> (a -> a) -> a -> a
127
applyIf b f x = if b then f x else x
128

    
129
-- | Comma-join a string list.
130
commaJoin :: [String] -> String
131
commaJoin = intercalate ","
132

    
133
-- | Split a list on a separator and return an array.
134
sepSplit :: Eq a => a -> [a] -> [[a]]
135
sepSplit sep s
136
  | null s    = []
137
  | null xs   = [x]
138
  | null ys   = [x,[]]
139
  | otherwise = x:sepSplit sep ys
140
  where (x, xs) = break (== sep) s
141
        ys = drop 1 xs
142

    
143
-- | Simple pluralize helper
144
plural :: Int -> String -> String -> String
145
plural 1 s _ = s
146
plural _ _ p = p
147

    
148
-- | Ensure a value is quoted if needed.
149
ensureQuoted :: String -> String
150
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
151
                 then '\'':v ++ "'"
152
                 else v
153

    
154
-- * Mathematical functions
155

    
156
-- Simple and slow statistical functions, please replace with better
157
-- versions
158

    
159
-- | Standard deviation function.
160
stdDev :: [Double] -> Double
161
stdDev lst =
162
  -- first, calculate the list length and sum lst in a single step,
163
  -- for performance reasons
164
  let (ll', sx) = foldl' (\(rl, rs) e ->
165
                           let rl' = rl + 1
166
                               rs' = rs + e
167
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
168
      ll = fromIntegral ll'::Double
169
      mv = sx / ll
170
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
171
  in sqrt (av / ll) -- stddev
172

    
173
-- *  Logical functions
174

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

    
180
-- | \"if\" as a function, rather than as syntactic sugar.
181
if' :: Bool -- ^ condition
182
    -> a    -- ^ \"then\" result
183
    -> a    -- ^ \"else\" result
184
    -> a    -- ^ \"then\" or "else" result depending on the condition
185
if' True x _ = x
186
if' _    _ y = y
187

    
188
-- * Parsing utility functions
189

    
190
-- | Parse results from readsPrec.
191
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
192
parseChoices _ _ ((v, ""):[]) = return v
193
parseChoices name s ((_, e):[]) =
194
    fail $ name ++ ": leftover characters when parsing '"
195
           ++ s ++ "': '" ++ e ++ "'"
196
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
197

    
198
-- | Safe 'read' function returning data encapsulated in a Result.
199
tryRead :: (Monad m, Read a) => String -> String -> m a
200
tryRead name s = parseChoices name s $ reads s
201

    
202
-- | Format a table of strings to maintain consistent length.
203
formatTable :: [[String]] -> [Bool] -> [[String]]
204
formatTable vals numpos =
205
    let vtrans = transpose vals  -- transpose, so that we work on rows
206
                                 -- rather than columns
207
        mlens = map (maximum . map length) vtrans
208
        expnd = map (\(flds, isnum, ml) ->
209
                         map (\val ->
210
                                  let delta = ml - length val
211
                                      filler = replicate delta ' '
212
                                  in if delta > 0
213
                                     then if isnum
214
                                          then filler ++ val
215
                                          else val ++ filler
216
                                     else val
217
                             ) flds
218
                    ) (zip3 vtrans numpos mlens)
219
   in transpose expnd
220

    
221
-- | Constructs a printable table from given header and rows
222
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
223
printTable lp header rows isnum =
224
  unlines . map ((++) lp . (:) ' ' . unwords) $
225
  formatTable (header:rows) isnum
226

    
227
-- | Converts a unit (e.g. m or GB) into a scaling factor.
228
parseUnitValue :: (Monad m) => Bool -> String -> m Rational
229
parseUnitValue noDecimal unit
230
  -- binary conversions first
231
  | null unit                     = return 1
232
  | unit == "m" || upper == "MIB" = return 1
233
  | unit == "g" || upper == "GIB" = return kbBinary
234
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
235
  -- SI conversions
236
  | unit == "M" || upper == "MB"  = return mbFactor
237
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
238
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
239
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
240
  where upper = map toUpper unit
241
        kbBinary = 1024 :: Rational
242
        kbDecimal = if noDecimal then kbBinary else 1000
243
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
244
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
245

    
246
-- | Tries to extract number and scale from the given string.
247
--
248
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
249
-- specified, it defaults to MiB. Return value is always an integral
250
-- value in MiB; if the first argument is True, all kilos are binary.
251
parseUnitEx :: (Monad m, Integral a, Read a) => Bool -> String -> m a
252
parseUnitEx noDecimal str =
253
  -- TODO: enhance this by splitting the unit parsing code out and
254
  -- accepting floating-point numbers
255
  case (reads str::[(Int, String)]) of
256
    [(v, suffix)] ->
257
      let unit = dropWhile (== ' ') suffix
258
      in do
259
        scaling <- parseUnitValue noDecimal unit
260
        return $ truncate (fromIntegral v * scaling)
261
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
262

    
263
-- | Tries to extract number and scale from the given string.
264
--
265
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
266
-- specified, it defaults to MiB. Return value is always an integral
267
-- value in MiB.
268
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
269
parseUnit = parseUnitEx False
270

    
271
-- | Tries to extract a number and scale from a given string, taking
272
-- all kilos to be binary.
273
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
274
parseUnitAssumeBinary = parseUnitEx True
275

    
276
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
277
-- otherwise returning the actual contained value.
278
exitIfBad :: String -> Result a -> IO a
279
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
280
exitIfBad _ (Ok v) = return v
281

    
282
-- | Exits immediately with an error message.
283
exitErr :: String -> IO a
284
exitErr errmsg = do
285
  hPutStrLn stderr $ "Error: " ++ errmsg
286
  exitWith (ExitFailure 1)
287

    
288
-- | Exits with an error message if the given boolean condition if true.
289
exitWhen :: Bool -> String -> IO ()
290
exitWhen True msg = exitErr msg
291
exitWhen False _  = return ()
292

    
293
-- | Exits with an error message /unless/ the given boolean condition
294
-- if true, the opposite of 'exitWhen'.
295
exitUnless :: Bool -> String -> IO ()
296
exitUnless cond = exitWhen (not cond)
297

    
298
-- | Unwraps a 'Result', logging a warning message and then returning a default
299
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
300
logWarningIfBad :: String -> a -> Result a -> IO a
301
logWarningIfBad msg defVal (Bad s) = do
302
  logWarning $ msg ++ ": " ++ s
303
  return defVal
304
logWarningIfBad _ _ (Ok v) = return v
305

    
306
-- | Try an IO interaction, log errors and unfold as a 'Result'.
307
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b)
308
tryAndLogIOError io msg okfn =
309
 try io >>= either
310
   (\ e -> do
311
       let combinedmsg = msg ++ ": " ++ show (e :: IOError)
312
       logError combinedmsg
313
       return . Bad $ combinedmsg)
314
   (return . okfn)
315

    
316
-- | Print a warning, but do not exit.
317
warn :: String -> IO ()
318
warn = hPutStrLn stderr . (++) "Warning: "
319

    
320
-- | Helper for 'niceSort'. Computes the key element for a given string.
321
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
322
           -> String                   -- ^ Remaining string
323
           -> ([Either Integer String], String)
324
extractKey ek [] = (reverse ek, [])
325
extractKey ek xs@(x:_) =
326
  let (span_fn, conv_fn) = if isDigit x
327
                             then (isDigit, Left . read)
328
                             else (not . isDigit, Right)
329
      (k, rest) = span span_fn xs
330
  in extractKey (conv_fn k:ek) rest
331

    
332
{-| Sort a list of strings based on digit and non-digit groupings.
333

    
334
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
335
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
336

    
337
The sort algorithm breaks each name in groups of either only-digits or
338
no-digits, and sorts based on each group.
339

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

    
347
-}
348
niceSort :: [String] -> [String]
349
niceSort = niceSortKey id
350

    
351
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
352
-- since we don't want to add an ordering constraint on the /a/ type,
353
-- hence the need to only compare the first element of the /(key, a)/
354
-- tuple.
355
niceSortKey :: (a -> String) -> [a] -> [a]
356
niceSortKey keyfn =
357
  map snd . sortBy (compare `on` fst) .
358
  map (\s -> (fst . extractKey [] $ keyfn s, s))
359

    
360
-- | Strip space characthers (including newline). As this is
361
-- expensive, should only be run on small strings.
362
rStripSpace :: String -> String
363
rStripSpace = reverse . dropWhile isSpace . reverse
364

    
365
-- | Returns a random UUID.
366
-- This is a Linux-specific method as it uses the /proc filesystem.
367
newUUID :: IO String
368
newUUID = do
369
  contents <- readFile ConstantUtils.randomUuidFile
370
  return $! rStripSpace $ take 128 contents
371

    
372
-- | Returns the current time as an 'Integer' representing the number
373
-- of seconds from the Unix epoch.
374
getCurrentTime :: IO Integer
375
getCurrentTime = do
376
  TOD ctime _ <- getClockTime
377
  return ctime
378

    
379
-- | Returns the current time as an 'Integer' representing the number
380
-- of microseconds from the Unix epoch (hence the need for 'Integer').
381
getCurrentTimeUSec :: IO Integer
382
getCurrentTimeUSec = do
383
  TOD ctime pico <- getClockTime
384
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
385
  -- picoseconds right
386
  return $ ctime * 1000000 + pico `div` 1000000
387

    
388
-- | Convert a ClockTime into a (seconds-only) timestamp.
389
clockTimeToString :: ClockTime -> String
390
clockTimeToString (TOD t _) = show t
391

    
392
{-| Strip a prefix from a string, allowing the last character of the prefix
393
(which is assumed to be a separator) to be absent from the string if the string
394
terminates there.
395

    
396
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
397
Nothing
398

    
399
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
400
Just \"baz\"
401

    
402
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
403
Just \"\"
404

    
405
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
406
Just \"\"
407

    
408
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
409
Nothing
410
-}
411
chompPrefix :: String -> String -> Maybe String
412
chompPrefix pfx str =
413
  if pfx `isPrefixOf` str || str == init pfx
414
    then Just $ drop (length pfx) str
415
    else Nothing
416

    
417
-- | Breaks a string in lines with length \<= maxWidth.
418
--
419
-- NOTE: The split is OK if:
420
--
421
-- * It doesn't break a word, i.e. the next line begins with space
422
--   (@isSpace . head $ rest@) or the current line ends with space
423
--   (@null revExtra@);
424
--
425
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
426
wrap :: Int      -- ^ maxWidth
427
     -> String   -- ^ string that needs wrapping
428
     -> [String] -- ^ string \"broken\" in lines
429
wrap maxWidth = filter (not . null) . map trim . wrap0
430
  where wrap0 :: String -> [String]
431
        wrap0 text
432
          | length text <= maxWidth = [text]
433
          | isSplitOK               = line : wrap0 rest
434
          | otherwise               = line' : wrap0 rest'
435
          where (line, rest) = splitAt maxWidth text
436
                (revExtra, revLine) = break isSpace . reverse $ line
437
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
438
                isSplitOK =
439
                  null revLine || null revExtra || startsWithSpace rest
440
                startsWithSpace (x:_) = isSpace x
441
                startsWithSpace _     = False
442

    
443
-- | Removes surrounding whitespace. Should only be used in small
444
-- strings.
445
trim :: String -> String
446
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
447

    
448
-- | A safer head version, with a default value.
449
defaultHead :: a -> [a] -> a
450
defaultHead def []    = def
451
defaultHead _   (x:_) = x
452

    
453
-- | A 'head' version in the I/O monad, for validating parameters
454
-- without which we cannot continue.
455
exitIfEmpty :: String -> [a] -> IO a
456
exitIfEmpty _ (x:_) = return x
457
exitIfEmpty s []    = exitErr s
458

    
459
-- | Obtain the unique element of a list in an arbitrary monad.
460
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
461
monadicThe s [] = fail s
462
monadicThe s (x:xs)
463
  | all (x ==) xs = return x
464
  | otherwise = fail s
465

    
466
-- | Split an 'Either' list into two separate lists (containing the
467
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows
468
-- recombination later.
469
--
470
-- This is splitter; for recombination, look at 'recombineEithers'.
471
-- The sum of \"left\" and \"right\" lists should be equal to the
472
-- original list length, and the trail list should be the same length
473
-- as well. The entries in the resulting lists are reversed in
474
-- comparison with the original list.
475
splitEithers :: [Either a b] -> ([a], [b], [Bool])
476
splitEithers = foldl' splitter ([], [], [])
477
  where splitter (l, r, t) e =
478
          case e of
479
            Left  v -> (v:l, r, False:t)
480
            Right v -> (l, v:r, True:t)
481

    
482
-- | Recombines two \"left\" and \"right\" lists using a \"trail\"
483
-- list into a single 'Either' list.
484
--
485
-- This is the counterpart to 'splitEithers'. It does the opposite
486
-- transformation, and the output list will be the reverse of the
487
-- input lists. Since 'splitEithers' also reverses the lists, calling
488
-- these together will result in the original list.
489
--
490
-- Mismatches in the structure of the lists (e.g. inconsistent
491
-- lengths) are represented via 'Bad'; normally this function should
492
-- not fail, if lists are passed as generated by 'splitEithers'.
493
recombineEithers :: (Show a, Show b) =>
494
                    [a] -> [b] -> [Bool] -> Result [Either a b]
495
recombineEithers lefts rights trail =
496
  foldM recombiner ([], lefts, rights) trail >>= checker
497
    where checker (eithers, [], []) = Ok eithers
498
          checker (_, lefts', rights') =
499
            Bad $ "Inconsistent results after recombination, l'=" ++
500
                show lefts' ++ ", r'=" ++ show rights'
501
          recombiner (es, l:ls, rs) False = Ok (Left l:es,  ls, rs)
502
          recombiner (es, ls, r:rs) True  = Ok (Right r:es, ls, rs)
503
          recombiner (_,  ls, rs) t = Bad $ "Inconsistent trail log: l=" ++
504
                                      show ls ++ ", r=" ++ show rs ++ ",t=" ++
505
                                      show t
506

    
507
-- | Default hints for the resolver
508
resolveAddrHints :: Maybe AddrInfo
509
resolveAddrHints =
510
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
511

    
512
-- | Resolves a numeric address.
513
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
514
resolveAddr port str = do
515
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
516
  return $ case resolved of
517
             [] -> Bad "Invalid results from lookup?"
518
             best:_ -> Ok (addrFamily best, addrAddress best)
519

    
520
-- | Set the owner and the group of a file (given as names, not numeric id).
521
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO ()
522
setOwnerAndGroupFromNames filename daemon dGroup = do
523
  -- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts
524
  -- is read only once per daemon startup, and then cached for further usage.
525
  runtimeEnts <- getEnts
526
  ents <- exitIfBad "Can't find required user/groups" runtimeEnts
527
  -- note: we use directly ! as lookup failures shouldn't happen, due
528
  -- to the map construction
529
  let uid = fst ents M.! daemon
530
  let gid = snd ents M.! dGroup
531
  setOwnerAndGroup filename uid gid
532

    
533
-- | Formats an integral number, appending a suffix.
534
formatOrdinal :: (Integral a, Show a) => a -> String
535
formatOrdinal num
536
  | num > 10 && num < 20 = suffix "th"
537
  | tens == 1            = suffix "st"
538
  | tens == 2            = suffix "nd"
539
  | tens == 3            = suffix "rd"
540
  | otherwise            = suffix "th"
541
  where tens     = num `mod` 10
542
        suffix s = show num ++ s
543

    
544
-- | Atomically write a file, by first writing the contents into a temporary
545
-- file and then renaming it to the old position.
546
atomicWriteFile :: FilePath -> String -> IO ()
547
atomicWriteFile path contents = do
548
  (tmppath, tmphandle) <- openTempFile (takeDirectory path) (takeBaseName path)
549
  hPutStr tmphandle contents
550
  hClose tmphandle
551
  renameFile tmppath path
552

    
553
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
554
-- back success.
555
lockFile :: FilePath -> IO (Result ())
556
lockFile path = do
557
  handle <- openFile path WriteMode
558
  fd <- handleToFd handle
559
  Control.Monad.liftM (either (Bad . show) Ok)
560
    (try (setLock fd (WriteLock, AbsoluteSeek, 0, 0)) :: IO (Either IOError ()))
561

    
562
-- | File stat identifier.
563
type FStat = (EpochTime, FileID, FileOffset)
564

    
565
-- | Null 'FStat' value.
566
nullFStat :: FStat
567
nullFStat = (-1, -1, -1)
568

    
569
-- | Computes the file cache data from a FileStatus structure.
570
buildFileStatus :: FileStatus -> FStat
571
buildFileStatus ofs =
572
    let modt = modificationTime ofs
573
        inum = fileID ofs
574
        fsize = fileSize ofs
575
    in (modt, inum, fsize)
576

    
577
-- | Wrapper over 'buildFileStatus'. This reads the data from the
578
-- filesystem and then builds our cache structure.
579
getFStat :: FilePath -> IO FStat
580
getFStat p = liftM buildFileStatus (getFileStatus p)
581

    
582
-- | Safe version of 'getFStat', that ignores IOErrors.
583
getFStatSafe :: FilePath -> IO FStat
584
getFStatSafe fpath = liftM (either (const nullFStat) id)
585
                       ((try $ getFStat fpath) :: IO (Either IOError FStat))
586

    
587
-- | Check if the file needs reloading
588
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
589
needsReload oldstat path = do
590
  newstat <- getFStat path
591
  return $ if newstat /= oldstat
592
             then Just newstat
593
             else Nothing
594

    
595
-- | Until the given point in time (useconds since the epoch), wait
596
-- for the output of a given method to change and return the new value;
597
-- make use of the promise that the output only changes if the reference
598
-- has a value different than the given one.
599
watchFileEx :: (Eq a, Eq b) => Integer -> b -> IORef b -> a -> IO a -> IO a
600
watchFileEx endtime base ref old read_fn = do
601
  current <- getCurrentTimeUSec
602
  if current > endtime then read_fn else do
603
    val <- readIORef ref
604
    if val /= base
605
      then do
606
        new <- read_fn
607
        if new /= old then return new else do
608
          logDebug "Observed change not relevant"
609
          threadDelay 100000
610
          watchFileEx endtime val ref old read_fn
611
      else do 
612
       threadDelay 100000
613
       watchFileEx endtime base ref old read_fn
614

    
615
-- | Within the given timeout (in seconds), wait for for the output
616
-- of the given method to change and return the new value; make use of
617
-- the promise that the method will only change its value, if
618
-- the given file changes on disk. If the file does not exist on disk, return
619
-- immediately.
620
watchFile :: Eq a => FilePath -> Int -> a -> IO a -> IO a
621
watchFile fpath timeout old read_fn = do
622
  current <- getCurrentTimeUSec
623
  let endtime = current + fromIntegral timeout * 1000000
624
  fstat <- getFStatSafe fpath
625
  ref <- newIORef fstat
626
  inotify <- initINotify
627
  let do_watch e = do
628
                     logDebug $ "Notified of change in " ++ fpath 
629
                                  ++ "; event: " ++ show e
630
                     when (e == Ignored)
631
                       (addWatch inotify [Modify, Delete] fpath do_watch
632
                          >> return ())
633
                     fstat' <- getFStatSafe fpath
634
                     writeIORef ref fstat'
635
  _ <- addWatch inotify [Modify, Delete] fpath do_watch
636
  newval <- read_fn
637
  if newval /= old
638
    then do
639
      logDebug $ "File " ++ fpath ++ " changed during setup of inotify"
640
      killINotify inotify
641
      return newval
642
    else do
643
      result <- watchFileEx endtime fstat ref old read_fn
644
      killINotify inotify
645
      return result
646

    
647
-- | Type describing ownership and permissions of newly generated
648
-- directories and files. All parameters are optional, with nothing
649
-- meaning that the default value should be left untouched.
650

    
651
data FilePermissions = FilePermissions { fpOwner :: Maybe String
652
                                       , fpGroup :: Maybe String
653
                                       , fpPermissions :: FileMode
654
                                       }
655

    
656
-- | Ensure that a given file or directory has the permissions, and
657
-- possibly ownerships, as required.
658
ensurePermissions :: FilePath -> FilePermissions -> IO (Result ())
659
ensurePermissions fpath perms = do
660
  eitherFileStatus <- try $ getFileStatus fpath
661
                      :: IO (Either IOError FileStatus)
662
  (flip $ either (return . Bad . show)) eitherFileStatus $ \fstat -> do
663
    ownertry <- case fpOwner perms of
664
      Nothing -> return $ Right ()
665
      Just owner -> try $ do
666
        ownerid <- userID `liftM` getUserEntryForName owner
667
        unless (ownerid == fileOwner fstat) $ do
668
          logDebug $ "Changing owner of " ++ fpath ++ " to " ++ owner
669
          setOwnerAndGroup fpath ownerid (-1)
670
    grouptry <- case fpGroup perms of
671
      Nothing -> return $ Right ()
672
      Just grp -> try $ do
673
        groupid <- groupID `liftM` getGroupEntryForName grp
674
        unless (groupid == fileGroup fstat) $ do
675
          logDebug $ "Changing group of " ++ fpath ++ " to " ++ grp
676
          setOwnerAndGroup fpath (-1) groupid
677
    let fp = fpPermissions perms
678
    permtry <- if fileMode fstat == fp
679
      then return $ Right ()
680
      else try $ do
681
        logInfo $ "Changing permissions of " ++ fpath ++ " to "
682
                    ++ showOct fp ""
683
        setFileMode fpath fp
684
    let errors = E.lefts ([ownertry, grouptry, permtry] :: [Either IOError ()])
685
    if null errors
686
      then return $ Ok ()
687
      else return . Bad $ show errors
688

    
689
-- | Safely rename a file, creating the target directory, if needed.
690
safeRenameFile :: FilePermissions -> FilePath -> FilePath -> IO (Result ())
691
safeRenameFile perms from to = do
692
  directtry <- try $ renameFile from to
693
  case (directtry :: Either IOError ()) of
694
    Right () -> return $ Ok ()
695
    Left _ -> do
696
      result <- try $ do
697
        let dir = takeDirectory to
698
        createDirectoryIfMissing True dir
699
        _ <- ensurePermissions dir perms
700
        renameFile from to
701
      return $ either (Bad . show) Ok (result :: Either IOError ())