Copyright | (c) 2013-2015 2018 Peter Trško |
---|---|
License | BSD3 |
Maintainer | peter.trsko@gmail.com |
Stability | experimental |
Portability | GHC specific language extensions. |
Safe Haskell | Safe |
Language | Haskell2010 |
Provide exclusive access to a resource using lock file.
- withLockFile :: (MonadMask m, MonadIO m) => LockingParameters -> FilePath -> m a -> m a
- withLockFile_ :: (MonadMask m, MonadIO m) => LockingParameters -> FilePath -> m a -> m ()
- data LockingParameters = LockingParameters {}
- data RetryStrategy
- = No
- | Indefinitely
- | NumberOfTimes !Word8
- data LockingException
- withLockExt :: FilePath -> FilePath
Usage Example
Following example acquires lock file and then waits 1000000
micro seconds
before releasing it. Note also that it is possible to specify retry
strategy. Here we set it to No
and therefore this code won't retry to
acquire lock file after first failure.
{-# LANGUAGE TypeApplications #-} module Main (main) where import Control.Concurrent (threadDelay
) -- From base package, but GHC specific. import qualified Control.Exception as Exception (handle
) import Data.Default.Class (def
) -- From data-default-class package, alternatively it's possible to use -- data-default package version 0.5.2 and above. -- http://hackage.haskell.org/package/data-default-class -- http://hackage.haskell.org/package/data-default import System.IO.LockFile (LockingException
,LockingParameters
(retryToAcquireLock
) ,RetryStrategy
(No
) ,withLockFile
) main :: IO () main = handleException .withLockFile
lockParams lockFile $ threadDelay 1000000 where lockParams =def
{retryToAcquireLock
=No
} lockFile = "/var/run/lock/my-example-lock" handleException = Exception.handle $ putStrLn . ("Locking failed with: " ++) . show @LockingException
This command line example shows that trying to execute two instances of
example
at the same time will result in failure of the second one.
$ ghc example.hs [1 of 1] Compiling Main ( example.hs, example.o ) Linking example ... $ ./example & ./example [1] 7893 Locking failed with: Unable to acquire lock file: "/var/run/lock/my-example-lock" $ [1]+ Done ./example
Run computation with locked resource.
:: (MonadMask m, MonadIO m) | |
=> LockingParameters | |
-> FilePath | Lock file name. |
-> m a | |
-> m a |
Acquire a lock file before running computation and release it when it's done.
If "action" raises IOException
then this is not wrapped by
LockingException
. Only IOException
that occurred during locking or
unlocking is mapped to LockingException
. This doesn't affect the fact
that lock file is removed even if "action" fails.
:: (MonadMask m, MonadIO m) | |
=> LockingParameters | |
-> FilePath | Lock file name. |
-> m a | |
-> m () |
Type restricted version of withLockFile
that discards result of the
action.
Configuration
data LockingParameters Source #
Locking algorithm parameters. When in doubt, use def
, otherwise start
with it. Example:
lockedDo :: (MonadMask
m,MonadIO
m) =>FilePath
-> m a -> m a lockedDo =withLockFile
lockParams lockFile where lockParams =def
{retryToAcquireLock
=NumberOfTimes
3 } lockFile =withLockExt
"/var/lock/my-app"
LockingParameters | |
|
Eq LockingParameters Source # | |
Data LockingParameters Source # | |
Read LockingParameters Source # | |
Show LockingParameters Source # | |
Generic LockingParameters Source # | |
Default LockingParameters Source # | Defined as:
Sleep interval is inspired by |
type Rep LockingParameters Source # | |
data RetryStrategy Source #
Defines strategy for handling situations when lock-file is already acquired.
No | Don't retry at all. |
Indefinitely | Retry indefinitely. |
NumberOfTimes !Word8 | Retry only specified number of times.
If equal to zero then it is interpreted same way as |
Eq RetryStrategy Source # | |
Data RetryStrategy Source # | |
Read RetryStrategy Source # | |
Show RetryStrategy Source # | |
Generic RetryStrategy Source # | |
Default RetryStrategy Source # | Defined as: |
type Rep RetryStrategy Source # | |
Exceptions
data LockingException Source #
UnableToAcquireLockFile FilePath | Wasn't able to aquire lock file specified as an argument. |
CaughtIOException IOException |
|
Utility functions
withLockExt :: FilePath -> FilePath Source #
Append default lock file extension. Useful e.g. for generating lock file name out of regular file name.