root / src / Ganeti / Utils.hs @ bf7ee7ad
History | View | Annotate | Download (18 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 |
, plural |
40 |
, niceSort |
41 |
, niceSortKey |
42 |
, exitIfBad |
43 |
, exitErr |
44 |
, exitWhen |
45 |
, exitUnless |
46 |
, logWarningIfBad |
47 |
, rStripSpace |
48 |
, newUUID |
49 |
, getCurrentTime |
50 |
, getCurrentTimeUSec |
51 |
, clockTimeToString |
52 |
, chompPrefix |
53 |
, warn |
54 |
, wrap |
55 |
, trim |
56 |
, defaultHead |
57 |
, exitIfEmpty |
58 |
, splitEithers |
59 |
, recombineEithers |
60 |
, resolveAddr |
61 |
, monadicThe |
62 |
, setOwnerAndGroupFromNames |
63 |
, formatOrdinal |
64 |
, atomicWriteFile |
65 |
, tryAndLogIOError |
66 |
) where |
67 |
|
68 |
import Control.Exception (try) |
69 |
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace) |
70 |
import Data.Function (on) |
71 |
import Data.List |
72 |
import qualified Data.Map as M |
73 |
import Control.Monad (foldM) |
74 |
import System.Directory (renameFile) |
75 |
import System.FilePath.Posix (takeDirectory, takeBaseName) |
76 |
|
77 |
import Debug.Trace |
78 |
import Network.Socket |
79 |
|
80 |
import Ganeti.BasicTypes |
81 |
import qualified Ganeti.ConstantUtils as ConstantUtils |
82 |
import Ganeti.Logging |
83 |
import Ganeti.Runtime |
84 |
import System.IO |
85 |
import System.Exit |
86 |
import System.Posix.Files |
87 |
import System.Time |
88 |
|
89 |
-- * Debug functions |
90 |
|
91 |
-- | To be used only for debugging, breaks referential integrity. |
92 |
debug :: Show a => a -> a |
93 |
debug x = trace (show x) x |
94 |
|
95 |
-- | Displays a modified form of the second parameter before returning |
96 |
-- it. |
97 |
debugFn :: Show b => (a -> b) -> a -> a |
98 |
debugFn fn x = debug (fn x) `seq` x |
99 |
|
100 |
-- | Show the first parameter before returning the second one. |
101 |
debugXy :: Show a => a -> b -> b |
102 |
debugXy = seq . debug |
103 |
|
104 |
-- * Miscellaneous |
105 |
|
106 |
-- | Apply the function if condition holds, otherwise use default value. |
107 |
applyIf :: Bool -> (a -> a) -> a -> a |
108 |
applyIf b f x = if b then f x else x |
109 |
|
110 |
-- | Comma-join a string list. |
111 |
commaJoin :: [String] -> String |
112 |
commaJoin = intercalate "," |
113 |
|
114 |
-- | Split a list on a separator and return an array. |
115 |
sepSplit :: Eq a => a -> [a] -> [[a]] |
116 |
sepSplit sep s |
117 |
| null s = [] |
118 |
| null xs = [x] |
119 |
| null ys = [x,[]] |
120 |
| otherwise = x:sepSplit sep ys |
121 |
where (x, xs) = break (== sep) s |
122 |
ys = drop 1 xs |
123 |
|
124 |
-- | Simple pluralize helper |
125 |
plural :: Int -> String -> String -> String |
126 |
plural 1 s _ = s |
127 |
plural _ _ p = p |
128 |
|
129 |
-- | Ensure a value is quoted if needed. |
130 |
ensureQuoted :: String -> String |
131 |
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v) |
132 |
then '\'':v ++ "'" |
133 |
else v |
134 |
|
135 |
-- * Mathematical functions |
136 |
|
137 |
-- Simple and slow statistical functions, please replace with better |
138 |
-- versions |
139 |
|
140 |
-- | Standard deviation function. |
141 |
stdDev :: [Double] -> Double |
142 |
stdDev lst = |
143 |
-- first, calculate the list length and sum lst in a single step, |
144 |
-- for performance reasons |
145 |
let (ll', sx) = foldl' (\(rl, rs) e -> |
146 |
let rl' = rl + 1 |
147 |
rs' = rs + e |
148 |
in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst |
149 |
ll = fromIntegral ll'::Double |
150 |
mv = sx / ll |
151 |
av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst |
152 |
in sqrt (av / ll) -- stddev |
153 |
|
154 |
-- * Logical functions |
155 |
|
156 |
-- Avoid syntactic sugar and enhance readability. These functions are proposed |
157 |
-- by some for inclusion in the Prelude, and at the moment they are present |
158 |
-- (with various definitions) in the utility-ht package. Some rationale and |
159 |
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else> |
160 |
|
161 |
-- | \"if\" as a function, rather than as syntactic sugar. |
162 |
if' :: Bool -- ^ condition |
163 |
-> a -- ^ \"then\" result |
164 |
-> a -- ^ \"else\" result |
165 |
-> a -- ^ \"then\" or "else" result depending on the condition |
166 |
if' True x _ = x |
167 |
if' _ _ y = y |
168 |
|
169 |
-- * Parsing utility functions |
170 |
|
171 |
-- | Parse results from readsPrec. |
172 |
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a |
173 |
parseChoices _ _ ((v, ""):[]) = return v |
174 |
parseChoices name s ((_, e):[]) = |
175 |
fail $ name ++ ": leftover characters when parsing '" |
176 |
++ s ++ "': '" ++ e ++ "'" |
177 |
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'" |
178 |
|
179 |
-- | Safe 'read' function returning data encapsulated in a Result. |
180 |
tryRead :: (Monad m, Read a) => String -> String -> m a |
181 |
tryRead name s = parseChoices name s $ reads s |
182 |
|
183 |
-- | Format a table of strings to maintain consistent length. |
184 |
formatTable :: [[String]] -> [Bool] -> [[String]] |
185 |
formatTable vals numpos = |
186 |
let vtrans = transpose vals -- transpose, so that we work on rows |
187 |
-- rather than columns |
188 |
mlens = map (maximum . map length) vtrans |
189 |
expnd = map (\(flds, isnum, ml) -> |
190 |
map (\val -> |
191 |
let delta = ml - length val |
192 |
filler = replicate delta ' ' |
193 |
in if delta > 0 |
194 |
then if isnum |
195 |
then filler ++ val |
196 |
else val ++ filler |
197 |
else val |
198 |
) flds |
199 |
) (zip3 vtrans numpos mlens) |
200 |
in transpose expnd |
201 |
|
202 |
-- | Constructs a printable table from given header and rows |
203 |
printTable :: String -> [String] -> [[String]] -> [Bool] -> String |
204 |
printTable lp header rows isnum = |
205 |
unlines . map ((++) lp . (:) ' ' . unwords) $ |
206 |
formatTable (header:rows) isnum |
207 |
|
208 |
-- | Converts a unit (e.g. m or GB) into a scaling factor. |
209 |
parseUnitValue :: (Monad m) => String -> m Rational |
210 |
parseUnitValue unit |
211 |
-- binary conversions first |
212 |
| null unit = return 1 |
213 |
| unit == "m" || upper == "MIB" = return 1 |
214 |
| unit == "g" || upper == "GIB" = return kbBinary |
215 |
| unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary |
216 |
-- SI conversions |
217 |
| unit == "M" || upper == "MB" = return mbFactor |
218 |
| unit == "G" || upper == "GB" = return $ mbFactor * kbDecimal |
219 |
| unit == "T" || upper == "TB" = return $ mbFactor * kbDecimal * kbDecimal |
220 |
| otherwise = fail $ "Unknown unit '" ++ unit ++ "'" |
221 |
where upper = map toUpper unit |
222 |
kbBinary = 1024 :: Rational |
223 |
kbDecimal = 1000 :: Rational |
224 |
decToBin = kbDecimal / kbBinary -- factor for 1K conversion |
225 |
mbFactor = decToBin * decToBin -- twice the factor for just 1K |
226 |
|
227 |
-- | Tries to extract number and scale from the given string. |
228 |
-- |
229 |
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is |
230 |
-- specified, it defaults to MiB. Return value is always an integral |
231 |
-- value in MiB. |
232 |
parseUnit :: (Monad m, Integral a, Read a) => String -> m a |
233 |
parseUnit str = |
234 |
-- TODO: enhance this by splitting the unit parsing code out and |
235 |
-- accepting floating-point numbers |
236 |
case (reads str::[(Int, String)]) of |
237 |
[(v, suffix)] -> |
238 |
let unit = dropWhile (== ' ') suffix |
239 |
in do |
240 |
scaling <- parseUnitValue unit |
241 |
return $ truncate (fromIntegral v * scaling) |
242 |
_ -> fail $ "Can't parse string '" ++ str ++ "'" |
243 |
|
244 |
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value, |
245 |
-- otherwise returning the actual contained value. |
246 |
exitIfBad :: String -> Result a -> IO a |
247 |
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s) |
248 |
exitIfBad _ (Ok v) = return v |
249 |
|
250 |
-- | Exits immediately with an error message. |
251 |
exitErr :: String -> IO a |
252 |
exitErr errmsg = do |
253 |
hPutStrLn stderr $ "Error: " ++ errmsg |
254 |
exitWith (ExitFailure 1) |
255 |
|
256 |
-- | Exits with an error message if the given boolean condition if true. |
257 |
exitWhen :: Bool -> String -> IO () |
258 |
exitWhen True msg = exitErr msg |
259 |
exitWhen False _ = return () |
260 |
|
261 |
-- | Exits with an error message /unless/ the given boolean condition |
262 |
-- if true, the opposite of 'exitWhen'. |
263 |
exitUnless :: Bool -> String -> IO () |
264 |
exitUnless cond = exitWhen (not cond) |
265 |
|
266 |
-- | Unwraps a 'Result', logging a warning message and then returning a default |
267 |
-- value if it is a 'Bad' value, otherwise returning the actual contained value. |
268 |
logWarningIfBad :: String -> a -> Result a -> IO a |
269 |
logWarningIfBad msg defVal (Bad s) = do |
270 |
logWarning $ msg ++ ": " ++ s |
271 |
return defVal |
272 |
logWarningIfBad _ _ (Ok v) = return v |
273 |
|
274 |
-- | Try an IO interaction, log errors and unfold as a 'Result'. |
275 |
tryAndLogIOError :: IO a -> String -> (a -> Result b) -> IO (Result b) |
276 |
tryAndLogIOError io msg okfn = |
277 |
try io >>= either |
278 |
(\ e -> do |
279 |
let combinedmsg = msg ++ ": " ++ show (e :: IOError) |
280 |
logError combinedmsg |
281 |
return . Bad $ combinedmsg) |
282 |
(return . okfn) |
283 |
|
284 |
-- | Print a warning, but do not exit. |
285 |
warn :: String -> IO () |
286 |
warn = hPutStrLn stderr . (++) "Warning: " |
287 |
|
288 |
-- | Helper for 'niceSort'. Computes the key element for a given string. |
289 |
extractKey :: [Either Integer String] -- ^ Current (partial) key, reversed |
290 |
-> String -- ^ Remaining string |
291 |
-> ([Either Integer String], String) |
292 |
extractKey ek [] = (reverse ek, []) |
293 |
extractKey ek xs@(x:_) = |
294 |
let (span_fn, conv_fn) = if isDigit x |
295 |
then (isDigit, Left . read) |
296 |
else (not . isDigit, Right) |
297 |
(k, rest) = span span_fn xs |
298 |
in extractKey (conv_fn k:ek) rest |
299 |
|
300 |
{-| Sort a list of strings based on digit and non-digit groupings. |
301 |
|
302 |
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function |
303 |
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@. |
304 |
|
305 |
The sort algorithm breaks each name in groups of either only-digits or |
306 |
no-digits, and sorts based on each group. |
307 |
|
308 |
Internally, this is not implemented via regexes (like the Python |
309 |
version), but via actual splitting of the string in sequences of |
310 |
either digits or everything else, and converting the digit sequences |
311 |
in /Left Integer/ and the non-digit ones in /Right String/, at which |
312 |
point sorting becomes trivial due to the built-in 'Either' ordering; |
313 |
we only need one extra step of dropping the key at the end. |
314 |
|
315 |
-} |
316 |
niceSort :: [String] -> [String] |
317 |
niceSort = niceSortKey id |
318 |
|
319 |
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@ |
320 |
-- since we don't want to add an ordering constraint on the /a/ type, |
321 |
-- hence the need to only compare the first element of the /(key, a)/ |
322 |
-- tuple. |
323 |
niceSortKey :: (a -> String) -> [a] -> [a] |
324 |
niceSortKey keyfn = |
325 |
map snd . sortBy (compare `on` fst) . |
326 |
map (\s -> (fst . extractKey [] $ keyfn s, s)) |
327 |
|
328 |
-- | Strip space characthers (including newline). As this is |
329 |
-- expensive, should only be run on small strings. |
330 |
rStripSpace :: String -> String |
331 |
rStripSpace = reverse . dropWhile isSpace . reverse |
332 |
|
333 |
-- | Returns a random UUID. |
334 |
-- This is a Linux-specific method as it uses the /proc filesystem. |
335 |
newUUID :: IO String |
336 |
newUUID = do |
337 |
contents <- readFile ConstantUtils.randomUuidFile |
338 |
return $! rStripSpace $ take 128 contents |
339 |
|
340 |
-- | Returns the current time as an 'Integer' representing the number |
341 |
-- of seconds from the Unix epoch. |
342 |
getCurrentTime :: IO Integer |
343 |
getCurrentTime = do |
344 |
TOD ctime _ <- getClockTime |
345 |
return ctime |
346 |
|
347 |
-- | Returns the current time as an 'Integer' representing the number |
348 |
-- of microseconds from the Unix epoch (hence the need for 'Integer'). |
349 |
getCurrentTimeUSec :: IO Integer |
350 |
getCurrentTimeUSec = do |
351 |
TOD ctime pico <- getClockTime |
352 |
-- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and |
353 |
-- picoseconds right |
354 |
return $ ctime * 1000000 + pico `div` 1000000 |
355 |
|
356 |
-- | Convert a ClockTime into a (seconds-only) timestamp. |
357 |
clockTimeToString :: ClockTime -> String |
358 |
clockTimeToString (TOD t _) = show t |
359 |
|
360 |
{-| Strip a prefix from a string, allowing the last character of the prefix |
361 |
(which is assumed to be a separator) to be absent from the string if the string |
362 |
terminates there. |
363 |
|
364 |
\>>> chompPrefix \"foo:bar:\" \"a:b:c\" |
365 |
Nothing |
366 |
|
367 |
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\" |
368 |
Just \"baz\" |
369 |
|
370 |
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\" |
371 |
Just \"\" |
372 |
|
373 |
\>>> chompPrefix \"foo:bar:\" \"foo:bar\" |
374 |
Just \"\" |
375 |
|
376 |
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\" |
377 |
Nothing |
378 |
-} |
379 |
chompPrefix :: String -> String -> Maybe String |
380 |
chompPrefix pfx str = |
381 |
if pfx `isPrefixOf` str || str == init pfx |
382 |
then Just $ drop (length pfx) str |
383 |
else Nothing |
384 |
|
385 |
-- | Breaks a string in lines with length \<= maxWidth. |
386 |
-- |
387 |
-- NOTE: The split is OK if: |
388 |
-- |
389 |
-- * It doesn't break a word, i.e. the next line begins with space |
390 |
-- (@isSpace . head $ rest@) or the current line ends with space |
391 |
-- (@null revExtra@); |
392 |
-- |
393 |
-- * It breaks a very big word that doesn't fit anyway (@null revLine@). |
394 |
wrap :: Int -- ^ maxWidth |
395 |
-> String -- ^ string that needs wrapping |
396 |
-> [String] -- ^ string \"broken\" in lines |
397 |
wrap maxWidth = filter (not . null) . map trim . wrap0 |
398 |
where wrap0 :: String -> [String] |
399 |
wrap0 text |
400 |
| length text <= maxWidth = [text] |
401 |
| isSplitOK = line : wrap0 rest |
402 |
| otherwise = line' : wrap0 rest' |
403 |
where (line, rest) = splitAt maxWidth text |
404 |
(revExtra, revLine) = break isSpace . reverse $ line |
405 |
(line', rest') = (reverse revLine, reverse revExtra ++ rest) |
406 |
isSplitOK = |
407 |
null revLine || null revExtra || startsWithSpace rest |
408 |
startsWithSpace (x:_) = isSpace x |
409 |
startsWithSpace _ = False |
410 |
|
411 |
-- | Removes surrounding whitespace. Should only be used in small |
412 |
-- strings. |
413 |
trim :: String -> String |
414 |
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace |
415 |
|
416 |
-- | A safer head version, with a default value. |
417 |
defaultHead :: a -> [a] -> a |
418 |
defaultHead def [] = def |
419 |
defaultHead _ (x:_) = x |
420 |
|
421 |
-- | A 'head' version in the I/O monad, for validating parameters |
422 |
-- without which we cannot continue. |
423 |
exitIfEmpty :: String -> [a] -> IO a |
424 |
exitIfEmpty _ (x:_) = return x |
425 |
exitIfEmpty s [] = exitErr s |
426 |
|
427 |
-- | Obtain the unique element of a list in an arbitrary monad. |
428 |
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a |
429 |
monadicThe s [] = fail s |
430 |
monadicThe s (x:xs) |
431 |
| all (x ==) xs = return x |
432 |
| otherwise = fail s |
433 |
|
434 |
-- | Split an 'Either' list into two separate lists (containing the |
435 |
-- 'Left' and 'Right' elements, plus a \"trail\" list that allows |
436 |
-- recombination later. |
437 |
-- |
438 |
-- This is splitter; for recombination, look at 'recombineEithers'. |
439 |
-- The sum of \"left\" and \"right\" lists should be equal to the |
440 |
-- original list length, and the trail list should be the same length |
441 |
-- as well. The entries in the resulting lists are reversed in |
442 |
-- comparison with the original list. |
443 |
splitEithers :: [Either a b] -> ([a], [b], [Bool]) |
444 |
splitEithers = foldl' splitter ([], [], []) |
445 |
where splitter (l, r, t) e = |
446 |
case e of |
447 |
Left v -> (v:l, r, False:t) |
448 |
Right v -> (l, v:r, True:t) |
449 |
|
450 |
-- | Recombines two \"left\" and \"right\" lists using a \"trail\" |
451 |
-- list into a single 'Either' list. |
452 |
-- |
453 |
-- This is the counterpart to 'splitEithers'. It does the opposite |
454 |
-- transformation, and the output list will be the reverse of the |
455 |
-- input lists. Since 'splitEithers' also reverses the lists, calling |
456 |
-- these together will result in the original list. |
457 |
-- |
458 |
-- Mismatches in the structure of the lists (e.g. inconsistent |
459 |
-- lengths) are represented via 'Bad'; normally this function should |
460 |
-- not fail, if lists are passed as generated by 'splitEithers'. |
461 |
recombineEithers :: (Show a, Show b) => |
462 |
[a] -> [b] -> [Bool] -> Result [Either a b] |
463 |
recombineEithers lefts rights trail = |
464 |
foldM recombiner ([], lefts, rights) trail >>= checker |
465 |
where checker (eithers, [], []) = Ok eithers |
466 |
checker (_, lefts', rights') = |
467 |
Bad $ "Inconsistent results after recombination, l'=" ++ |
468 |
show lefts' ++ ", r'=" ++ show rights' |
469 |
recombiner (es, l:ls, rs) False = Ok (Left l:es, ls, rs) |
470 |
recombiner (es, ls, r:rs) True = Ok (Right r:es, ls, rs) |
471 |
recombiner (_, ls, rs) t = Bad $ "Inconsistent trail log: l=" ++ |
472 |
show ls ++ ", r=" ++ show rs ++ ",t=" ++ |
473 |
show t |
474 |
|
475 |
-- | Default hints for the resolver |
476 |
resolveAddrHints :: Maybe AddrInfo |
477 |
resolveAddrHints = |
478 |
Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] } |
479 |
|
480 |
-- | Resolves a numeric address. |
481 |
resolveAddr :: Int -> String -> IO (Result (Family, SockAddr)) |
482 |
resolveAddr port str = do |
483 |
resolved <- getAddrInfo resolveAddrHints (Just str) (Just (show port)) |
484 |
return $ case resolved of |
485 |
[] -> Bad "Invalid results from lookup?" |
486 |
best:_ -> Ok (addrFamily best, addrAddress best) |
487 |
|
488 |
-- | Set the owner and the group of a file (given as names, not numeric id). |
489 |
setOwnerAndGroupFromNames :: FilePath -> GanetiDaemon -> GanetiGroup -> IO () |
490 |
setOwnerAndGroupFromNames filename daemon dGroup = do |
491 |
-- TODO: it would be nice to rework this (or getEnts) so that runtimeEnts |
492 |
-- is read only once per daemon startup, and then cached for further usage. |
493 |
runtimeEnts <- getEnts |
494 |
ents <- exitIfBad "Can't find required user/groups" runtimeEnts |
495 |
-- note: we use directly ! as lookup failures shouldn't happen, due |
496 |
-- to the map construction |
497 |
let uid = fst ents M.! daemon |
498 |
let gid = snd ents M.! dGroup |
499 |
setOwnerAndGroup filename uid gid |
500 |
|
501 |
-- | Formats an integral number, appending a suffix. |
502 |
formatOrdinal :: (Integral a, Show a) => a -> String |
503 |
formatOrdinal num |
504 |
| num > 10 && num < 20 = suffix "th" |
505 |
| tens == 1 = suffix "st" |
506 |
| tens == 2 = suffix "nd" |
507 |
| tens == 3 = suffix "rd" |
508 |
| otherwise = suffix "th" |
509 |
where tens = num `mod` 10 |
510 |
suffix s = show num ++ s |
511 |
|
512 |
-- | Atomically write a file, by first writing the contents into a temporary |
513 |
-- file and then renaming it to the old position. |
514 |
atomicWriteFile :: FilePath -> String -> IO () |
515 |
atomicWriteFile path contents = do |
516 |
(tmppath, tmphandle) <- openTempFile (takeDirectory path) (takeBaseName path) |
517 |
hPutStr tmphandle contents |
518 |
hClose tmphandle |
519 |
renameFile tmppath path |