[Haskell-cafe] File locking wishlist

Joachim Breitner mail at joachim-breitner.de
Mon Jun 9 16:57:38 EDT 2008


Hi again,

Am Donnerstag, den 05.06.2008, 17:22 +0200 schrieb Joachim Breitner:
> Hi,
> 
> for a program of mine (darcswatch[1]), a rather long running process is
> run at certain events (by cron, and by new emails). I want to achieve
> that:
>  * Only one instance of the program runs at a time.
>  * If new events come in while the program runs, it should re-run itself
>  * There is information attached to the events (only one Bool ATM)
> 
> So I’d like to implement something with this, or a similar, interface:
> 
> =======================================================================
> module MyLocking where
> 
> -- | tries to get the lock. If it fails, notifies the running process
> --   to re-start itself afterwards, with the given information
> --   returns True if the lock was aquired
> lockOrMark :: Show a => FilePath -> a -> IO Bool
> 
> -- | release the lock. If new events have come in, they are returned
> --   in the list, and the lock is still kept. If the list is empty,
> --   the lock was successfully released.
> releaseLock :: Read a => FilePath -> IO [a]
> =======================================================================

I wrote a module that provides this API. It can be found here:
http://darcs.nomeata.de/darcswatch/src/LockRestart.hs

I use it for darcswatch, you can see the relevant change here:
http://darcs.nomeata.de/cgi-bin/darcsweb.cgi?r=darcswatch;a=filediff;h=20080609203612-23c07-aec8c4e1f22a9c3bdd44d062ab26f7d18a880a18.gz;f=src/Main.hs

Actually, since only the call to "or" in the third changed line from the
bottom is special to darcswatch, this can be moved into LockRestart, so
the change to the program is reduced to this:

         config <- read `fmap` readFile (confdir ++ "config")
+
+	 lockRestart (cOutput config) patchNew or True (do_work config)
+
+do_work config patchNew = do
         putStrLn "Reading repositories..."

or even

         config <- read `fmap` readFile (confdir ++ "config")
+
+	 lockRestart (cOutput config) patchNew or True $ \patchNew -> do
+       
         putStrLn "Reading repositories..."

if you prefer.


Enjoy,
Joachim Breitner


-- 
Joachim Breitner
  e-Mail: mail at joachim-breitner.de
  Homepage: http://www.joachim-breitner.de
  ICQ#: 74513189
  Jabber-ID: nomeata at joachim-breitner.de
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 197 bytes
Desc: Dies ist ein digital signierter Nachrichtenteil
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20080609/49ba5360/attachment.bin


More information about the Haskell-Cafe mailing list