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

[ bsd3, library, system ] [ Propose Tags ]

Provide exclusive access to a resource using lock file, which are files whose purpose is to signal by their presence that some resource is locked.

Code example can be found in System.IO.LockFile module.


[Skip to Readme]

Flags

Manual Flags

NameDescriptionDefault
pedantic

Pass additional warning flags to GHC.

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.5.0.0, 0.5.0.1, 0.5.0.2, 0.7.0.0
Change log ChangeLog.md
Dependencies base (>=4.9 && <5), data-default-class (>=0.0 && <0.2), directory (>=1.1 && <1.4), exceptions (>0.6 && <0.11), transformers (>=0.3 && <0.6) [details]
License BSD-3-Clause
Copyright (c) 2013-2016, 2018 Peter Trško
Author Peter Trsko
Maintainer peter.trsko@gmail.com
Category System
Home page https://github.com/trskop/lock-file#readme
Bug tracker https://github.com/trskop/lock-file/issues
Source repo head: git clone git://github.com/trskop/lock-file.git
this: git clone git://github.com/trskop/lock-file.git(tag 0.7.0.0)
Uploaded by PeterTrsko at 2018-04-15T15:55:35Z
Distributions NixOS:0.7.0.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 3927 total (24 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-04-15 [all 1 reports]

Readme for lock-file-0.7.0.0

[back to package description]

Lock File

Haskell Programming Language BSD3 License

Hackage Build

Description

Provide exclusive access to a resource using lock file, which are files whose purpose is to signal by their presence that some resource is locked.

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
-- Description:  Simple example that acquires lock for a short period of time.
-- Copyright:    (c) 2013, 2014 Peter Trsko
-- License:      BSD3
--
-- Maintainer:   peter.trsko@gmail.com
-- Stability:    experimental
-- Portability:  portable
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 (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
    ( 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.

stack ghc example/example.hs
[1 of 1] Compiling Main             ( example/example.hs, example/example.o )
Linking example/example ...
$ ./example/example & ./example/example
[1] 7893
Locking failed with: Unable to acquire lock file: "/var/run/lock/my-example-lock"
$ [1]+  Done                    ./example/example

PID File Example

Lock file, as implemented by this library, is created containing PID of the process that created it. PID file, on UNIX-like system, is a special case of lock file. It prevents the same daemon to be started up multiple times.

Thanks to the above fact we can now create function with following type signature:

withPidFile :: IO () -> IO ()

Its purpose is to wrap application main and acquire PID file prior to passing control to the application code, or fail if PID file is already acquired.

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Main
  where

import Control.Applicative (pure)
import Control.Concurrent (threadDelay)
import Control.Exception (catch)
import Control.Monad ((>=>), (>>=))
import Data.Function ((.), ($), const)
import Data.Functor ((<$>))
import Data.Monoid ((<>))
import System.Environment (getEnv, getProgName)
import System.Exit (exitFailure)
import System.IO (IO, FilePath, hPutStrLn, putStrLn, stderr)
import Text.Show (show, showString)

import System.Posix.User (getEffectiveUserID)

import Data.Default.Class (def)
import System.IO.LockFile
    ( LockingException(CaughtIOException, UnableToAcquireLockFile)
    , LockingParameters(retryToAcquireLock)
    , RetryStrategy(No)
    , withLockFile
    )


withPidFile :: IO () -> IO ()
withPidFile m = do
    pidFilePath <- mkPidFilePath
    withLockFile def{retryToAcquireLock = No} pidFilePath m
        `catch` (printLockingException pidFilePath >=> const exitFailure)
  where
    mkPidFilePath :: IO FilePath
    mkPidFilePath = do
        fileName <- (<> ".pid") <$> getProgName
        getEffectiveUserID >>= \case
            0 -> pure $ "/var/run/" <> fileName
            _ -> (<> ('/' : '.' : fileName)) <$> getEnv "HOME"
                -- This may throw exception if $HOME environment varialbe is
                -- not set.

    printLockingException :: FilePath -> LockingException -> IO ()
    printLockingException filePath = hPutStrLn stderr . mkMsg . \case
        UnableToAcquireLockFile _ -> "File already exists."
        CaughtIOException       e -> show e
      where
        mkMsg =
            showString filePath . showString ": Unable to create PID file: "

main :: IO ()
main = withPidFile $ do
    putStrLn "Hello World!"
    threadDelay 1000000

Building options

  • -fpedantic (disabled by default)

    Pass additional warning flags to GHC.