[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 System.Process.readProcessWithExitCode function, but following
the advice in the comment for this function, I rolled my own stuff and
ended up writing the following:

 doRunMvnInIO pom args filters e
  = do (Just inh, Just outh, Just errh, pid) -
 createProcess (proc (maven e)  ([-f, pom] ++ args)) { std_in  = 
 CreatePipe,
 std_out = 
 CreatePipe,
 std_err = 
 CreatePipe }
   waitQ - newEmptyMVar

   mapM (printAndWait waitQ)  [outh, errh]

   hClose inh
   -- wait on the process
   waitForProcess pid
 where
   printAndWait waitQ hdl = do out - hGetContents hdl
   forkIO (mapM (putStrLn) (filter filters 
 $ lines out)  putMVar waitQ ())
   takeMVar waitQ
   hClose hdl

This is actually a rewrite of the following function:

 doRunMvnInIO' pom args filters e
  = do (Just inh, Just outh, Just errh, pid) -
 createProcess (proc (maven e)  ([-f, pom] ++ args)) { std_in  = 
 CreatePipe,
 std_out = 
 CreatePipe,
 std_err = 
 CreatePipe }
   waitQ - newEmptyMVar

   mapM (printAndWait waitQ)  [outh, errh] = mapM (\_ - takeMVar waitQ)

   hClose inh
   hClose outh
   hClose errh
   -- wait on the process
   waitForProcess pid
 where
   printAndWait waitQ hdl = do out - hGetContents hdl
   forkIO (mapM (putStrLn) (filter filters 
 $ lines out)  putMVar waitQ ())

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
 - in doRunMvnInIO', this is not true and both theads run concurrently.

but actually there does not seem to be a difference: printing is still
interleaved in both functions, AFAICT.

I would welcome any help on this.
Best regards,
Arnaud
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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.

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 some code
suggestions or pointers to something similar?

Alternatively, is there any way in standard Haskell to define some
kind of union class:

U = (A, B, C, D)

and then using

newtype MyType = MyType Obj deriving U

which would at least be shorter?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 derived by GHC using the

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

feature.

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 some code
suggestions or pointers to something similar?

Alternatively, is there any way in standard Haskell to define some
kind of union class:

U = (A, B, C, D)

and then using

newtype MyType = MyType Obj deriving U

which would at least be shorter?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, 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.

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 some code
suggestions or pointers to something similar?

Alternatively, is there any way in standard Haskell to define some
kind of union class:

U = (A, B, C, D)

and then using

newtype MyType = MyType Obj deriving U

which would at least be shorter?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 Mitrofanov miguelim...@yandex.ru wrote:
   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, 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.

  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 some code
  suggestions or pointers to something similar?

  Alternatively, is there any way in standard Haskell to define some
  kind of union class:

  U = (A, B, C, D)

  and then using

  newtype MyType = MyType Obj deriving U

  which would at least be shorter?
  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 the

 {-# LANGUAGE GeneralizedNewtypeDeriving #-}

 feature.

 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 some code
 suggestions or pointers to something similar?


This works in TH:

 [d|newtype Blah = Blah Int deriving (Num,Show,Eq)|]

But the parameterized variations on this theme do not:

 derive1 name = [d|newtype $name = Blah Int deriving (Num,Show,Eq)|]
Malformed head of type or class declaration

 derive2 name = [d|newtype Blah = $name Int deriving (Num,Show,Eq)|]
parse error in data/newtype declaration

I think it has something to do with the type of the splice. Perhaps you can
look into further:
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/template-haskell.html

Sean
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
  - in doRunMvnInIO', this is not true and both theads run concurrently.

but actually there does not seem to be a difference: printing is still
interleaved in both functions, AFAICT.

   

Hi,

I've tried your code (substituting a program that spits out different 
streams of numbers on stdout and stderr for maven), and I see the 
behaviour you had expected: the first version does print all of stdout 
before stderr, whereas the second version shows interleaving of the two 
streams.  Are you certain that you are seeing interleaving in the first 
version?


Thanks,

Neil.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 expect stdout's content to be printed
 before stderr, ie. the 2 threads are ordered because I call takeMVar
 in between calls to forkIO
  - in doRunMvnInIO', this is not true and both theads run concurrently.

 but actually there does not seem to be a difference: printing is still
 interleaved in both functions, AFAICT.



 Hi,

 I've tried your code (substituting a program that spits out different
 streams of numbers on stdout and stderr for maven), and I see the behaviour
 you had expected: the first version does print all of stdout before stderr,
 whereas the second version shows interleaving of the two streams.  Are you
 certain that you are seeing interleaving in the first version?

 Thanks,

 Neil.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
 return $! StrictMonad x
 StrictMonad v= f = f v
 

It seems to be valid IMHO Functor and Monad (I haven't prove it) as long
as functions terminates.
   


I'm not sure if I'm allowed to use unsafePerformIO in my 
counter-example, but you used it so why not ;-)

The first monad law says: return a = k = k a

let k = const (StrictMonad ())
a = unsafePerformIO launchMissiles

In k a no missiles will be launched, in return a = k, they will be 
launched.  You can construct a similar example against m = return = 
m.  Although, if you changed your definition of bind to:


StrictMonad v = f = return v = f = return

Then as long as return x = return = return x (which it does for you) 
then you automatically satisfy the first two monad laws!  Which is an 
interesting way of solving the problem -- haven't checked the third law 
though.


Thanks,

Neil.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 $ do
   (return $! x) `catch` \(SomeException _) -  return x
   return $! StrictMonad x
   StrictMonad v= f = f v
   
  It seems to be valid IMHO Functor and Monad (I haven't prove it) as long
  as functions terminates.
 
 
 I'm not sure if I'm allowed to use unsafePerformIO in my 
 counter-example, but you used it so why not ;-)
 The first monad law says: return a = k = k a
 
 let k = const (StrictMonad ())
  a = unsafePerformIO launchMissiles
 
 In k a no missiles will be launched, in return a = k, they will be 
 launched.

I guess we enter a grey area - I did use unsafePerformIO but without
side-effects. 

 You can construct a similar example against m = return = 
 m.

Assuming StrictMonad (constructor) is hidden - I don't think so.

 Although, if you changed your definition of bind to:
 
 StrictMonad v = f = return v = f = return
 
 Then as long as return x = return = return x (which it does for you) 
 then you automatically satisfy the first two monad laws!  Which is an 
 interesting way of solving the problem -- haven't checked the third law 
 though.
 

My error.

 Thanks,
 
 Neil.


Regards


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 some code
 suggestions or pointers to something similar?

The solutions first:
-
{-# LANGUAGE TemplateHaskell #-}

module T(mkNewType) where

import Language.Haskell.TH

decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
decl = do
[d] - decls
runIO $ print d -- just to show inetrnals
return d

mkNewType :: String - Q [Dec]
mkNewType n = do
d - decl
let name = mkName n
return $ (\x - [x]) $ case d of
(NewtypeD cxt _ argvars (NormalC _ args) derivings) -
NewtypeD cxt name argvars (NormalC name args) derivings
--
I took perfectly valid declaration, dissected it using case analysis
and changed relevant parts.

And an example client:
-
{-# LANGUAGE TemplateHaskell #-}

import T

$(mkNewType A)
-
It all work together.

I studied how to use Template Haskell that way: I obtained
declarations of what I need, printed them and looked through
documentation for relevant data types and constructors. It's not
harder that any other library in Haskell, actually.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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.

Any ideas?

The CPP solution works but Template Haskell is definitely cooler, so
it would be great to get this to work!

Kevin

On Sep 14, 2:29 pm,  Zefirov sergu...@gmail.com wrote:
 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 some code
  suggestions or pointers to something similar?

 The solutions first:
 -
 {-# LANGUAGE TemplateHaskell #-}

 module T(mkNewType) where

 import Language.Haskell.TH

 decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
 decl = do
         [d] - decls
         runIO $ print d -- just to show inetrnals
         return d

 mkNewType :: String - Q [Dec]
 mkNewType n = do
         d - decl
         let name = mkName n
         return $ (\x - [x]) $ case d of
                 (NewtypeD cxt _ argvars (NormalC _ args) derivings) -
                         NewtypeD cxt name argvars (NormalC name args) 
 derivings
 --
 I took perfectly valid declaration, dissected it using case analysis
 and changed relevant parts.

 And an example client:
 -
 {-# LANGUAGE TemplateHaskell #-}

 import T

 $(mkNewType A)
 -
 It all work together.

 I studied how to use Template Haskell that way: I obtained
 declarations of what I need, printed them and looked through
 documentation for relevant data types and constructors. It's not
 harder that any other library in Haskell, actually.
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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, 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.

 Any ideas?

 The CPP solution works but Template Haskell is definitely cooler, so
 it would be great to get this to work!

 Kevin

 On Sep 14, 2:29 pm,  Zefirov sergu...@gmail.com wrote:

  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 some code
   suggestions or pointers to something similar?

  The solutions first:
  -
  {-# LANGUAGE TemplateHaskell #-}

  module T(mkNewType) where

  import Language.Haskell.TH

  decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
  decl = do
          [d] - decls
          runIO $ print d -- just to show inetrnals
          return d

  mkNewType :: String - Q [Dec]
  mkNewType n = do
          d - decl
          let name = mkName n
          return $ (\x - [x]) $ case d of
                  (NewtypeD cxt _ argvars (NormalC _ args) derivings) -
                          NewtypeD cxt name argvars (NormalC name args) 
  derivings
  --
  I took perfectly valid declaration, dissected it using case analysis
  and changed relevant parts.

  And an example client:
  -
  {-# LANGUAGE TemplateHaskell #-}

  import T

  $(mkNewType A)
  -
  It all work together.

  I studied how to use Template Haskell that way: I obtained
  declarations of what I need, printed them and looked through
  documentation for relevant data types and constructors. It's not
  harder that any other library in Haskell, actually.
  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 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, 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.

 Any ideas?

 The CPP solution works but Template Haskell is definitely cooler, so
 it would be great to get this to work!

 Kevin

 On Sep 14, 2:29 pm,  Zefirov sergu...@gmail.com wrote:

  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 some code
   suggestions or pointers to something similar?

  The solutions first:
  -
  {-# LANGUAGE TemplateHaskell #-}

  module T(mkNewType) where

  import Language.Haskell.TH

  decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
  decl = do
          [d] - decls
          runIO $ print d -- just to show inetrnals
          return d

  mkNewType :: String - Q [Dec]
  mkNewType n = do
          d - decl
          let name = mkName n
          return $ (\x - [x]) $ case d of
                  (NewtypeD cxt _ argvars (NormalC _ args) derivings) -
                          NewtypeD cxt name argvars (NormalC name args) 
  derivings
  --
  I took perfectly valid declaration, dissected it using case analysis
  and changed relevant parts.

  And an example client:
  -
  {-# LANGUAGE TemplateHaskell #-}

  import T

  $(mkNewType A)
  -
  It all work together.

  I studied how to use Template Haskell that way: I obtained
  declarations of what I need, printed them and looked through
  documentation for relevant data types and constructors. It's not
  harder that any other library in Haskell, actually.
  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 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 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, 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.

  Any ideas?

  The CPP solution works but Template Haskell is definitely cooler, so
  it would be great to get this to work!

  Kevin

  On Sep 14, 2:29 pm,  Zefirov sergu...@gmail.com wrote:

   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 some code
suggestions or pointers to something similar?

   The solutions first:
   -
   {-# LANGUAGE TemplateHaskell #-}

   module T(mkNewType) where

   import Language.Haskell.TH

   decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|]
   decl = do
           [d] - decls
           runIO $ print d -- just to show inetrnals
           return d

   mkNewType :: String - Q [Dec]
   mkNewType n = do
           d - decl
           let name = mkName n
           return $ (\x - [x]) $ case d of
                   (NewtypeD cxt _ argvars (NormalC _ args) derivings) -
                           NewtypeD cxt name argvars (NormalC name args) 
   derivings
   --
   I took perfectly valid declaration, dissected it using case analysis
   and changed relevant parts.

   And an example client:
   -
   {-# LANGUAGE TemplateHaskell #-}

   import T

   $(mkNewType A)
   -
   It all work together.

   I studied how to use Template Haskell that way: I obtained
   declarations of what I need, printed them and looked through
   documentation for relevant data types and constructors. It's not
   harder that any other library in Haskell, actually.
   ___
   Haskell-Cafe mailing list
   haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
  ___
  Haskell-Cafe mailing list
  haskell-c...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 =
 (editField1.set) newName -- set field1 to new value
   . editField3 not  -- apply function (not) to field3
   . (editIf field3.editField2.editIf (10)) (1+)
  -- increase field2's value if field2's value  10
  -- and field3 is True

sec also supports functions, lists, Maybe and other monads


Chris Eidhof wrote:
 
 For completeness, using fclabels (yet another record package) you can
 write it like this:
 
 
 {-# LANGUAGE TemplateHaskell #-}
 module Records where
 
 import Data.Record.Label
 
 data MyRecord = MyRecord { _field1 :: String, _field2 :: Int, _field3 ::
 Bool }
 
 $(mkLabels [''MyRecord])
 
 modifyThree f g h = modL field1 f
   . modL field2 g
   . modL field3 h
 
 -chris
 
 On 11 sep 2010, at 19:21, Jonathan Geddes wrote:
 
 I know that record updates is a topic that has become a bit of a dead
 horse, but here I go anyway:
 
 I find that most of the record updates I read and write take the form
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f $ field1 myRecord
, field2 = g $ field2 myRecord
, field3 = h $ filed3 myRecord
}
 
 I find myself wishing I could write something more like
 
 someUpdate :: MyRecord - MyRecord
 someUpdate myRecord = myRecord
{ field1 = f
, field2 = g
, field3 = h
}
 
 with equivalent semantics. Here = reads is transformed by. Operator
 = could still be used for assignment as in current record updates.
 
 The best part about such an extension, in my opinion, is that it would
 open the door for anonymous lambda record updates. Something like:
 
 someUpdate :: MyRecord - MyRecord
 someUpdate = \{field1 = f, field2 = g, field3 = h}
 
 again, with the same semantics. This becomes possible because you no
 longer need to refer to the record within the {} part of the update.
 
 This would be useful, for example, in the State monad. We could write:
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \{field1 = (++!)}
...
 
 where currently we see code like
 
 someStateTransform :: State MyRecord ()
 someStateTransform = do
modify $ \record-record{field1 = (++!) $ field1 record}
...
 
 which repeats the record name 3 times and the field name twice. The
 repetition just feels out of place next to all the other terse,
 readable Haskell code in the program.
 
 So what do my fellow haskellers think? Is this idea worth writing up a
 proposal for?
 
 Alternatively, can you offer me some advice on writing code in Haskell
 2010 that avoids the ugly, repetitive style of record update?
 
 --Jonathan
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://old.nabble.com/record-update-tp29686064p29710821.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 this:


http://research.microsoft.com/en-us/um/people/simonpj/papers/asynch-exns.ps.gz

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 that would handle normal IO exceptions.

Edward
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 that would handle normal IO exceptions.


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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 use threads to gradually force some
data, if it turns out the data won't be needed the threads are killed.
 I've never had a disaster because of it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 termination simply by using appropriate bracketing
 functions that would handle normal IO exceptions.

 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.

That's surprising to me -- this is how we kill the Snap webserver
(killThread the controlling thread...).

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 useful, such as record punning and field
disambiguation.
Since these are already extensions, they're more likely to make it into
Haskell 20XX. Are these considered to be the solution to current record
syntax problems?

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 myRecord{..}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 claim that killThread makes sense outside of
that very narrow context.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 killing main thread again, which
then again kills child threads and interrupt cleanup.

Probably it can be solved with mask:

http://hackage.haskell.org/trac/ghc/ticket/1036

My question is if there is some good code example how to achieve that
before mask is available. The code I wrote in my original post does
not work as intended.


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 by GHC using the
 
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 
 feature.
 
 I would like to use some macro system (perhaps Template Haskell?) to
 reduce this to something like
 
 defObj MyType

How about the straightforward?

 {-# LANGUAGE CPP #-}
 #define defObj(t)   newtype t = t Obj deriving (A,B,C,D)

 defObj(Foo)
 defObj(Bar)
 

It has the advantage of being (de facto) portable.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 a (somewhat) logical sequence
of operations for a graph writer to implement, getting a few freebies
along the way.  There aren't too many extensions or complications.
The most odd thing is the way I arranged the types.  A quick look at
some typesigs should clear up confusion, but:

Node g is the entire node, eg (Int,a)
NodeIndex is just the index eg Int
NodeLabel is just the label eg. athe same for edge.

I'm just fishing for ideas and opinions, and whether or not this seems
simpler to use.

http://codepad.org/UXUL7LZv

{-# LANGUAGE   TypeFamilies
,FlexibleContexts

  #-}

  --TODO: Visitors? DFF searches

import qualified Data.IntMap as I
import Data.List (find,unfoldr,foldl')
import Data.Maybe (fromJust)
import Control.Arrow (second)

class Graph g where
type NodeIndex g
type EdgeIndex g
type Node g --The entire node, including index, any labels and/or data.
type Edge g --ditto
node_index :: g - Node g - NodeIndex g
edge_index :: g - Edge g - EdgeIndex g

empty :: g
isEmpty :: g - Bool
mkGraph :: [Node g] - [Edge g] - g

class Graph g = DirectionalGraph g where
edges_out :: g - NodeIndex g - [Edge g]
source , target :: g - EdgeIndex g - Node g

degree_out :: g - NodeIndex g - Int
degree_out = length ... edges_out

class DirectionalGraph g = BidirectionalGraph g where
edges_in :: g - NodeIndex g - [Edge g]
edges_both :: g - NodeIndex g - [Edge g]
edges_both g n = edges_out g n ++ edges_in g n

degree_in :: g - NodeIndex g - Int
degree_in = length ... edges_in
degree :: g - NodeIndex g - Int
degree g n = degree_out g n + degree_in g n

class Graph g = AdjacencyGraph g where
nodes_out,nodes_in,nodes_both :: g - NodeIndex g - [NodeIndex g]

class Graph g = VertexGraph g where
nodes :: g - [Node g]
node :: g - NodeIndex g - Maybe (Node g)
hasNode :: g - NodeIndex g - Bool
hasNode g n = maybe False (const True) (node g n)
order :: g - Int
order = length . nodes

class Graph g = EdgeGraph g where
edges :: g - [Edge g]
edge :: g - EdgeIndex g - Maybe (Edge g)
hasEdge :: g - EdgeIndex g - Bool
hasEdge g e = maybe False (const True) (edge g e)
size :: g - Int
size = length . edges

class Graph g = MutableGraph g where
insert_node :: Node g - g - g --if preexists, update
remove_node :: NodeIndex g - g - g
insert_edge :: Edge g - g - g --if preexists, update
remove_edge :: EdgeIndex g - g - g

class Graph g = PropertyGraph g where
type NodeLabel g
type EdgeLabel g

node_label :: Node g - NodeLabel g
edge_label :: Edge g - EdgeLabel g

node_labelize :: NodeIndex g - NodeLabel g - Node g
edge_labelize :: EdgeIndex g - EdgeLabel g - Edge g

get_node_label :: g - NodeIndex g - NodeLabel g
get_edge_label :: g - EdgeIndex g - EdgeLabel g

class (VertexGraph g,BidirectionalGraph g,MutableGraph g) =
InductiveGraph g where
data Context g
edgesInC :: Context g - [Edge g]
nodeC :: Context g - Node g
edgesOutC :: Context g - [Edge g]

make_context :: [Edge g] - Node g - [Edge g] - Context g

--minimum definition is match or context, but default works too
context :: g - NodeIndex g - Maybe (Context g)
--context = fmap fst ... match
context g n = dofoundNode - node g n
return $ make_context (edges_in g n) foundNode
(edges_out g n)

match :: g - NodeIndex g - Maybe (Context g,g)
match g n = fmap (flip (,) $ remove_node n g) $ context g n

insert :: Context g - g - g
insert c g = foldr insert_edge g'' (edgesOutC c)
where
g' = insert_node (nodeC c) g
g'' = foldr insert_edge g' (edgesInC c)

toContexts   :: g - [Context g]
toContexts g = unfoldr matchIt (g, map (node_index g) $ nodes g)
  where
matchIt (_,  []) = Nothing
matchIt (g', (n:ns)) = fmap (second (flip (,) ns)) $ match g n

fromContexts :: [Context g] - g
fromContexts = foldr insert empty

adjust   :: (Context g - Context g) - NodeIndex g - g - g
adjust f n g = maybe g (uncurry (insert . f)) $ match g n

gfoldr :: (Context g - b - b) - b - g - b
gfoldr f i = foldr f i . toContexts

gfoldl' :: (b - Context g - b) - b - g - b
gfoldl' f i = foldl' f i . toContexts

gfilter   :: (Context g - Bool) - g - g
gfilter f = fromContexts . filter f . toContexts

class (InductiveGraph g) = MappableGraph g where

gmap   :: InductiveGraph g' = (Context g - Context g') - g - g'
gmap f = fromContexts . map f . toContexts

nmap   :: (InductiveGraph g,Edge g ~ 

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:

http://hackage.haskell.org/package/threads

Regards,

Bas

On Mon, Sep 13, 2010 at 5:32 AM, Mitar mmi...@gmail.com wrote:
 Hi!

 I run multiple threads where I would like that exception from any of
 them (and main) propagate to others but at the same time that they can
 gracefully cleanup after themselves (even if this means not exiting).
 I have this code to try, but cleanup functions (stop) are interrupted.
 How can I improve this code so that this not happen?

 module Test where

 import Control.Concurrent
 import Control.Exception
 import Control.Monad

 thread :: String - IO ThreadId
 thread name = do
  mainThread - myThreadId
  forkIO $ handle (throwTo mainThread :: SomeException - IO ()) $ --
 I want that possible exception in start, stop or run is propagated to
 the main thread so that all other threads are cleaned up
    bracket_ start stop run
      where start = putStrLn $ name ++  started
            stop  = forever $ putStrLn $ name ++  stopped -- I want
 that all threads have as much time as they need to cleanup after
 themselves (closing (IO) resources and similar), even if this means
 not dying
            run   = forever $ threadDelay $ 10 * 1000 * 1000

 run :: IO ()
 run = do
  threadDelay $ 1000 * 1000
  fail exit

 main :: IO ()
 main = do
  bracket (thread foo) killThread $
    \_ - bracket (thread bar) killThread $
      \_ - bracket (thread baz) killThread (\_ - run)


 Mitar
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 possibly
 re-raise an exception that was thrown in or to it:

Thanks. Will look into it.


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 deeper, it looks like some of the record-related ghc
 extensions might also be useful, such as record punning and field
 disambiguation.
 Since these are already extensions, they're more likely to make it into
 Haskell 20XX. Are these considered to be the solution to current record
 syntax problems?
 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 myRecord{..}

or just:

someUpdate :: MyRecord - MyRecord
someUpdate myrec...@myrecord{..} =
myRecord{ field1 = f field1
    , field2 = g field2
        , field3 = h field3
}

Conrad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 is that my main thread then
 kills child threads, which then start killing main thread again, which
 then again kills child threads and interrupt cleanup.


This sounds wrong. Why is the main thread sending more than one kill?
Handlers for some exception shouldn't run more than once unless you
set them up that way.

Are you perhaps being tripped up by the issue whereby when the main
thread dies, the RTS just shuts down even if other threads are
running? You might find you need some kind of maybe MVar-driven
mechanism to keep the main thread alive until all else is definitely
dead.

Maybe this behaviour should be considered a bug, I don't know. It
would be nice if after a forkIO threads were effectively equal.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 myRecord{..}

No, those are recursive let bindings!  If f = (1:), then field1 = [1,1,1,1...]

As Conrad suggests, use:

   someUpdate myRecord@(MyRecord{..}) = myRecord
  { field1 = f field1
  , field2 = f field2
  , field3 = f field3
  }

The reason this works is that field1 in field1 =  is not a real
scoped variable, but rather an identifier for a field in the record.
It's all somewhat subtle...

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 length, and a collection
of random words. So I have
docLength :: IO Int
word :: IO Put

Oh, also
putSpace :: Put

My first attempt:
doc :: IO Put
doc = docLength = go
  where
  go 1 = word
  go n = word  return putSpace  go (n-1)

Unfortunately, with this approach, you end up with a one-word
document. I think this makes sense because of the monad laws, but I
haven't checked it.

Second attempt:
doc :: IO Put
doc = docLength = go
  where
  go 1 = word
  go n = do
w - word
ws - go (n-1)
return (w  putSpace  ws)

This one actually works, but it holds onto everything in memory
instead of outputting as it goes. If docLength tends to be large, this
leads to big problems.

Oh, yes, and my main is currently
main = L.writeFile out.txt = fmap runPut doc

This needs to be lazier so disk writing can start sooner, and to avoid
eating up tons of memory. Any ideas?

Thanks!
Chad
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
 developers have thought really carefully about this:

 
 http://research.microsoft.com/en-us/um/people/simonpj/papers/asynch-exns.ps.gz

 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 that would handle normal IO exceptions.

The point is that killThread throws an exception.  An exception is
usually an error condition.  My approach strictly separates an
unexpected crash from an intended quit.  After all an application
exiting normally shouldn't be an exception (i.e. something unexpected).

Also using the Quit command from my example you can actually wait for
the thread to finish cleanup work.  You can't do this with an exception.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 master thread has a catch handler which
catches the AsyncException generated by the call to killThread. When we
get this, we instruct any service loop threads to exit, and they all
wait for service threads to terminate (currently by sleep-polling a
connections table, which I should probably fix...). Then the master
thread exits by just returning.

Note that I think the main thread being killed kills all threads issue
can be circumvented by using a little gadget like this:


someWorkToDo :: IO ()
someWorkToDo = someStuff `catch` cleanupHandler

main :: IO ()
main = do
mv  - newEmptyMVar
tid - forkIO (someWorkToDo `finally` putMVar mv ())

-- wait on thread to finish; any exception here is probably an
-- AsyncException, so kill the someWorkToDo master thread
-- yourself and wait on the mvar again

takeMVar mv `catch` \(e::SomeException) - do
killThread tid
takeMVar mv


At least, this is what we do in our webserver, and it seems to work
fine -- users complain about the delay involved in our slow cleanup
handler when they ctrl-c the server. :)

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 unexpected crash from an intended quit.

For this you can have multiple types of exceptions, some which signify
error condition and some which signify that user has interrupted a
process and that process should gracefully (exceptionally) quit.

I like exceptions because you can split main logic from exceptional
logic (like user wants to prematurely stop the program). But you still
want to clean up properly everything. Once you have this exceptional
logic in place (and you should always have it as some exceptional
things can always happen) why do not use it also for less exceptional
things (because you have cleaner code then).

 Also using the Quit command from my example you can actually wait for
 the thread to finish cleanup work.  You can't do this with an exception.

You can. If you would have a proper way to mask them:

http://hackage.haskell.org/trac/ghc/ticket/1036


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 sufficient API for visitors already defined.

Cheers,
Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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:

1e8
clang: 0.180s
gcc: 0.179s
ghc 6.12.1 (viac): 0.187s
ghc 6.12.1 (fasm): 0.218s
ghc HEAD (viac): 0.186s
ghc HEAD (fasm): 0.179s
ghc HEAD (llvm): 0.174s

1e9
clang: 1.657s
gcc: 1.647s
ghc 6.12.1 (viac): 1.653s
ghc 6.12.1 (fasm): 1.975s
ghc HEAD (viac): 1.648s
ghc HEAD (fasm): 1.658s
ghc HEAD (llvm): 1.646s

So basically all have the same time except ghc 6.12.1 where fasm is a
little slow.

On windows xp 32bit I get quite different results which I trust less
as the times are jumping around much more then they were on linux:

1e8
gcc: 0.365s
ghc 6.12.1 (viac): 5.287s
ghc 6.12.1 (fasm): 1.332s
ghc HEAD (viac): 5.292s
ghc HEAD (fasm): 0.875s
ghc HEAD (llvm): 0.359s

Not sure why the results on windows are so different. If anyone else
wants to run the two programs on Windows and check that would be
great.

Cheers,
David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
 correctly with thread termination simply by using appropriate bracketing
 functions that would handle normal IO exceptions.


 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.


I don't use killThread, and I write what I'd call somewhat complex
concurrent Haskell software for a living right now :-).

Instead I have a TChan of commands that I can send to a thread, either from
the outside or inside, and that thread will eventually come back to it's
event loop that looks at such messages, and shut down gracefully from there.

Of course the only time this would happen is if something goes wrong and I'm
going to restart and forget all the data I have accumulated thus far anyway.



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 out of curiosity and got the following 
 times.

 Linux, 64bit, Ubuntu 10.10:

 1e8
 clang: 0.180s
 gcc: 0.179s
 ghc 6.12.1 (viac): 0.187s
 ghc 6.12.1 (fasm): 0.218s
 ghc HEAD (viac): 0.186s
 ghc HEAD (fasm): 0.179s
 ghc HEAD (llvm): 0.174s

 1e9
 clang: 1.657s
 gcc: 1.647s
 ghc 6.12.1 (viac): 1.653s
 ghc 6.12.1 (fasm): 1.975s
 ghc HEAD (viac): 1.648s
 ghc HEAD (fasm): 1.658s
 ghc HEAD (llvm): 1.646s

 So basically all have the same time except ghc 6.12.1 where fasm is a
 little slow.

 On windows xp 32bit I get quite different results which I trust less
 as the times are jumping around much more then they were on linux:

Thanks for your rather extensive effort to pin down the performance
numbers. I just wanted to add a suggestion: I would highly recommend
using criterion for this.  It's easy, simple, and good at giving you
statistically robust measures of the time it takes.

http://hackage.haskell.org/package/criterion

I resisted using it for a while, but once I took the plunge I was
quite happy with the results.  It's a library that is definitely worth
the spin up time (for me at least).

Jason
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#ReferenceGuide
http://book.realworldhaskell.org/read/using-parsec.html
http://lstephen.wordpress.com/2007/06/19/first-go-with-parsec/
http://jonathan.tang.name/files/scheme_in_48/tutorial/overview.html
http://www.defmacro.org/ramblings/lisp-in-haskell.html

I'm having trouble coding a simple parser to count the number of
lines in a text file.

lineCount fails to compile; the compiler error text is below it.

Any advice, code, etc. would be appreciated.

For those using Gtk2Hs + Glade, I have included the glade file after
the Haskell code, in case you want to try it. (You will need to
remove the leading   and fix some lines that the email wrapped.)

If you do wish to offer code, feel free to remove or rewrite: eol,
textLines and lineCount entirely. I'm looking for the simplest
way to code this.

Thanks very much,
-- Peter



 -- A parsing demo, using:
 -- Haskell + Gtk2Hs + Glade (GtkBuilder) + Parsec
 module Main where

 -- import Data.IORef
 import Graphics.UI.Gtk
 import Graphics.UI.Gtk.Builder
 import Graphics.UI.Gtk.Selectors.FileChooser
 -- import System.Cmd  -- e.g., for invoking a shell cmd
 import System.Glib.GError
 import Text.ParserCombinators.Parsec

 main :: IO ()
 main = do
initGUI

-- create builder; load UI file
builder - builderNew
handleGError (\(GError dom code msg) - fail msg) $
   builderAddFromFile builder demo.glade
   -- Error message would look something like:
   -- app.exe: user error (Failed to open file 'app.glade':
   --No such file or directory)

-- get widget handles   (reduce boilerplate?)
mainWindow - builderGetObject builder castToWindow mainWindow
pickFileButton -
   builderGetObject builder castToFileChooserButton pickFileButton
parseButton- builderGetObject builder castToButton parseButton
exitButton - builderGetObject builder castToButton exitButton

-- signal handlers --

-- parse selected file
onClicked parseButton $ do
   file - fileChooserGetFilename pickFileButton

   case file of
  Nothing - do
 putStrLn \nPlease first select a file.
 return ()
  Just file - do
 putStrLn $ \nParsing file:  ++ show file
 result - parseFromFile lineCount file
 case (result) of
Left err - print err
Right x - putStrLn $ Line count =  ++ show x
 return ()

-- exit
onDestroy mainWindow mainQuit
onClicked exitButton mainQuit

-- go
widgetShowAll mainWindow
mainGUI

 -
 eol = char '\n'

 --  from RWH; perhaps use in future:
 -- eol =   try (string \n\r)
 -- | try (string \r\n)
 -- | string \n
 -- | string \r
 -- ? end of line

 textLines = endBy eol

 lineCount :: Parser Int
 lineCount = do
xs - textLines
return (length xs)


 -- demo.hs:72:3:
 -- Couldn't match expected type `GenParser Char () Int'
 --against inferred type `GenParser Char st sep - b'
 -- In a stmt of a 'do' expression: xs - textLines
 -- In the expression:
 -- do { xs - textLines;
 --  return (length xs) }
 -- In the definition of `lineCount':
 -- lineCount = do { xs - textLines;
 --  return (length xs) }


-- demo.glade follows --

 ?xml version=1.0?
 interface
   requires lib=gtk+ version=2.16/
   !-- interface-naming-policy project-wide --
   object class=GtkWindow id=mainWindow
 property name=visibleTrue/property
 property name=title translatable=yesdemo v.8/property
 child
   object class=GtkVBox id=vbox1
 property name=visibleTrue/property
 property name=border_width6/property
 property name=orientationvertical/property
 property name=spacing10/property
 child
   object class=GtkLabel id=label1
 property name=visibleTrue/property
 property name=tooltip_text translatable=yesYou can hover 
 over the buttons below for some information about them.

 You can also resize this window, to make the buttons bigger.
 /property
 property name=label translatable=yesDemo: Haskell + Gtk2Hs 
 + Glade (GtkBuilder) + Parsec
 /property
   /object
   packing
 property name=position0/property
   /packing
 /child
 child
   object class=GtkHBox id=hbox1
 property name=visibleTrue/property
 property name=spacing5/property
 child
   object class=GtkFrame id=pickFileframe
 property name=visibleTrue/property
 property name=tooltip_text 

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:

 http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#UserGuide
 http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#ReferenceGuide
 http://book.realworldhaskell.org/read/using-parsec.html
 http://lstephen.wordpress.com/2007/06/19/first-go-with-parsec/
 http://jonathan.tang.name/files/scheme_in_48/tutorial/overview.html
 http://www.defmacro.org/ramblings/lisp-in-haskell.html

 I'm having trouble coding a simple parser to count the number of
 lines in a text file.

 lineCount fails to compile; the compiler error text is below it.

 Any advice, code, etc. would be appreciated.

 For those using Gtk2Hs + Glade, I have included the glade file after
 the Haskell code, in case you want to try it. (You will need to
 remove the leading   and fix some lines that the email wrapped.)

 If you do wish to offer code, feel free to remove or rewrite: eol,
 textLines and lineCount entirely. I'm looking for the simplest
 way to code this.

 Thanks very much,
 -- Peter


What do you expect the type of 'textLines' to be? Does the error
change if you add a type annotation to 'textLines'?

Adding more type signatures is my usual first step in understanding
bewildering error messages.

In this case, I think the issue is that the 'emdBy' function from
Parsec expect two arguments[1], and you have only give it one. You've
written the 'separator' parser, but you also need to specify what to
parse between the separators.

If this is as complex as the task is, you may be better off with the
function Prelude.lines[2] :-)

Take care,
Antoine

[1] 
http://hackage.haskell.org/packages/archive/parsec/3.1.0/doc/html/Text-Parsec-Combinator.html#v:endBy

[2] 
http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Prelude.html#v:lines
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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?

  My approach strictly separates an unexpected crash from an intended
 quit.

 For this you can have multiple types of exceptions, some which signify
 error condition and some which signify that user has interrupted a
 process and that process should gracefully (exceptionally) quit.

 I like exceptions because you can split main logic from exceptional
 logic (like user wants to prematurely stop the program). But you still
 want to clean up properly everything. Once you have this exceptional
 logic in place (and you should always have it as some exceptional
 things can always happen) why do not use it also for less exceptional
 things (because you have cleaner code then).

The problem with exceptions is that Haskell's type system doesn't really
capture them.  A function raising an exception is semantically
equivalent to a function, which recurses forever.  On the other hand a
well-typed abortion using the ContT monad transformer /is/ captured by
the type system and hence can be stated and type-checked explicitly.

Exceptions are side effects in Haskell.  That's why an exception is
semantically equivalent to a crash, hence my wording.


  Also using the Quit command from my example you can actually wait
  for the thread to finish cleanup work.  You can't do this with an
  exception.

 You can. If you would have a proper way to mask them:

 http://hackage.haskell.org/trac/ghc/ticket/1036

Even if you could mask them exception throwing and catching is outside
of Haskell's type system.  They're still an IO side effect.

And also there is nothing wrong with using ContT.  It doesn't make the
code any more complicated and very likely even less.  See my example.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 like to ask to perhaps solve my
 wonder. From time to time I'm seeing people here recommending Scala as a
 kind of replacement for non-existent Haskell on Java/JVM platform. My
 wonder is: why the people here do not recommend CAL, which at least to
 me, looks much more closer to Haskell than Scala is. Are there any bad
 experiences with this language and OpenQuark platform? I'm asking since
 I'm currently playing with it and plan to use it for java objects data
 processing.
 
 Thanks,
 Karel
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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!

You can use the threads library which correctly abstracts over this pattern:

http://hackage.haskell.org/package/threads

Regards,

Bas

On Wed, Sep 15, 2010 at 2:23 AM, Gregory Collins
g...@gregorycollins.net wrote:
 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 master thread has a catch handler which
 catches the AsyncException generated by the call to killThread. When we
 get this, we instruct any service loop threads to exit, and they all
 wait for service threads to terminate (currently by sleep-polling a
 connections table, which I should probably fix...). Then the master
 thread exits by just returning.

 Note that I think the main thread being killed kills all threads issue
 can be circumvented by using a little gadget like this:

 
    someWorkToDo :: IO ()
    someWorkToDo = someStuff `catch` cleanupHandler

    main :: IO ()
    main = do
        mv  - newEmptyMVar
        tid - forkIO (someWorkToDo `finally` putMVar mv ())

        -- wait on thread to finish; any exception here is probably an
        -- AsyncException, so kill the someWorkToDo master thread
        -- yourself and wait on the mvar again

        takeMVar mv `catch` \(e::SomeException) - do
            killThread tid
            takeMVar mv
 

 At least, this is what we do in our webserver, and it seems to work
 fine -- users complain about the delay involved in our slow cleanup
 handler when they ctrl-c the server. :)

 G
 --
 Gregory Collins g...@gregorycollins.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 installed leaving
 your main thread in a dead-lock!

Good catch, thank you,

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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.

Kevin

On Sep 14, 11:01 pm, John Meacham j...@repetae.net wrote:
 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 by GHC using the

  {-# LANGUAGE GeneralizedNewtypeDeriving #-}

  feature.

  I would like to use some macro system (perhaps Template Haskell?) to
  reduce this to something like

  defObj MyType

 How about the straightforward?

  {-# LANGUAGE CPP #-}
  #define defObj(t)   newtype t = t Obj deriving (A,B,C,D)

  defObj(Foo)
  defObj(Bar)
  

 It has the advantage of being (de facto) portable.

         John

 --
 John Meacham - ⑆repetae.net⑆john⑈ -http://notanumber.net/
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 to not be surprised later.

Also note that the threads library correctly unblocks asynchronous
exceptions when necessary.

Regards,

Bas

[1] http://hackage.haskell.org/trac/ghc/ticket/4035

On Wed, Sep 15, 2010 at 7:38 AM, Gregory Collins
g...@gregorycollins.net wrote:
 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 installed leaving
 your main thread in a dead-lock!

 Good catch, thank you,

 G
 --
 Gregory Collins g...@gregorycollins.net

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe