Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ a2a1a8ca

History | View | Annotate | Download (28.1 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
  , atomicWriteFile
69
  , atomicUpdateFile
70
  , atomicUpdateLockedFile
71
  , atomicUpdateLockedFile_
72
  , tryAndLogIOError
73
  , lockFile
74
  , withLockedFile
75
  , FStat
76
  , nullFStat
77
  , getFStat
78
  , getFStatSafe
79
  , needsReload
80
  , watchFile
81
  , safeRenameFile
82
  , FilePermissions(..)
83
  , ensurePermissions
84
  ) where
85

    
86
import Control.Concurrent
87
import Control.Exception (try)
88
import qualified Control.Exception.Lifted as L
89
import Control.Monad
90
import Control.Monad.Base (MonadBase(..))
91
import Control.Monad.Error
92
import Control.Monad.Trans.Control
93
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
94
import qualified Data.Either as E
95
import Data.Function (on)
96
import Data.IORef
97
import Data.List
98
import qualified Data.Map as M
99
import Numeric (showOct)
100
import System.Directory (renameFile, createDirectoryIfMissing)
101
import System.FilePath.Posix (takeDirectory, takeBaseName)
102
import System.INotify
103
import System.Posix.Types
104

    
105
import Debug.Trace
106
import Network.Socket
107

    
108
import Ganeti.BasicTypes
109
import qualified Ganeti.ConstantUtils as ConstantUtils
110
import Ganeti.Logging
111
import Ganeti.Runtime
112
import System.IO
113
import System.Exit
114
import System.Posix.Files
115
import System.Posix.IO
116
import System.Posix.User
117
import System.Time
118

    
119
-- * Debug functions
120

    
121
-- | To be used only for debugging, breaks referential integrity.
122
debug :: Show a => a -> a
123
debug x = trace (show x) x
124

    
125
-- | Displays a modified form of the second parameter before returning
126
-- it.
127
debugFn :: Show b => (a -> b) -> a -> a
128
debugFn fn x = debug (fn x) `seq` x
129

    
130
-- | Show the first parameter before returning the second one.
131
debugXy :: Show a => a -> b -> b
132
debugXy = seq . debug
133

    
134
-- * Miscellaneous
135

    
136
-- | Apply the function if condition holds, otherwise use default value.
137
applyIf :: Bool -> (a -> a) -> a -> a
138
applyIf b f x = if b then f x else x
139

    
140
-- | Comma-join a string list.
141
commaJoin :: [String] -> String
142
commaJoin = intercalate ","
143

    
144
-- | Split a list on a separator and return an array.
145
sepSplit :: Eq a => a -> [a] -> [[a]]
146
sepSplit sep s
147
  | null s    = []
148
  | null xs   = [x]
149
  | null ys   = [x,[]]
150
  | otherwise = x:sepSplit sep ys
151
  where (x, xs) = break (== sep) s
152
        ys = drop 1 xs
153

    
154
-- | Simple pluralize helper
155
plural :: Int -> String -> String -> String
156
plural 1 s _ = s
157
plural _ _ p = p
158

    
159
-- | Ensure a value is quoted if needed.
160
ensureQuoted :: String -> String
161
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
162
                 then '\'':v ++ "'"
163
                 else v
164

    
165
-- * Mathematical functions
166

    
167
-- Simple and slow statistical functions, please replace with better
168
-- versions
169

    
170
-- | Standard deviation function.
171
stdDev :: [Double] -> Double
172
stdDev lst =
173
  -- first, calculate the list length and sum lst in a single step,
174
  -- for performance reasons
175
  let (ll', sx) = foldl' (\(rl, rs) e ->
176
                           let rl' = rl + 1
177
                               rs' = rs + e
178
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
179
      ll = fromIntegral ll'::Double
180
      mv = sx / ll
181
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
182
  in sqrt (av / ll) -- stddev
183

    
184
-- *  Logical functions
185

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

    
191
-- | \"if\" as a function, rather than as syntactic sugar.
192
if' :: Bool -- ^ condition
193
    -> a    -- ^ \"then\" result
194
    -> a    -- ^ \"else\" result
195
    -> a    -- ^ \"then\" or "else" result depending on the condition
196
if' True x _ = x
197
if' _    _ y = y
198

    
199
-- * Parsing utility functions
200

    
201
-- | Parse results from readsPrec.
202
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
203
parseChoices _ _ ((v, ""):[]) = return v
204
parseChoices name s ((_, e):[]) =
205
    fail $ name ++ ": leftover characters when parsing '"
206
           ++ s ++ "': '" ++ e ++ "'"
207
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
208

    
209
-- | Safe 'read' function returning data encapsulated in a Result.
210
tryRead :: (Monad m, Read a) => String -> String -> m a
211
tryRead name s = parseChoices name s $ reads s
212

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

    
232
-- | Constructs a printable table from given header and rows
233
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
234
printTable lp header rows isnum =
235
  unlines . map ((++) lp . (:) ' ' . unwords) $
236
  formatTable (header:rows) isnum
237

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

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

    
274
-- | Tries to extract number and scale from the given string.
275
--
276
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
277
-- specified, it defaults to MiB. Return value is always an integral
278
-- value in MiB.
279
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
280
parseUnit = parseUnitEx False
281

    
282
-- | Tries to extract a number and scale from a given string, taking
283
-- all kilos to be binary.
284
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
285
parseUnitAssumeBinary = parseUnitEx True
286

    
287
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
288
-- otherwise returning the actual contained value.
289
exitIfBad :: String -> Result a -> IO a
290
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
291
exitIfBad _ (Ok v) = return v
292

    
293
-- | Exits immediately with an error message.
294
exitErr :: String -> IO a
295
exitErr errmsg = do
296
  hPutStrLn stderr $ "Error: " ++ errmsg
297
  exitWith (ExitFailure 1)
298

    
299
-- | Exits with an error message if the given boolean condition if true.
300
exitWhen :: Bool -> String -> IO ()
301
exitWhen True msg = exitErr msg
302
exitWhen False _  = return ()
303

    
304
-- | Exits with an error message /unless/ the given boolean condition
305
-- if true, the opposite of 'exitWhen'.
306
exitUnless :: Bool -> String -> IO ()
307
exitUnless cond = exitWhen (not cond)
308

    
309
-- | Unwraps a 'Result', logging a warning message and then returning a default
310
-- value if it is a 'Bad' value, otherwise returning the actual contained value.
311
logWarningIfBad :: String -> a -> Result a -> IO a
312
logWarningIfBad msg defVal (Bad s) = do
313
  logWarning $ msg ++ ": " ++ s
314
  return defVal
315
logWarningIfBad _ _ (Ok v) = return v
316

    
317
-- | Try an IO interaction, log errors and unfold as a 'Result'.
318
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b)
319
tryAndLogIOError io msg okfn =
320
 try io >>= either
321
   (\ e -> do
322
       let combinedmsg = msg ++ ": " ++ show (e :: IOError)
323
       logError combinedmsg
324
       return . Bad $ combinedmsg)
325
   (return . okfn)
326

    
327
-- | Print a warning, but do not exit.
328
warn :: String -> IO ()
329
warn = hPutStrLn stderr . (++) "Warning: "
330

    
331
-- | Helper for 'niceSort'. Computes the key element for a given string.
332
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
333
           -> String                   -- ^ Remaining string
334
           -> ([Either Integer String], String)
335
extractKey ek [] = (reverse ek, [])
336
extractKey ek xs@(x:_) =
337
  let (span_fn, conv_fn) = if isDigit x
338
                             then (isDigit, Left . read)
339
                             else (not . isDigit, Right)
340
      (k, rest) = span span_fn xs
341
  in extractKey (conv_fn k:ek) rest
342

    
343
{-| Sort a list of strings based on digit and non-digit groupings.
344

    
345
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
346
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
347

    
348
The sort algorithm breaks each name in groups of either only-digits or
349
no-digits, and sorts based on each group.
350

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

    
358
-}
359
niceSort :: [String] -> [String]
360
niceSort = niceSortKey id
361

    
362
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
363
-- since we don't want to add an ordering constraint on the /a/ type,
364
-- hence the need to only compare the first element of the /(key, a)/
365
-- tuple.
366
niceSortKey :: (a -> String) -> [a] -> [a]
367
niceSortKey keyfn =
368
  map snd . sortBy (compare `on` fst) .
369
  map (\s -> (fst . extractKey [] $ keyfn s, s))
370

    
371
-- | Strip space characthers (including newline). As this is
372
-- expensive, should only be run on small strings.
373
rStripSpace :: String -> String
374
rStripSpace = reverse . dropWhile isSpace . reverse
375

    
376
-- | Returns a random UUID.
377
-- This is a Linux-specific method as it uses the /proc filesystem.
378
newUUID :: IO String
379
newUUID = do
380
  contents <- readFile ConstantUtils.randomUuidFile
381
  return $! rStripSpace $ take 128 contents
382

    
383
-- | Returns the current time as an 'Integer' representing the number
384
-- of seconds from the Unix epoch.
385
getCurrentTime :: IO Integer
386
getCurrentTime = do
387
  TOD ctime _ <- getClockTime
388
  return ctime
389

    
390
-- | Returns the current time as an 'Integer' representing the number
391
-- of microseconds from the Unix epoch (hence the need for 'Integer').
392
getCurrentTimeUSec :: IO Integer
393
getCurrentTimeUSec = do
394
  TOD ctime pico <- getClockTime
395
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
396
  -- picoseconds right
397
  return $ ctime * 1000000 + pico `div` 1000000
398

    
399
-- | Convert a ClockTime into a (seconds-only) timestamp.
400
clockTimeToString :: ClockTime -> String
401
clockTimeToString (TOD t _) = show t
402

    
403
{-| Strip a prefix from a string, allowing the last character of the prefix
404
(which is assumed to be a separator) to be absent from the string if the string
405
terminates there.
406

    
407
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
408
Nothing
409

    
410
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
411
Just \"baz\"
412

    
413
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
414
Just \"\"
415

    
416
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
417
Just \"\"
418

    
419
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
420
Nothing
421
-}
422
chompPrefix :: String -> String -> Maybe String
423
chompPrefix pfx str =
424
  if pfx `isPrefixOf` str || str == init pfx
425
    then Just $ drop (length pfx) str
426
    else Nothing
427

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

    
454
-- | Removes surrounding whitespace. Should only be used in small
455
-- strings.
456
trim :: String -> String
457
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
458

    
459
-- | A safer head version, with a default value.
460
defaultHead :: a -> [a] -> a
461
defaultHead def []    = def
462
defaultHead _   (x:_) = x
463

    
464
-- | A 'head' version in the I/O monad, for validating parameters
465
-- without which we cannot continue.
466
exitIfEmpty :: String -> [a] -> IO a
467
exitIfEmpty _ (x:_) = return x
468
exitIfEmpty s []    = exitErr s
469

    
470
-- | Obtain the unique element of a list in an arbitrary monad.
471
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
472
monadicThe s [] = fail s
473
monadicThe s (x:xs)
474
  | all (x ==) xs = return x
475
  | otherwise = fail s
476

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

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

    
518
-- | Default hints for the resolver
519
resolveAddrHints :: Maybe AddrInfo
520
resolveAddrHints =
521
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
522

    
523
-- | Resolves a numeric address.
524
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr))
525
resolveAddr port str = do
526
  resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port))
527
  return $ case resolved of
528
             [] -> Bad "Invalid results from lookup?"
529
             best:_ -> Ok (addrFamily best, addrAddress best)
530

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

    
544
-- | Resets permissions so that the owner can read/write and the group only
545
-- read. All other permissions are cleared.
546
setOwnerWGroupR :: FilePath -> IO ()
547
setOwnerWGroupR path = setFileMode path mode
548
  where mode = foldl unionFileModes nullFileMode
549
                     [ownerReadMode, ownerWriteMode, groupReadMode]
550

    
551
-- | Formats an integral number, appending a suffix.
552
formatOrdinal :: (Integral a, Show a) => a -> String
553
formatOrdinal num
554
  | num > 10 && num < 20 = suffix "th"
555
  | tens == 1            = suffix "st"
556
  | tens == 2            = suffix "nd"
557
  | tens == 3            = suffix "rd"
558
  | otherwise            = suffix "th"
559
  where tens     = num `mod` 10
560
        suffix s = show num ++ s
561

    
562
-- | Atomically write a file, by first writing the contents into a temporary
563
-- file and then renaming it to the old position.
564
atomicWriteFile :: FilePath -> String -> IO ()
565
atomicWriteFile path contents = atomicUpdateFile path
566
                                  (\_ fh -> hPutStr fh contents)
567

    
568
-- | Atomically update a file, by first creating a temporary file, running the
569
-- given action on it, and then renaming it to the old position.
570
-- Usually the action will write to the file and update its permissions.
571
-- The action is allowed to close the file descriptor, but isn't required to do
572
-- so.
573
atomicUpdateFile :: (MonadBaseControl IO m)
574
                 => FilePath -> (FilePath -> Handle -> m a) -> m a
575
atomicUpdateFile path action = do
576
  (tmppath, tmphandle) <- liftBase $ openTempFile (takeDirectory path)
577
                                                  (takeBaseName path)
578
  r <- L.finally (action tmppath tmphandle) (liftBase $ hClose tmphandle)
579
  -- if all went well, rename the file
580
  liftBase $ renameFile tmppath path
581
  return r
582

    
583
-- | Opens a file in a R/W mode, locks it (blocking if needed) and runs
584
-- a given action while the file is locked. Releases the lock and
585
-- closes the file afterwards.
586
withLockedFile :: (MonadError e m, Error e, MonadBaseControl IO m)
587
               => FilePath -> (Fd -> m a) -> m a
588
withLockedFile path =
589
    L.bracket (openAndLock path) (liftBase . closeFd)
590
  where
591
    openAndLock :: (MonadError e m, Error e, MonadBaseControl IO m)
592
                => FilePath -> m Fd
593
    openAndLock p = liftBase $ do
594
      fd <- openFd p ReadWrite Nothing defaultFileFlags
595
      waitToSetLock fd (WriteLock, AbsoluteSeek, 0, 0)
596
      return fd
597

    
598
-- | Just as 'atomicUpdateFile', but in addition locks the file during the
599
-- operation using 'withLockedFile' and checks if the file has been modified.
600
-- The action is only run if it hasn't, otherwise an error is thrown.
601
-- The file must exist.
602
-- Returns the new file status after the operation is finished.
603
atomicUpdateLockedFile :: FilePath
604
                       -> FStat
605
                       -> (FilePath -> Handle -> IO a)
606
                       -> ResultT IOError IO (FStat, a)
607
atomicUpdateLockedFile path fstat action =
608
    withLockedFile path checkStatAndRun
609
  where
610
    checkStatAndRun _ = do
611
      newstat <- liftIO $ getFStat path
612
      unless (fstat == newstat)
613
             (failError $ "Cannot overwrite file " ++ path ++
614
                          ": it has been modified since last written" ++
615
                          " (" ++ show fstat ++ " != " ++ show newstat ++ ")")
616
      liftIO $ atomicUpdateFile path actionAndStat
617
    actionAndStat tmppath tmphandle = do
618
      r <- action tmppath tmphandle
619
      hClose tmphandle -- close the handle so that we get meaningful stats
620
      finalstat <- liftIO $ getFStat tmppath
621
      return (finalstat, r)
622

    
623
-- | Just as 'atomicUpdateLockedFile', but discards the action result.
624
atomicUpdateLockedFile_ :: FilePath
625
                        -> FStat
626
                        -> (FilePath -> Handle -> IO a)
627
                        -> ResultT IOError IO FStat
628
atomicUpdateLockedFile_ path oldstat
629
  = liftM fst . atomicUpdateLockedFile path oldstat
630

    
631
-- | Attempt, in a non-blocking way, to obtain a lock on a given file; report
632
-- back success.
633
lockFile :: FilePath -> IO (Result ())
634
lockFile path = runResultT . liftIO $ do
635
  handle <- openFile path WriteMode
636
  fd <- handleToFd handle
637
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
638

    
639
-- | File stat identifier.
640
type FStat = (EpochTime, FileID, FileOffset)
641

    
642
-- | Null 'FStat' value.
643
nullFStat :: FStat
644
nullFStat = (-1, -1, -1)
645

    
646
-- | Computes the file cache data from a FileStatus structure.
647
buildFileStatus :: FileStatus -> FStat
648
buildFileStatus ofs =
649
    let modt = modificationTime ofs
650
        inum = fileID ofs
651
        fsize = fileSize ofs
652
    in (modt, inum, fsize)
653

    
654
-- | Wrapper over 'buildFileStatus'. This reads the data from the
655
-- filesystem and then builds our cache structure.
656
getFStat :: FilePath -> IO FStat
657
getFStat p = liftM buildFileStatus (getFileStatus p)
658

    
659
-- | Safe version of 'getFStat', that ignores IOErrors.
660
getFStatSafe :: FilePath -> IO FStat
661
getFStatSafe fpath = liftM (either (const nullFStat) id)
662
                       ((try $ getFStat fpath) :: IO (Either IOError FStat))
663

    
664
-- | Check if the file needs reloading
665
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
666
needsReload oldstat path = do
667
  newstat <- getFStat path
668
  return $ if newstat /= oldstat
669
             then Just newstat
670
             else Nothing
671

    
672
-- | Until the given point in time (useconds since the epoch), wait
673
-- for the output of a given method to change and return the new value;
674
-- make use of the promise that the output only changes if the reference
675
-- has a value different than the given one.
676
watchFileEx :: (Eq a, Eq b) => Integer -> b -> IORef b -> a -> IO a -> IO a
677
watchFileEx endtime base ref old read_fn = do
678
  current <- getCurrentTimeUSec
679
  if current > endtime then read_fn else do
680
    val <- readIORef ref
681
    if val /= base
682
      then do
683
        new <- read_fn
684
        if new /= old then return new else do
685
          logDebug "Observed change not relevant"
686
          threadDelay 100000
687
          watchFileEx endtime val ref old read_fn
688
      else do 
689
       threadDelay 100000
690
       watchFileEx endtime base ref old read_fn
691

    
692
-- | Within the given timeout (in seconds), wait for for the output
693
-- of the given method to change and return the new value; make use of
694
-- the promise that the method will only change its value, if
695
-- the given file changes on disk. If the file does not exist on disk, return
696
-- immediately.
697
watchFile :: Eq a => FilePath -> Int -> a -> IO a -> IO a
698
watchFile fpath timeout old read_fn = do
699
  current <- getCurrentTimeUSec
700
  let endtime = current + fromIntegral timeout * 1000000
701
  fstat <- getFStatSafe fpath
702
  ref <- newIORef fstat
703
  inotify <- initINotify
704
  let do_watch e = do
705
                     logDebug $ "Notified of change in " ++ fpath 
706
                                  ++ "; event: " ++ show e
707
                     when (e == Ignored)
708
                       (addWatch inotify [Modify, Delete] fpath do_watch
709
                          >> return ())
710
                     fstat' <- getFStatSafe fpath
711
                     writeIORef ref fstat'
712
  _ <- addWatch inotify [Modify, Delete] fpath do_watch
713
  newval <- read_fn
714
  if newval /= old
715
    then do
716
      logDebug $ "File " ++ fpath ++ " changed during setup of inotify"
717
      killINotify inotify
718
      return newval
719
    else do
720
      result <- watchFileEx endtime fstat ref old read_fn
721
      killINotify inotify
722
      return result
723

    
724
-- | Type describing ownership and permissions of newly generated
725
-- directories and files. All parameters are optional, with nothing
726
-- meaning that the default value should be left untouched.
727

    
728
data FilePermissions = FilePermissions { fpOwner :: Maybe String
729
                                       , fpGroup :: Maybe String
730
                                       , fpPermissions :: FileMode
731
                                       }
732

    
733
-- | Ensure that a given file or directory has the permissions, and
734
-- possibly ownerships, as required.
735
ensurePermissions :: FilePath -> FilePermissions -> IO (Result ())
736
ensurePermissions fpath perms = do
737
  eitherFileStatus <- try $ getFileStatus fpath
738
                      :: IO (Either IOError FileStatus)
739
  (flip $ either (return . Bad . show)) eitherFileStatus $ \fstat -> do
740
    ownertry <- case fpOwner perms of
741
      Nothing -> return $ Right ()
742
      Just owner -> try $ do
743
        ownerid <- userID `liftM` getUserEntryForName owner
744
        unless (ownerid == fileOwner fstat) $ do
745
          logDebug $ "Changing owner of " ++ fpath ++ " to " ++ owner
746
          setOwnerAndGroup fpath ownerid (-1)
747
    grouptry <- case fpGroup perms of
748
      Nothing -> return $ Right ()
749
      Just grp -> try $ do
750
        groupid <- groupID `liftM` getGroupEntryForName grp
751
        unless (groupid == fileGroup fstat) $ do
752
          logDebug $ "Changing group of " ++ fpath ++ " to " ++ grp
753
          setOwnerAndGroup fpath (-1) groupid
754
    let fp = fpPermissions perms
755
    permtry <- if fileMode fstat == fp
756
      then return $ Right ()
757
      else try $ do
758
        logInfo $ "Changing permissions of " ++ fpath ++ " to "
759
                    ++ showOct fp ""
760
        setFileMode fpath fp
761
    let errors = E.lefts ([ownertry, grouptry, permtry] :: [Either IOError ()])
762
    if null errors
763
      then return $ Ok ()
764
      else return . Bad $ show errors
765

    
766
-- | Safely rename a file, creating the target directory, if needed.
767
safeRenameFile :: FilePermissions -> FilePath -> FilePath -> IO (Result ())
768
safeRenameFile perms from to = do
769
  directtry <- try $ renameFile from to
770
  case (directtry :: Either IOError ()) of
771
    Right () -> return $ Ok ()
772
    Left _ -> do
773
      result <- try $ do
774
        let dir = takeDirectory to
775
        createDirectoryIfMissing True dir
776
        _ <- ensurePermissions dir perms
777
        renameFile from to
778
      return $ either (Bad . show) Ok (result :: Either IOError ())