Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 69bf84e1

History | View | Annotate | Download (24.8 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 Control.Monad.IO.Class (liftIO)
83
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
84
import qualified Data.Either as E
85
import Data.Function (on)
86
import Data.IORef
87
import Data.List
88
import qualified Data.Map as M
89
import Numeric (showOct)
90
import System.Directory (renameFile, createDirectoryIfMissing)
91
import System.FilePath.Posix (takeDirectory, takeBaseName)
92
import System.INotify
93
import System.Posix.Types
94

    
95
import Debug.Trace
96
import Network.Socket
97

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

    
109
-- * Debug functions
110

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

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

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

    
124
-- * Miscellaneous
125

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

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

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

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

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

    
155
-- * Mathematical functions
156

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

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

    
174
-- *  Logical functions
175

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

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

    
189
-- * Parsing utility functions
190

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
554
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
555
-- back success.
556
lockFile :: FilePath -> IO (Result ())
557
lockFile path = runResultT . liftIO $ do
558
  handle <- openFile path WriteMode
559
  fd <- handleToFd handle
560
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
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 ())