{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE CPP #-}
module System.FileLock
( FileLock
, SharedExclusive(..)
, lockFile
, tryLockFile
, unlockFile
, withFileLock
, withTryFileLock
) where
import Control.Applicative
import qualified Control.Exception as E
import Control.Monad
import Data.IORef
import Data.Traversable (traverse)
import Data.Typeable
import Prelude
#ifdef USE_FLOCK
import qualified System.FileLock.Internal.Flock as I
#elif USE_LOCKFILEEX
import qualified System.FileLock.Internal.LockFileEx as I
#else
#error No backend is available
#endif
data FileLock = Lock
{-# UNPACk #-} !I.Lock
{-# UNPACk #-} !(IORef Bool)
deriving (Typeable)
instance Eq FileLock where
Lock _ x == Lock _ y = x == y
newLock :: I.Lock -> IO FileLock
newLock x = Lock x <$> newIORef True
data SharedExclusive
= Shared
| Exclusive
deriving (Show, Eq, Typeable)
lockFile :: FilePath -> SharedExclusive -> IO FileLock
lockFile path mode = newLock =<< I.lock path (mode == Exclusive)
tryLockFile :: FilePath -> SharedExclusive -> IO (Maybe FileLock)
tryLockFile path mode = traverse newLock =<< I.tryLock path (mode == Exclusive)
unlockFile :: FileLock -> IO ()
unlockFile (Lock l ref) = do
wasAlive <- atomicModifyIORef ref $ \old -> (False, old)
when wasAlive $ I.unlock l
withFileLock :: FilePath -> SharedExclusive -> (FileLock -> IO a) -> IO a
withFileLock path mode = E.bracket (lockFile path mode) unlockFile
withTryFileLock :: FilePath -> SharedExclusive -> (FileLock -> IO a) -> IO (Maybe a)
withTryFileLock path mode f = E.bracket (tryLockFile path mode) (traverse unlockFile) (traverse f)