module Hackage.Security.Util.IO (
    
    getFileSize
  , handleDoesNotExist
  , withDirLock
    
  , timedIO
  ) where
import Control.Monad (unless)
import Control.Exception
import Data.Time
import System.IO hiding (openTempFile, withFile)
import System.IO.Error
import Hackage.Security.Util.Path
import Hackage.Security.Util.FileLock (hTryLock, LockMode(ExclusiveLock), FileLockingNotSupported)
getFileSize :: (Num a, FsRoot root) => Path root -> IO a
getFileSize fp = fromInteger <$> withFile fp ReadMode hFileSize
handleDoesNotExist :: IO a -> IO (Maybe a)
handleDoesNotExist act =
   handle aux (Just <$> act)
  where
    aux e =
      if isDoesNotExistError e
        then return Nothing
        else throwIO e
withDirLock :: Path Absolute -> IO a -> IO a
withDirLock dir = bracket takeLock releaseLock . const
  where
    lock :: Path Absolute
    lock = dir </> fragment "hackage-security-lock"
    lock' :: FilePath
    lock' = toFilePath lock
    takeLock = do
        h <- openFile lock' ReadWriteMode
        handle (takeDirLock h) $ do
            gotlock <- hTryLock h ExclusiveLock
            unless gotlock $
                fail $ "hTryLock: lock already exists: " ++ lock'
            return (Just h)
    takeDirLock :: Handle -> FileLockingNotSupported -> IO (Maybe Handle)
    takeDirLock h _ = do
        
        
        hClose h
        handle onIOError (removeFile lock)
        createDirectory lock
        return Nothing
    onIOError :: IOError -> IO ()
    onIOError _ = hPutStrLn stderr
        "withDirLock: cannot remove lock file before directory lock fallback"
    releaseLock (Just h) = hClose h
    releaseLock Nothing  = removeDirectory lock
timedIO :: String -> IO a -> IO a
timedIO label act = do
    before <- getCurrentTime
    result <- act
    after  <- getCurrentTime
    hPutStrLn stderr $ label ++ ": " ++ show (after `diffUTCTime` before)
    hFlush stderr
    return result