Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ b3f95121

History | View | Annotate | Download (22.7 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
  ) where
76

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

    
90
import Debug.Trace
91
import Network.Socket
92

    
93
import Ganeti.BasicTypes
94
import qualified Ganeti.ConstantUtils as ConstantUtils
95
import Ganeti.Logging
96
import Ganeti.Runtime
97
import System.IO
98
import System.Exit
99
import System.Posix.Files
100
import System.Posix.IO
101
import System.Time
102

    
103
-- * Debug functions
104

    
105
-- | To be used only for debugging, breaks referential integrity.
106
debug :: Show a => a -> a
107
debug x = trace (show x) x
108

    
109
-- | Displays a modified form of the second parameter before returning
110
-- it.
111
debugFn :: Show b => (a -> b) -> a -> a
112
debugFn fn x = debug (fn x) `seq` x
113

    
114
-- | Show the first parameter before returning the second one.
115
debugXy :: Show a => a -> b -> b
116
debugXy = seq . debug
117

    
118
-- * Miscellaneous
119

    
120
-- | Apply the function if condition holds, otherwise use default value.
121
applyIf :: Bool -> (a -> a) -> a -> a
122
applyIf b f x = if b then f x else x
123

    
124
-- | Comma-join a string list.
125
commaJoin :: [String] -> String
126
commaJoin = intercalate ","
127

    
128
-- | Split a list on a separator and return an array.
129
sepSplit :: Eq a => a -> [a] -> [[a]]
130
sepSplit sep s
131
  | null s    = []
132
  | null xs   = [x]
133
  | null ys   = [x,[]]
134
  | otherwise = x:sepSplit sep ys
135
  where (x, xs) = break (== sep) s
136
        ys = drop 1 xs
137

    
138
-- | Simple pluralize helper
139
plural :: Int -> String -> String -> String
140
plural 1 s _ = s
141
plural _ _ p = p
142

    
143
-- | Ensure a value is quoted if needed.
144
ensureQuoted :: String -> String
145
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
146
                 then '\'':v ++ "'"
147
                 else v
148

    
149
-- * Mathematical functions
150

    
151
-- Simple and slow statistical functions, please replace with better
152
-- versions
153

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

    
168
-- *  Logical functions
169

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

    
175
-- | \"if\" as a function, rather than as syntactic sugar.
176
if' :: Bool -- ^ condition
177
    -> a    -- ^ \"then\" result
178
    -> a    -- ^ \"else\" result
179
    -> a    -- ^ \"then\" or "else" result depending on the condition
180
if' True x _ = x
181
if' _    _ y = y
182

    
183
-- * Parsing utility functions
184

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

    
193
-- | Safe 'read' function returning data encapsulated in a Result.
194
tryRead :: (Monad m, Read a) => String -> String -> m a
195
tryRead name s = parseChoices name s $ reads s
196

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

    
216
-- | Constructs a printable table from given header and rows
217
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
218
printTable lp header rows isnum =
219
  unlines . map ((++) lp . (:) ' ' . unwords) $
220
  formatTable (header:rows) isnum
221

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

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

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

    
266
-- | Tries to extract a number and scale from a given string, taking
267
-- all kilos to be binary.
268
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
269
parseUnitAssumeBinary = parseUnitEx True
270

    
271
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
272
-- otherwise returning the actual contained value.
273
exitIfBad :: String -> Result a -> IO a
274
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
275
exitIfBad _ (Ok v) = return v
276

    
277
-- | Exits immediately with an error message.
278
exitErr :: String -> IO a
279
exitErr errmsg = do
280
  hPutStrLn stderr $ "Error: " ++ errmsg
281
  exitWith (ExitFailure 1)
282

    
283
-- | Exits with an error message if the given boolean condition if true.
284
exitWhen :: Bool -> String -> IO ()
285
exitWhen True msg = exitErr msg
286
exitWhen False _  = return ()
287

    
288
-- | Exits with an error message /unless/ the given boolean condition
289
-- if true, the opposite of 'exitWhen'.
290
exitUnless :: Bool -> String -> IO ()
291
exitUnless cond = exitWhen (not cond)
292

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

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

    
311
-- | Print a warning, but do not exit.
312
warn :: String -> IO ()
313
warn = hPutStrLn stderr . (++) "Warning: "
314

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

    
327
{-| Sort a list of strings based on digit and non-digit groupings.
328

    
329
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
330
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
331

    
332
The sort algorithm breaks each name in groups of either only-digits or
333
no-digits, and sorts based on each group.
334

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

    
342
-}
343
niceSort :: [String] -> [String]
344
niceSort = niceSortKey id
345

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

    
355
-- | Strip space characthers (including newline). As this is
356
-- expensive, should only be run on small strings.
357
rStripSpace :: String -> String
358
rStripSpace = reverse . dropWhile isSpace . reverse
359

    
360
-- | Returns a random UUID.
361
-- This is a Linux-specific method as it uses the /proc filesystem.
362
newUUID :: IO String
363
newUUID = do
364
  contents <- readFile ConstantUtils.randomUuidFile
365
  return $! rStripSpace $ take 128 contents
366

    
367
-- | Returns the current time as an 'Integer' representing the number
368
-- of seconds from the Unix epoch.
369
getCurrentTime :: IO Integer
370
getCurrentTime = do
371
  TOD ctime _ <- getClockTime
372
  return ctime
373

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

    
383
-- | Convert a ClockTime into a (seconds-only) timestamp.
384
clockTimeToString :: ClockTime -> String
385
clockTimeToString (TOD t _) = show t
386

    
387
{-| Strip a prefix from a string, allowing the last character of the prefix
388
(which is assumed to be a separator) to be absent from the string if the string
389
terminates there.
390

    
391
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
392
Nothing
393

    
394
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
395
Just \"baz\"
396

    
397
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
398
Just \"\"
399

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

    
403
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
404
Nothing
405
-}
406
chompPrefix :: String -> String -> Maybe String
407
chompPrefix pfx str =
408
  if pfx `isPrefixOf` str || str == init pfx
409
    then Just $ drop (length pfx) str
410
    else Nothing
411

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

    
438
-- | Removes surrounding whitespace. Should only be used in small
439
-- strings.
440
trim :: String -> String
441
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
442

    
443
-- | A safer head version, with a default value.
444
defaultHead :: a -> [a] -> a
445
defaultHead def []    = def
446
defaultHead _   (x:_) = x
447

    
448
-- | A 'head' version in the I/O monad, for validating parameters
449
-- without which we cannot continue.
450
exitIfEmpty :: String -> [a] -> IO a
451
exitIfEmpty _ (x:_) = return x
452
exitIfEmpty s []    = exitErr s
453

    
454
-- | Obtain the unique element of a list in an arbitrary monad.
455
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
456
monadicThe s [] = fail s
457
monadicThe s (x:xs)
458
  | all (x ==) xs = return x
459
  | otherwise = fail s
460

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

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

    
502
-- | Default hints for the resolver
503
resolveAddrHints :: Maybe AddrInfo
504
resolveAddrHints =
505
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
506

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

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

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

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

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

    
557
-- | File stat identifier.
558
type FStat = (EpochTime, FileID, FileOffset)
559

    
560
-- | Null 'FStat' value.
561
nullFStat :: FStat
562
nullFStat = (-1, -1, -1)
563

    
564
-- | Computes the file cache data from a FileStatus structure.
565
buildFileStatus :: FileStatus -> FStat
566
buildFileStatus ofs =
567
    let modt = modificationTime ofs
568
        inum = fileID ofs
569
        fsize = fileSize ofs
570
    in (modt, inum, fsize)
571

    
572
-- | Wrapper over 'buildFileStatus'. This reads the data from the
573
-- filesystem and then builds our cache structure.
574
getFStat :: FilePath -> IO FStat
575
getFStat p = liftM buildFileStatus (getFileStatus p)
576

    
577
-- | Safe version of 'getFStat', that ignores IOErrors.
578
getFStatSafe :: FilePath -> IO FStat
579
getFStatSafe fpath = liftM (either (const nullFStat) id)
580
                       ((try $ getFStat fpath) :: IO (Either IOError FStat))
581

    
582
-- | Check if the file needs reloading
583
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
584
needsReload oldstat path = do
585
  newstat <- getFStat path
586
  return $ if newstat /= oldstat
587
             then Just newstat
588
             else Nothing
589

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

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