Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 129bde01

History | View | Annotate | Download (24.8 kB)

1
{-# LANGUAGE FlexibleContexts #-}
2

    
3
{-| Utility functions. -}
4

    
5
{-
6

    
7
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
8

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

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

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

    
24
-}
25

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

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

    
97
import Debug.Trace
98
import Network.Socket
99

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

    
111
-- * Debug functions
112

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

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

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

    
126
-- * Miscellaneous
127

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

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

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

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

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

    
157
-- * Mathematical functions
158

    
159
-- Simple and slow statistical functions, please replace with better
160
-- versions
161

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

    
176
-- *  Logical functions
177

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

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

    
191
-- * Parsing utility functions
192

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
335
{-| Sort a list of strings based on digit and non-digit groupings.
336

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

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

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

    
350
-}
351
niceSort :: [String] -> [String]
352
niceSort = niceSortKey id
353

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

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

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

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

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

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

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

    
399
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
400
Nothing
401

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

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

    
408
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
409
Just \"\"
410

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

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

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

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

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

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

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

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

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

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

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

    
536
-- | Resets permissions so that the owner can read/write and the group only
537
-- read. All other permissions are cleared.
538
setOwnerWGroupR :: FilePath -> IO ()
539
setOwnerWGroupR path = setFileMode path mode
540
  where mode = foldl unionFileModes nullFileMode
541
                     [ownerReadMode, ownerWriteMode, groupReadMode]
542

    
543
-- | Formats an integral number, appending a suffix.
544
formatOrdinal :: (Integral a, Show a) => a -> String
545
formatOrdinal num
546
  | num > 10 && num < 20 = suffix "th"
547
  | tens == 1            = suffix "st"
548
  | tens == 2            = suffix "nd"
549
  | tens == 3            = suffix "rd"
550
  | otherwise            = suffix "th"
551
  where tens     = num `mod` 10
552
        suffix s = show num ++ s
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 ())