[Haskell-beginners] STM and IO

Chris G cgrebeld at gmail.com
Thu Apr 9 13:56:23 EDT 2009


Since the file handle is closed after you read the contents, you need to
open a new one before writing to it.

On Thu, Apr 9, 2009 at 12:20 PM, emmanuel.delaborde <
emmanuel.delaborde at cimex.com> wrote:

>
> From: Quentin Moser <quentin.moser at unifr.ch>
> Subject: Re: [Haskell-beginners] STM and IO
>
> Your problem has nothing to do with lazyness; Haskell simply kills all
> other threads when the main thread returns from main. You have to
> somehow wait for them to complete in main or they won't have time to
> run.
>
>
> Doh!
> I've been bitten before...
>
> Now onto the second problem: ignore me if I'm wrong, but it seems your
> intent is to spawn 10 threads that will each try to run (writeTo store)
> once. What your current code does is spawn one thread that sequentially
> runs writeTo 10 times.
>
>
> yes you are right of course
>
> Note: I haven't tried running any of this code, but it seems simple
> enough to be confident in.
>
>
> I had to make a change to myFork to get it to compile, here's what I have
> now:
>
> module Main where
>
> import Control.Monad
> import Control.Concurrent
> import Control.Concurrent.STM
> import System.IO
> import Control.Exception (finally)
>
> myFork :: IO () -> IO (MVar ())
> myFork a = do
>   v <- newEmptyMVar
>   a `finally` (putMVar v ())
>   return v -- to honor the return type
>
> myWait :: MVar () -> IO ()
> myWait = readMVar
>
> main = do
>    let fname = "store.txt"
>    fh <- openFile fname ReadWriteMode
>    store <- atomically $ newTMVar fh
>    waitMes <- 10 `replicateM` (myFork $ writeTo store)
>    mapM_ myWait waitMes
>
> writeTo :: TMVar (Handle) -> IO ()
> writeTo store = do
>    fh <- atomically $ takeTMVar store
>    text <- hGetContents fh
>    hPutStr fh (text ++ " some text ")
>    atomically $ putTMVar store fh
>
> Now I get the following error : test3: store.txt: hPutStr: illegal
> operation (handle is closed)
>
> reading the doc about hGetContents, I found that  : "Computation
> hGetContents hdl returns the list of characters corresponding to the unread
> portion of the channel or file managed by hdl, which is put into an
> intermediate state, semi-closed. In this state, hdl is effectively closed"
>
>
> Intuitively I'd want to write something like
> : writeTo filename = atomically (do { s <- readFile filename ;
> writeFile filename (s ++ "blah") })
> but the type system prevents me from doing IO within STM
> I do not know how to go about sharing access to a file between multiple
> threads using STM... any pointers ?
>
> Thanks
>
> E.
>
>
>
>
>
>
>
>
>
> --
> Emmanuel Delaborde
> Web Technologist
> Cimex
> 53-55 Scrutton Street, London UK, EC2A 4PJ
> T: +44 (0)20 7324 7780
> F: +44 (0)20 7324 7781
> http://www.cimex.com
>
> -----------------------------------------------------------------------------------------------
>
> This e-mail (and any attachments) is confidential and may contain
> personal views which are not the views of Cimex Media Ltd and
> any affiliated companies, unless specifically stated. It is intended
> for the use of the individual or group to whom it is addressed. If
> you have received it in error, please delete it from your system,
> do not use, copy or disclose the information in any way nor act in
> reliance on it and please notify postmaster at cimex.com
>
> A company registered in England  Wales. Company Number 03765711
> Registered Office : The Olde Bakehouse, 156 Watling Street East, Towcester,
> Northants NN12 6DB
>
> This email was scanned by Postini, the leading provider in Managed Email Security.
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090409/d8a52eba/attachment-0001.htm


More information about the Beginners mailing list