Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 751fb9e2

History | View | Annotate | Download (20.2 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
  ) where
74

    
75
import Control.Exception (try)
76
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
77
import Data.Function (on)
78
import Data.List
79
import qualified Data.Map as M
80
import Control.Monad (foldM, liftM)
81
import System.Directory (renameFile)
82
import System.FilePath.Posix (takeDirectory, takeBaseName)
83
import System.Posix.Types
84

    
85
import Debug.Trace
86
import Network.Socket
87

    
88
import Ganeti.BasicTypes
89
import qualified Ganeti.ConstantUtils as ConstantUtils
90
import Ganeti.Logging
91
import Ganeti.Runtime
92
import System.IO
93
import System.Exit
94
import System.Posix.Files
95
import System.Posix.IO
96
import System.Time
97

    
98
-- * Debug functions
99

    
100
-- | To be used only for debugging, breaks referential integrity.
101
debug :: Show a => a -> a
102
debug x = trace (show x) x
103

    
104
-- | Displays a modified form of the second parameter before returning
105
-- it.
106
debugFn :: Show b => (a -> b) -> a -> a
107
debugFn fn x = debug (fn x) `seq` x
108

    
109
-- | Show the first parameter before returning the second one.
110
debugXy :: Show a => a -> b -> b
111
debugXy = seq . debug
112

    
113
-- * Miscellaneous
114

    
115
-- | Apply the function if condition holds, otherwise use default value.
116
applyIf :: Bool -> (a -> a) -> a -> a
117
applyIf b f x = if b then f x else x
118

    
119
-- | Comma-join a string list.
120
commaJoin :: [String] -> String
121
commaJoin = intercalate ","
122

    
123
-- | Split a list on a separator and return an array.
124
sepSplit :: Eq a => a -> [a] -> [[a]]
125
sepSplit sep s
126
  | null s    = []
127
  | null xs   = [x]
128
  | null ys   = [x,[]]
129
  | otherwise = x:sepSplit sep ys
130
  where (x, xs) = break (== sep) s
131
        ys = drop 1 xs
132

    
133
-- | Simple pluralize helper
134
plural :: Int -> String -> String -> String
135
plural 1 s _ = s
136
plural _ _ p = p
137

    
138
-- | Ensure a value is quoted if needed.
139
ensureQuoted :: String -> String
140
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
141
                 then '\'':v ++ "'"
142
                 else v
143

    
144
-- * Mathematical functions
145

    
146
-- Simple and slow statistical functions, please replace with better
147
-- versions
148

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

    
163
-- *  Logical functions
164

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

    
170
-- | \"if\" as a function, rather than as syntactic sugar.
171
if' :: Bool -- ^ condition
172
    -> a    -- ^ \"then\" result
173
    -> a    -- ^ \"else\" result
174
    -> a    -- ^ \"then\" or "else" result depending on the condition
175
if' True x _ = x
176
if' _    _ y = y
177

    
178
-- * Parsing utility functions
179

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

    
188
-- | Safe 'read' function returning data encapsulated in a Result.
189
tryRead :: (Monad m, Read a) => String -> String -> m a
190
tryRead name s = parseChoices name s $ reads s
191

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

    
211
-- | Constructs a printable table from given header and rows
212
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
213
printTable lp header rows isnum =
214
  unlines . map ((++) lp . (:) ' ' . unwords) $
215
  formatTable (header:rows) isnum
216

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

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

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

    
261
-- | Tries to extract a number and scale from a given string, taking
262
-- all kilos to be binary.
263
parseUnitAssumeBinary :: (Monad m, Integral a, Read a) => String -> m a
264
parseUnitAssumeBinary = parseUnitEx True
265

    
266
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
267
-- otherwise returning the actual contained value.
268
exitIfBad :: String -> Result a -> IO a
269
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
270
exitIfBad _ (Ok v) = return v
271

    
272
-- | Exits immediately with an error message.
273
exitErr :: String -> IO a
274
exitErr errmsg = do
275
  hPutStrLn stderr $ "Error: " ++ errmsg
276
  exitWith (ExitFailure 1)
277

    
278
-- | Exits with an error message if the given boolean condition if true.
279
exitWhen :: Bool -> String -> IO ()
280
exitWhen True msg = exitErr msg
281
exitWhen False _  = return ()
282

    
283
-- | Exits with an error message /unless/ the given boolean condition
284
-- if true, the opposite of 'exitWhen'.
285
exitUnless :: Bool -> String -> IO ()
286
exitUnless cond = exitWhen (not cond)
287

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

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

    
306
-- | Print a warning, but do not exit.
307
warn :: String -> IO ()
308
warn = hPutStrLn stderr . (++) "Warning: "
309

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

    
322
{-| Sort a list of strings based on digit and non-digit groupings.
323

    
324
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
325
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
326

    
327
The sort algorithm breaks each name in groups of either only-digits or
328
no-digits, and sorts based on each group.
329

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

    
337
-}
338
niceSort :: [String] -> [String]
339
niceSort = niceSortKey id
340

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

    
350
-- | Strip space characthers (including newline). As this is
351
-- expensive, should only be run on small strings.
352
rStripSpace :: String -> String
353
rStripSpace = reverse . dropWhile isSpace . reverse
354

    
355
-- | Returns a random UUID.
356
-- This is a Linux-specific method as it uses the /proc filesystem.
357
newUUID :: IO String
358
newUUID = do
359
  contents <- readFile ConstantUtils.randomUuidFile
360
  return $! rStripSpace $ take 128 contents
361

    
362
-- | Returns the current time as an 'Integer' representing the number
363
-- of seconds from the Unix epoch.
364
getCurrentTime :: IO Integer
365
getCurrentTime = do
366
  TOD ctime _ <- getClockTime
367
  return ctime
368

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

    
378
-- | Convert a ClockTime into a (seconds-only) timestamp.
379
clockTimeToString :: ClockTime -> String
380
clockTimeToString (TOD t _) = show t
381

    
382
{-| Strip a prefix from a string, allowing the last character of the prefix
383
(which is assumed to be a separator) to be absent from the string if the string
384
terminates there.
385

    
386
\>>> chompPrefix \"foo:bar:\" \"a:b:c\"
387
Nothing
388

    
389
\>>> chompPrefix \"foo:bar:\" \"foo:bar:baz\"
390
Just \"baz\"
391

    
392
\>>> chompPrefix \"foo:bar:\" \"foo:bar:\"
393
Just \"\"
394

    
395
\>>> chompPrefix \"foo:bar:\" \"foo:bar\"
396
Just \"\"
397

    
398
\>>> chompPrefix \"foo:bar:\" \"foo:barbaz\"
399
Nothing
400
-}
401
chompPrefix :: String -> String -> Maybe String
402
chompPrefix pfx str =
403
  if pfx `isPrefixOf` str || str == init pfx
404
    then Just $ drop (length pfx) str
405
    else Nothing
406

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

    
433
-- | Removes surrounding whitespace. Should only be used in small
434
-- strings.
435
trim :: String -> String
436
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
437

    
438
-- | A safer head version, with a default value.
439
defaultHead :: a -> [a] -> a
440
defaultHead def []    = def
441
defaultHead _   (x:_) = x
442

    
443
-- | A 'head' version in the I/O monad, for validating parameters
444
-- without which we cannot continue.
445
exitIfEmpty :: String -> [a] -> IO a
446
exitIfEmpty _ (x:_) = return x
447
exitIfEmpty s []    = exitErr s
448

    
449
-- | Obtain the unique element of a list in an arbitrary monad.
450
monadicThe :: (Eq a, Monad m) => String -> [a] -> m a
451
monadicThe s [] = fail s
452
monadicThe s (x:xs)
453
  | all (x ==) xs = return x
454
  | otherwise = fail s
455

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

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

    
497
-- | Default hints for the resolver
498
resolveAddrHints :: Maybe AddrInfo
499
resolveAddrHints =
500
  Just defaultHints { addrFlags = [AI_NUMERICHOST, AI_NUMERICSERV] }
501

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

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

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

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

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

    
552
-- | File stat identifier.
553
type FStat = (EpochTime, FileID, FileOffset)
554

    
555
-- | Null 'FStat' value.
556
nullFStat :: FStat
557
nullFStat = (-1, -1, -1)
558

    
559
-- | Computes the file cache data from a FileStatus structure.
560
buildFileStatus :: FileStatus -> FStat
561
buildFileStatus ofs =
562
    let modt = modificationTime ofs
563
        inum = fileID ofs
564
        fsize = fileSize ofs
565
    in (modt, inum, fsize)
566

    
567
-- | Wrapper over 'buildFileStatus'. This reads the data from the
568
-- filesystem and then builds our cache structure.
569
getFStat :: FilePath -> IO FStat
570
getFStat p = liftM buildFileStatus (getFileStatus p)
571

    
572
-- | Safe version of 'getFStat', that ignores IOErrors.
573
getFStatSafe :: FilePath -> IO FStat
574
getFStatSafe fpath = liftM (either (const nullFStat) id)
575
                       ((try $ getFStat fpath) :: IO (Either IOError FStat))
576

    
577
-- | Check if the file needs reloading
578
needsReload :: FStat -> FilePath -> IO (Maybe FStat)
579
needsReload oldstat path = do
580
  newstat <- getFStat path
581
  return $ if newstat /= oldstat
582
             then Just newstat
583
             else Nothing