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

Copyright(c) 2013-2015 2018 Peter Trško
LicenseBSD3
Maintainerpeter.trsko@gmail.com
Stabilityexperimental
PortabilityGHC specific language extensions.
Safe HaskellSafe
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.

{-# 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.

withLockFile Source #

Arguments

:: (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.

withLockFile_ Source #

Arguments

:: (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"

Constructors

LockingParameters 

Fields

Instances

Eq LockingParameters Source # 
Data LockingParameters Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LockingParameters -> c LockingParameters #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LockingParameters #

toConstr :: LockingParameters -> Constr #

dataTypeOf :: LockingParameters -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LockingParameters) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockingParameters) #

gmapT :: (forall b. Data b => b -> b) -> LockingParameters -> LockingParameters #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LockingParameters -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LockingParameters -> r #

gmapQ :: (forall d. Data d => d -> u) -> LockingParameters -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LockingParameters -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LockingParameters -> m LockingParameters #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LockingParameters -> m LockingParameters #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LockingParameters -> m LockingParameters #

Read LockingParameters Source # 
Show LockingParameters Source # 
Generic LockingParameters Source # 
Default LockingParameters Source #

Defined as:

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

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

type Rep LockingParameters Source # 
type Rep LockingParameters = D1 * (MetaData "LockingParameters" "System.IO.LockFile.Internal" "lock-file-0.7.0.0-HyF0nY0IvY2Cpy0LnOwds2" False) (C1 * (MetaCons "LockingParameters" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "retryToAcquireLock") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RetryStrategy)) (S1 * (MetaSel (Just Symbol "sleepBetweenRetries") SourceUnpack SourceStrict DecidedStrict) (Rec0 * Word64))))

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.

Instances

Eq RetryStrategy Source # 
Data RetryStrategy Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RetryStrategy -> c RetryStrategy #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RetryStrategy #

toConstr :: RetryStrategy -> Constr #

dataTypeOf :: RetryStrategy -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RetryStrategy) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RetryStrategy) #

gmapT :: (forall b. Data b => b -> b) -> RetryStrategy -> RetryStrategy #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RetryStrategy -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RetryStrategy -> r #

gmapQ :: (forall d. Data d => d -> u) -> RetryStrategy -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RetryStrategy -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RetryStrategy -> m RetryStrategy #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RetryStrategy -> m RetryStrategy #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RetryStrategy -> m RetryStrategy #

Read RetryStrategy Source # 
Show RetryStrategy Source # 
Generic RetryStrategy Source # 

Associated Types

type Rep RetryStrategy :: * -> * #

Default RetryStrategy Source #

Defined as: def = Indefinitely

Methods

def :: RetryStrategy #

type Rep RetryStrategy Source # 
type Rep RetryStrategy = D1 * (MetaData "RetryStrategy" "System.IO.LockFile.Internal" "lock-file-0.7.0.0-HyF0nY0IvY2Cpy0LnOwds2" False) ((:+:) * (C1 * (MetaCons "No" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Indefinitely" PrefixI False) (U1 *)) (C1 * (MetaCons "NumberOfTimes" PrefixI False) (S1 * (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 * Word8)))))

Exceptions

Utility functions

withLockExt :: FilePath -> FilePath Source #

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