[Haskell-cafe] Question on concurrency

2010-09-14 Thread Arnaud Bailly
Hello Haskellers, Having been pretty much impressed by Don Stewart's Practical Haskell (http://donsbot.wordpress.com/2010/08/17/practical-haskell/), I started to write a Haskell script to run maven jobs (yes, I know...). In the course of undertaking this fantastic endeavour, I started to use the

[Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically derived by GHC using the {-# LANGUAGE GeneralizedNewtypeDeriving #-} feature.

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Miguel Mitrofanov
class (A x, B x, C x, D x) = U x ? 14.09.2010 12:24, Kevin Jardine пишет: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Miguel Mitrofanov
Sorry, got stupid today. Won't help. 14.09.2010 12:29, Miguel Mitrofanov пишет: class (A x, B x, C x, D x) = U x ? 14.09.2010 12:24, Kevin Jardine пишет: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B,

[Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
I supposed the simple solution might be CPP: #define defObj(NAME) newtype NAME = NAME Obj deriving (A,B,C,D) and then use defObj (MyType) I have heard some people, however, say that CPP macros are horrible in Haskell, so is there a better solution? Kevin On Sep 14, 10:34 am, Miguel

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Sean Leather
On Tue, Sep 14, 2010 at 10:24, Kevin Jardine wrote: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically derived by GHC using

Re: [Haskell-cafe] Question on concurrency

2010-09-14 Thread Neil Brown
On 14/09/10 07:45, Arnaud Bailly wrote: What surprised me is that I would expect the behaviour of the two functions to be different: - in doRunMvnInIO, I would expect stdout's content to be printed before stderr, ie. the 2 threads are ordered because I call takeMVar in between calls to forkIO

Re: [Haskell-cafe] Question on concurrency

2010-09-14 Thread Arnaud Bailly
Probably did not test enough. Sorry for the noise. arnaud On Tue, Sep 14, 2010 at 12:18 PM, Neil Brown nc...@kent.ac.uk wrote: On 14/09/10 07:45, Arnaud Bailly wrote: What surprised me is that I would expect the behaviour of the two functions to be different:  - in doRunMvnInIO, I would

Re: [Haskell-cafe] Full strict functor by abusing Haskell exceptions

2010-09-14 Thread Neil Brown
On 13/09/10 17:25, Maciej Piechotka wrote: import Control.Exception import Foreign import Prelude hiding (catch) data StrictMonad a = StrictMonad a deriving Show instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) - return x

Re: [Haskell-cafe] Full strict functor by abusing Haskell exceptions

2010-09-14 Thread Maciej Piechotka
On Tue, 2010-09-14 at 11:27 +0100, Neil Brown wrote: On 13/09/10 17:25, Maciej Piechotka wrote: import Control.Exception import Foreign import Prelude hiding (catch) data StrictMonad a = StrictMonad a deriving Show instance Monad StrictMonad where return x = unsafePerformIO $

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Serguey Zefirov
2010/9/14 Kevin Jardine kevinjard...@gmail.com: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like defObj MyType I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has

[Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
Thanks Serguey! The library code compiles, but when I try to use it in client code: a. I get: Not in scope: type constructor or class 'A' and even stranger, b. GHC cannot find any of my code after the $(mkNewType A) and claims that all the functions I defined there are also not in scope.

[Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
Hmm - It seems to work if the code is defined before my main function and not after it. Does this have to do with TH being part of the compile process and so the order matters? Kevin On Sep 14, 6:03 pm, Kevin Jardine kevinjard...@gmail.com wrote: Thanks Serguey! The library code compiles,

Re: [Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Erik Hesselink
Yes, if you use template haskell, all top level functions and values have to be defined before you use them. Erik On Tue, Sep 14, 2010 at 18:11, Kevin Jardine kevinjard...@gmail.com wrote: Hmm - It seems to work if the code is defined before my main function and not after it. Does this have

[Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
OK, thanks for everyone's help! Serguey's code works very well now. Kevin On Sep 14, 6:14 pm, Erik Hesselink hessel...@gmail.com wrote: Yes, if you use template haskell, all top level functions and values have to be defined before you use them. Erik On Tue, Sep 14, 2010 at 18:11, Kevin

Re: re[Haskell-cafe] cord update

2010-09-14 Thread -Steffen
While we are at it using Semantic Editor Combinators (sec on hackage): {-# LANGUAGE TemplateHaskell #-} module T where import Data.SemanticEditors data MyRecord = MyRecord { field1 :: String, field2 :: Int, field3 :: Bool } deriving(Show) mkEditors [''MyRecord] editRecord str =

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Edward Z. Yang
Excerpts from Ertugrul Soeylemez's message of Mon Sep 13 03:03:11 -0400 2010: In general it's better to avoid using killThread. There are much cleaner ways to tell a thread to exit. This advice doesn't really apply to Haskell: in fact, the GHC developers have thought really carefully about

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Bryan O'Sullivan
On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang ezy...@mit.edu wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread termination simply by using appropriate bracketing functions

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Evan Laforge
Ertugrul's advice is still correct. I'd wager there are very few concurrent applications that could survive a killThread without disaster. People simply don't write or test code with that in mind, and even when they do, it's more likely than not to be wrong. Does this apply to pure code? I

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Gregory Collins
Bryan O'Sullivan b...@serpentine.com writes: On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang ezy...@mit.edu wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact correctly with thread

Re: [Haskell-cafe] record update

2010-09-14 Thread Jonathan Geddes
Wow, I had no idea there were so many record packages! This indicates a couple things to me: a) Haskell is very flexible. b) I'm not the only one who things the built-in record system isn't perfect. Digging a bit deeper, it looks like some of the record-related ghc extensions might also be

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Bryan O'Sullivan
On Tue, Sep 14, 2010 at 12:04 PM, Gregory Collins g...@gregorycollins.netwrote: That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...). It's one thing to design code to work that way and test it all the time, but it would be quite another to

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Mitar
Hi! On Tue, Sep 14, 2010 at 9:04 PM, Gregory Collins g...@gregorycollins.net wrote: That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...). Yes. This does work. The only problem is that my main thread then kills child threads, which then start

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread John Meacham
On Tue, Sep 14, 2010 at 01:24:16AM -0700, Kevin Jardine wrote: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically derived

[Haskell-cafe] copy of boost graph library

2010-09-14 Thread Thomas Bereknyei
I was looking around and liked some of the ways that Boost organizes its libraries. So it got me thinking that it might be easy to use the same for a Haskell graph library. This IS NOT FGL, but does include some elements of it at the end (InductiveGraph). Mostly what I like, is that it presents

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Bas van Dijk
Note that killing the main thread will also kill all other threads. See: http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-Concurrent.html#11 You can use my threads library to wait on a child thread and possibly re-raise an exception that was thrown in or to it:

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Mitar
Hi! On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk v.dijk@gmail.com wrote: Note that killing the main thread will also kill all other threads. See: Yes. But how does those other threads have time to cleanup is my question. You can use my threads library to wait on a child thread and

Re: [Haskell-cafe] record update

2010-09-14 Thread Conrad Parker
On 15 September 2010 04:31, Jonathan Geddes geddes.jonat...@gmail.com wrote: Wow, I had no idea there were so many record packages! This indicates a couple things to me: a) Haskell is very flexible. b) I'm not the only one who things the built-in record system isn't perfect. Digging a bit

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Ben Millwood
On Tue, Sep 14, 2010 at 9:44 PM, Mitar mmi...@gmail.com wrote: Hi! On Tue, Sep 14, 2010 at 9:04 PM, Gregory Collins g...@gregorycollins.net wrote: That's surprising to me -- this is how we kill the Snap webserver (killThread the controlling thread...). Yes. This does work. The only problem

Re: [Haskell-cafe] record update

2010-09-14 Thread Luke Palmer
On Tue, Sep 14, 2010 at 1:31 PM, Jonathan Geddes geddes.jonat...@gmail.com wrote: With these extensions, couldn't I write the following? someUpdate :: MyRecord - MyRecord someUpdate myRecord@(MyRecord{..}) = let     { field1 = f field1     , field2 = g field2     , field3 = h filed3     } in

[Haskell-cafe] IO Put confusion

2010-09-14 Thread Chad Scherrer
Hello, I need to be able to use strict bytestrings to efficiently build a lazy bytestring, so I'm using putByteString in Data.Binary. But I also need random numbers, so I'm using mwc-random. I end up in the IO Put monad, and it's giving me some issues. To build a random document, I need a random

[Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Ertugrul Soeylemez
Edward Z. Yang ezy...@mit.edu wrote: Excerpts from Ertugrul Soeylemez's message of Mon Sep 13 03:03:11 -0400 2010: In general it's better to avoid using killThread. There are much cleaner ways to tell a thread to exit. This advice doesn't really apply to Haskell: in fact, the GHC

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Gregory Collins
Mitar mmi...@gmail.com writes: Hi! On Tue, Sep 14, 2010 at 11:46 PM, Bas van Dijk v.dijk@gmail.com wrote: Note that killing the main thread will also kill all other threads. See: Yes. But how does those other threads have time to cleanup is my question. What we do in Snap is this: the

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Mitar
Hi! On Wed, Sep 15, 2010 at 2:16 AM, Ertugrul Soeylemez e...@ertes.de wrote: The point is that killThread throws an exception.  An exception is usually an error condition. This is reasoning based on nomenclature. If exceptions were named Signal or Interrupt?  My approach strictly separates an

Re: [Haskell-cafe] copy of boost graph library

2010-09-14 Thread Jason Dagit
On Tue, Sep 14, 2010 at 2:12 PM, Thomas Bereknyei tombe...@gmail.com wrote:  --TODO: Visitors? DFF searches I don't feel qualified to comment on much in your email, but this todo gave me pause: http://www.mail-archive.com/haskell-cafe@haskell.org/msg60468.html I think you might have a

Re: [Haskell-cafe] benchmarking c/c++ and haskell

2010-09-14 Thread David Terei
On 13 September 2010 20:41, Vo Minh Thu not...@gmail.com wrote: ... the post is from 2008. No LLVM goodness. So I thought GHC 6.12.1 (not the latest and greatest HEAD) would be enough. I compiled the two programs myself out of curiosity and got the following times. Linux, 64bit, Ubuntu 10.10:

Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread David Leimbach
On Tue, Sep 14, 2010 at 11:29 AM, Bryan O'Sullivan b...@serpentine.comwrote: On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang ezy...@mit.edu wrote: Pure code can always be safely asynchronously interrupted (even code using state like the ST monad), and IO code can be made to interact

Re: [Haskell-cafe] benchmarking c/c++ and haskell

2010-09-14 Thread Jason Dagit
On Tue, Sep 14, 2010 at 5:50 PM, David Terei dave.te...@gmail.com wrote: On 13 September 2010 20:41, Vo Minh Thu not...@gmail.com wrote: ... the post is from 2008. No LLVM goodness. So I thought GHC 6.12.1 (not the latest and greatest HEAD) would be enough. I compiled the two programs myself

[Haskell-cafe] Simple Parsec example, question

2010-09-14 Thread Peter Schmitz
Simple Parsec example, question I am learning Parsec and have been studying some great reference and tutorial sites I have found (much thanks to the authors), including: http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#UserGuide

Re: [Haskell-cafe] Simple Parsec example, question

2010-09-14 Thread Antoine Latter
Hi Peter, On Tue, Sep 14, 2010 at 8:23 PM, Peter Schmitz ps.hask...@gmail.com wrote: Simple Parsec example, question I am learning Parsec and have been studying some great reference and tutorial sites I have found (much thanks to the authors), including:

[Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Ertugrul Soeylemez
Mitar mmi...@gmail.com wrote: On Wed, Sep 15, 2010 at 2:16 AM, Ertugrul Soeylemez e...@ertes.de wrote: The point is that killThread throws an exception.  An exception is usually an error condition. This is reasoning based on nomenclature. If exceptions were named Signal or Interrupt?  

Re: [Haskell-cafe] CAL experience

2010-09-14 Thread Tom Davies
I use CAL for various hobby projects, and despite development being quiet I find it robust. I suspect that the lack of extensions over Haskell 98 puts some people off. Tom On 10/09/2010, at 5:31 AM, Karel Gardas karel.gar...@centrum.cz wrote: Hello, as this is really friendly forum, I'd

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Bas van Dijk
Don't forget to block asynchronous exception _before_ you fork in:        tid - forkIO (someWorkToDo `finally` putMVar mv ()) Otherwise an asynchronous exception might be thrown to the thread _before_ the 'putMVar mv ()' exception handler is installed leaving your main thread in a dead-lock!

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Gregory Collins
Bas van Dijk v.dijk@gmail.com writes: Don't forget to block asynchronous exception _before_ you fork in:        tid - forkIO (someWorkToDo `finally` putMVar mv ()) Otherwise an asynchronous exception might be thrown to the thread _before_ the 'putMVar mv ()' exception handler is

[Haskell-cafe] Re: Scraping boilerplate deriving?

2010-09-14 Thread Kevin Jardine
Hi John, That's what I had originally. However, some people have made critical comments about CPP macros on this list and I thought that TH was considered the better option. What do other people think? Serguey's code is great in any case as it gives me a clearer understanding on how TH works.

Re: [Haskell-cafe] Cleaning up threads

2010-09-14 Thread Bas van Dijk
Also don't forget to unblock asynchronous exceptions inside 'someWorkToDo' otherwise you can't throw exceptions to the thread. Note that 'finally' unblocks asynchronous exceptions but I consider this a bug. In the upcoming base library this is fixed[1] but I would advise to fix the code right now