lock-file-0.5.0.2: Provide exclusive access to a resource using lock file.

Copyright(c) 2013-2015, Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityCPP, NoImplicitPrelude
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.IO.LockFile

Contents

Description

Provide exclusive access to a resource using lock file.

Synopsis

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.

module Main (main)
    where

import Control.Concurrent (threadDelay)
    -- From base package, but GHC specific.

import qualified Control.Monad.TaggedException as Exception (handle)
    -- From tagged-exception-core package.
    -- http://hackage.haskell.org/package/tagged-exception-core
import Data.Default.Class (Default(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
    ( 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

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.

withLockFile Source

Arguments

:: (MonadMask m, MonadIO m) 
=> LockingParameters 
-> FilePath

Lock file name.

-> m a 
-> Throws LockingException 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.

withLockFile_ Source

Arguments

:: (MonadMask m, MonadIO m) 
=> LockingParameters 
-> FilePath

Lock file name.

-> m () 
-> Throws LockingException m () 

Type restricted version of withLockFile.

withLockFile' Source

Arguments

:: (MonadMask m, MonadIO m) 
=> LockingParameters 
-> FilePath

Lock file name.

-> m a 
-> m a 

Version of withLockFile that hides exception witness from its type signature.

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
    -> Throws LockingException m a
lockedDo = withLockFile lockParams lockFile
  where
    lockParams = def
        { retryToAcquireLock = NumberOfTimes 3
        }

    lockFile = withLockExt "/var/lock/my-app"

Constructors

LockingParameters 

Fields

retryToAcquireLock :: !RetryStrategy

Strategy for handling situations when lock-file is already acquired.

sleepBetweenRetires :: !Word64

Sleep interval in microseconds.

Instances

Eq LockingParameters 
Data LockingParameters 
Read LockingParameters 
Show LockingParameters 
Generic LockingParameters 
Default LockingParameters

Defined as:

def = LockingParameters
    { retryToAcquireLock  = def
    , sleepBetweenRetires = 8000000  -- 8 seconds
    }

Sleep interval is inspired by lockfile command line utility that is part of Procmail.

Typeable * LockingParameters 
type Rep LockingParameters 

data RetryStrategy Source

Defines strategy for handling situations when lock-file is already acquired.

Constructors

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 No.

Exceptions

data LockingException Source

Constructors

UnableToAcquireLockFile FilePath

Wasn't able to aquire lock file specified as an argument.

CaughtIOException IOException

IOException occurred while creating or removing lock file.

Utility functions

withLockExt :: FilePath -> FilePath Source

Append default lock file extension. Useful e.g. for generating lock file name out of regular file name.