{-# 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.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 Lock
_ IORef Bool
x == :: FileLock -> FileLock -> Bool
== Lock Lock
_ IORef Bool
y = IORef Bool
x forall a. Eq a => a -> a -> Bool
== IORef Bool
y
newLock :: I.Lock -> IO FileLock
newLock :: Lock -> IO FileLock
newLock Lock
x = Lock -> IORef Bool -> FileLock
Lock Lock
x forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. a -> IO (IORef a)
newIORef Bool
True
data SharedExclusive
= Shared
| Exclusive
deriving (Int -> SharedExclusive -> ShowS
[SharedExclusive] -> ShowS
SharedExclusive -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SharedExclusive] -> ShowS
$cshowList :: [SharedExclusive] -> ShowS
show :: SharedExclusive -> String
$cshow :: SharedExclusive -> String
showsPrec :: Int -> SharedExclusive -> ShowS
$cshowsPrec :: Int -> SharedExclusive -> ShowS
Show, SharedExclusive -> SharedExclusive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SharedExclusive -> SharedExclusive -> Bool
$c/= :: SharedExclusive -> SharedExclusive -> Bool
== :: SharedExclusive -> SharedExclusive -> Bool
$c== :: SharedExclusive -> SharedExclusive -> Bool
Eq, Typeable)
lockFile :: FilePath -> SharedExclusive -> IO FileLock
lockFile :: String -> SharedExclusive -> IO FileLock
lockFile String
path SharedExclusive
mode = Lock -> IO FileLock
newLock forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Bool -> IO Lock
I.lock String
path (SharedExclusive
mode forall a. Eq a => a -> a -> Bool
== SharedExclusive
Exclusive)
tryLockFile :: FilePath -> SharedExclusive -> IO (Maybe FileLock)
tryLockFile :: String -> SharedExclusive -> IO (Maybe FileLock)
tryLockFile String
path SharedExclusive
mode = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Lock -> IO FileLock
newLock forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Bool -> IO (Maybe Lock)
I.tryLock String
path (SharedExclusive
mode forall a. Eq a => a -> a -> Bool
== SharedExclusive
Exclusive)
unlockFile :: FileLock -> IO ()
unlockFile :: FileLock -> IO ()
unlockFile (Lock Lock
l IORef Bool
ref) = do
Bool
wasAlive <- forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef IORef Bool
ref forall a b. (a -> b) -> a -> b
$ \Bool
old -> (Bool
False, Bool
old)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
wasAlive forall a b. (a -> b) -> a -> b
$ Lock -> IO ()
I.unlock Lock
l
withFileLock :: FilePath -> SharedExclusive -> (FileLock -> IO a) -> IO a
withFileLock :: forall a. String -> SharedExclusive -> (FileLock -> IO a) -> IO a
withFileLock String
path SharedExclusive
mode = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
E.bracket (String -> SharedExclusive -> IO FileLock
lockFile String
path SharedExclusive
mode) FileLock -> IO ()
unlockFile
withTryFileLock :: FilePath -> SharedExclusive -> (FileLock -> IO a) -> IO (Maybe a)
withTryFileLock :: forall a.
String -> SharedExclusive -> (FileLock -> IO a) -> IO (Maybe a)
withTryFileLock String
path SharedExclusive
mode FileLock -> IO a
f = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
E.bracket (String -> SharedExclusive -> IO (Maybe FileLock)
tryLockFile String
path SharedExclusive
mode) (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FileLock -> IO ()
unlockFile) (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FileLock -> IO a
f)