RE: [Haskell-cafe] Re: :t main

2005-12-06 Thread David Menendez
I wrote:
> | My guess is that comonadic IO would look more like dataflow
> | programming.

Simon Peyton-Jones writes:

> I've not been following this thread, but I wanted to check: you do
> know about Tarmo Uustalu's stuff about comonads, don't you?
> 
> http://www.cs.helsinki.fi/u/ekarttun/comonad/  summarises (link to
> "The essence of dataflow programming" at the bottom)

You caught me. That paper was the reason I thought comonadic IO might
resemble dataflow programming. I should have provided a link, but I was
lazy.

I also recommend "Comonadic functional attribute evaluation"[1] and "The
dual of substitution is redecoration"[2], which have nothing to do with
IO but do describe some applications of comonads.

[1] 
[2] 
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] FFI in threaded mode (was Re: New runtime crash, not sure what to make of it)

2005-12-06 Thread Joel Reymont
The program runs fine in non-threaded mode, including from within  
ghci. The crash below hapens when using -threaded.


I tried to come up with a repro case but could not reproduce the crash.

Thanks, Joel

On Dec 7, 2005, at 12:51 AM, Joel Reymont wrote:

Program compiled with -threaded on Mac OSX. Crash happens when  
waiting in select, I think.


Program received signal EXC_BAD_ACCESS, Could not access memory.
Reason: KERN_PROTECTION_FAILURE at address: 0x
[Switching to process 832 thread 0x2303]
0x0011ce20 in stg_enter_info ()
(gdb) where
#0  0x0011ce20 in stg_enter_info ()
#1  0x00170e7c in StgRunIsImplementedInAssembler ()
#2  0x001247a4 in schedule ()
#3  0x00124468 in taskStart ()
#4  0x0017f800 in startProcWrapper ()
#5  0x9002b200 in _pthread_body ()


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Einar Karttunen
On 06.12 20:57, Tomasz Zielonka wrote:
> On Tue, Dec 06, 2005 at 02:52:03PM +, Joel Reymont wrote:
> > Well, I do need to have access to all those thread handles.

Since thread creation is inside IO anyways you might want to
look at Control.Concurrent.QSem which solves this in an
easy fashion. If you want to use STM then a global 
TVar Int should work fine.

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


[Haskell-cafe] New runtime crash, not sure what to make of it

2005-12-06 Thread Joel Reymont
Program compiled with -threaded on Mac OSX. Crash happens when  
waiting in select, I think.


Program received signal EXC_BAD_ACCESS, Could not access memory.
Reason: KERN_PROTECTION_FAILURE at address: 0x
[Switching to process 832 thread 0x2303]
0x0011ce20 in stg_enter_info ()
(gdb) where
#0  0x0011ce20 in stg_enter_info ()
#1  0x00170e7c in StgRunIsImplementedInAssembler ()
#2  0x001247a4 in schedule ()
#3  0x00124468 in taskStart ()
#4  0x0017f800 in startProcWrapper ()
#5  0x9002b200 in _pthread_body ()

Haskell stack trace:

(gdb) p16 $r22
0x130a87c:  0x130a898
0x130a878:  0x13162c 
0x130a874:  0x2a
0x130a870:  0x1305000
0x130a86c:  0x1b6aec 
0x130a868:  0x130a884
0x130a864:  0x20e174 
0x130a860:  0x20e17c 
0x130a85c:  0x1315b0 
0x130a858:  0x130a878
0x130a854:  0x130a86c
0x130a850:  0x20e174 
0x130a84c:  0x10002 
0x130a848:  0x1174c0 
0x130a844:  0x170114 
0x130a840:  0x170208 
0x130a83c:  0x118bd0 

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Retrieving the caught signal within a handler

2005-12-06 Thread John Meacham
On a related note, it would be nice if we could get at the information
in the siginfo_t structure which can be read about in sigaction(2).
John

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


Re: [Haskell-cafe] Connecting to a running process (REPL)

2005-12-06 Thread John Meacham
On Tue, Dec 06, 2005 at 10:35:50AM +, Joel Reymont wrote:
> Is there a good standard way of supplying a read-eval prompt in a  
> program?

You might want to look at this module which is a program independent
read-eval prompt that I use for jhci. it is completely independent of
the rest of the compiler (like everything in the Util.* hierarchy) and
depends only on ghc provided libraries.

http://repetae.net/john/repos/jhc/Util/Interact.hs

for an example of its use see

http://repetae.net/john/repos/jhc/Interactive.hs

John

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


Re: [Haskell-cafe] Can't Haskell catch upwith Clean's uniqueness typing?

2005-12-06 Thread Robin Green
On Tuesday 06 December 2005 21:00, [EMAIL PROTECTED] wrote:
> In Clean, you can (and often are required to) assign uniqueness attributes
> to some parts of a function's type signature. The extended type checker
> ensures that none of those parts is referred to more than once during a
> single run of the program. Based on this guarantee, a function does not
> have to allocate new memory at all to store a unique result but can
> overwrite the unique arguments in place.

The rough equivalent to this in Haskell would be ST and STRefs, I believe. 
They work somewhat differently, however.

> My question is - and this might better suit to Haskell -, can't uniqueness
> be inferred (and exploited) automatically in many cases?

I'm not sure that uniqueness is the right thing to focus on here. I see this 
suggestion as a special case of situations where the compiler can know that a 
value will never be needed after a certain point, and therefore it can be 
free'd instead of being garbage collected (I don't know the technical term 
for that). These situations are - surely - not limited to situations where 
the value is referred to only once.

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


Re: [Haskell-cafe] Can't Haskell catch upwith Clean's uniqueness typing?

2005-12-06 Thread Robert Dockins
On Tuesday 06 December 2005 04:00 pm, [EMAIL PROTECTED] wrote:
> From: "Shae Matijs Erisson - [EMAIL PROTECTED]"
> Sent: Tuesday, December 06, 2005 6:16 PM
>
> > [EMAIL PROTECTED] writes:
> > > being occupied with learning both languages, I'm getting curious if
> > > Haskell couldn't achieve most of the performance gains resulting from
> > > uniqueness typing in Clean by *automatically* determining the reference
> > > count of arguments wherever possible and subsequently allowing them to
> > > be physically replaced immediately by (the corresponding part of) the
> > > function's result. Are there any principal obstacles, or *could* this
> > > be done, or *is* this even done already, e. g. in ghc?
> >
> > Maybe you're describing speculative evaluation?
> >
> > Optimistic Evaluation: An Adaptive Evaluation Strategy for Non-Strict
> > Programs http://citeseer.ist.psu.edu/ennals03optimistic.html
> > --
>
> Thanks for the pointer - I have heard a little about optimistic evaluation
> already, but don't know much of the details (yet). Anyway, from what I
> know, I think it's a different thing.
>
> In Clean, you can (and often are required to) assign uniqueness attributes
> to some parts of a function's type signature. The extended type checker
> ensures that none of those parts is referred to more than once during a
> single run of the program. Based on this guarantee, a function does not
> have to allocate new memory at all to store a unique result but can
> overwrite the unique arguments in place.
>
> Apparently, the uniqueness assignments have to comply with very tight laws
> - getting a program through the Clean type checker can be tough, once it
> reports an uniqueness coercion error. I suppose, no explicit uniqueness
> attributing is going to be implemented in Haskell, anyway.
>
> My question is - and this might better suit to Haskell -, can't uniqueness
> be inferred (and exploited) automatically in many cases?

Yes, probably.  There is a technique called sharing analysis that attempts to 
determine when a datastructure is only referenced once (ie, NOT shared).  If 
you can prove a datastructure node is not shared then you can reuse it 
destructively.

Here is a paper on the technique.  It's written for lisp cons cells, but one 
might be able to generalize the technique to ADT.  I don't know where to find 
a free copy.

http://portal.acm.org/citation.cfm?id=99375


There has also been some similar work done along these lines for Mercury (a 
logic programming language).

http://www.cs.mu.oz.au/research/mercury/information/papers.html

Search for papers with the word "reuse" in the title.  I'm not very familiar 
with this work, so I don't know how applicable this might be.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can't Haskell catch upwith Clean's uniqueness typing?

2005-12-06 Thread haskell-cafe . mail . zooloo

From: "Shae Matijs Erisson - [EMAIL PROTECTED]"
Sent: Tuesday, December 06, 2005 6:16 PM


> [EMAIL PROTECTED] writes:
>
> > being occupied with learning both languages, I'm getting curious if
> > Haskell couldn't achieve most of the performance gains resulting from
> > uniqueness typing in Clean by *automatically* determining the reference
> > count of arguments wherever possible and subsequently allowing them to
> > be physically replaced immediately by (the corresponding part of) the
> > function's result. Are there any principal obstacles, or *could* this be
> > done, or *is* this even done already, e. g. in ghc?
>
> Maybe you're describing speculative evaluation?
>
> Optimistic Evaluation: An Adaptive Evaluation Strategy for Non-Strict Programs
> http://citeseer.ist.psu.edu/ennals03optimistic.html
> --


Thanks for the pointer - I have heard a little about optimistic evaluation 
already, but don't know much of the
details (yet). Anyway, from what I know, I think it's a different thing.

In Clean, you can (and often are required to) assign uniqueness attributes to 
some parts of a function's type signature.
The extended type checker ensures that none of those parts is referred to more 
than once during a single run of the
program. Based on this guarantee, a function does not have to allocate new 
memory at all to store a unique result but can
overwrite the unique arguments in place.

Apparently, the uniqueness assignments have to comply with very tight laws - 
getting a program through the Clean type
checker can be tough, once it reports an uniqueness coercion error. I suppose, 
no explicit uniqueness attributing is going
to be implemented in Haskell, anyway.

My question is - and this might better suit to Haskell -, can't uniqueness be 
inferred (and exploited) automatically in
many cases?


Regards,

zooloo




-- 
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.371 / Virus Database: 267.13.12/192 - Release Date: 05.12.2005

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


Re: [Haskell-cafe] Can't Haskell catch up with Clean's uniqueness typing?

2005-12-06 Thread Tomasz Zielonka
On Tue, Dec 06, 2005 at 03:17:21PM +0100, [EMAIL PROTECTED] wrote:
> being occupied with learning both languages, I'm getting curious if
> Haskell couldn't achieve most of the performance gains resulting from
> uniqueness typing in Clean by *automatically* determining the
> reference count of arguments wherever possible and subsequently
> allowing them to be physically replaced immediately by (the
> corresponding part of) the function's result.

We can get similar performance from Haskell using various features of
GHC (unboxed arrays, mutable arrays, ST monad, soon SMP, etc) and one
can argue that they are even nicer.

I liked the concept of UT in Clean, but I haven't ever got comfortable
with using it to write real programs.

> Are there any principal obstacles, or *could* this be done, or *is*
> this even done already, e. g. in ghc?

I think the biggest obstacle is that almost nobody asks for it.
Well, you asked, but how much Haskell code did you write to be
sure that you really need it?

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learning Haskell

2005-12-06 Thread Tomasz Zielonka
On Mon, Dec 05, 2005 at 09:08:32PM -0500, Cale Gibbard wrote:
> To your second question, I'd say that Haskell isn't bad at small
> things. One can write a great deal of useful one-or-two-line Haskell
> programs. I'd consider its use in shell-scripting like tasks perhaps a
> little bit odd, but not really awkward at all.

For me, it isn't odd at all. I often face the some problem with
traditional shell scripting using tools like awk, cut, head, tail, sort,
etc - these tools are most often used in a way that is very sensitive
to formats of processed (text) files. This is a dangerous kind of
sensitivity, which often results in silent errors.

On the other hand in Haskell, with use of libraries like Parsec, it
is very easy to create a precise parser for the intended file format.
Almost every divergence from the assumed format will cause the program
to fail with a nice error message pointing to the problem.

Of course you can do similar things with regular expression provided
by tools like awk, sed and perl, but regexps don't scale to more
complicated formats (regular languages vs. context-free languages).

> Haskell code is generally pretty fun to write, there's usually not a
> lot of framework cruft that you need to write to get started on code
> that works.

Some Haskell libraries, like Parsec, require a bit of constant
boilerplate code to use - but you can write your own library
to move some of boilerplate code to one place. Recently, I was
very happy when I realized that I could reduce most of my small
Parsec-using programs by 5-10 lines of code this way.

If you wonder what kind of functions are these, below are their
signatures. I would have to ask my boss to show the actual code, but
they are really quite simple, and the types tell everything.

parseFile :: CharParser () a -> FilePath -> IO a
parseStdIn :: CharParser () a -> IO a

parseOrFail :: Monad m => GenParser tok () a -> SourceName -> [tok] -> m a

lazyMany :: CharParser () a -> SourceName -> [Char] -> [a]
parserToMaybeFun :: GenParser tok () a -> ([tok] -> Maybe (a, [tok]))

parseWithText :: CharParser st a -> CharParser st (a, String)

With these some programs become really simple:

import ...

main = do
x <- parseStdIn fileParser
do something with x

fileParser = do
...

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Connecting to a running process (REPL)

2005-12-06 Thread Tomasz Zielonka
On Tue, Dec 06, 2005 at 10:35:50AM +, Joel Reymont wrote:
> Is there a good standard way of supplying a read-eval prompt in a  
> program?
> 
> I would like to a running process with something ghci-like to be able  
> to inspect the state and possibly modify it. The running process  
> would be heavily multi-threaded.

Some time ago I was thinking about implementing a Haskell telnet
server module, but now I think that this would be a difficult
solution for a simple problem.

You can almost use GHCi for what you want. You could simply run
your program under from within GHCi. Of course you would have to
structure your program in such a way that you could reach the
interesting parts somehow. I think it could look like this:

$ ghci
...
Prelude> :l Prog
Prog> root <- runProg
...
Prog> threads <- getClientThreads root
...

Unfortunately it seems that forkIO'ed threads are freezed when GHCi is
waiting for command-line input. I bet it would be possible to let
the threads work in the background. I think the current behaviour is
caused by using readline, which is a foreign library. Or it is by
design?

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Tomasz Zielonka
On Tue, Dec 06, 2005 at 02:52:03PM +, Joel Reymont wrote:
> Well, I do need to have access to all those thread handles.

A TVar Int and a set/list of handles?

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Learning Haskell

2005-12-06 Thread Wolfgang Jeltsch
Am Dienstag, 6. Dezember 2005 14:43 schrieb Bulat Ziganshin:
> [...]

> so, in my feel, Haskell is better in areas where there is no standard
> quick-and-dirty solutions and all languages are in equal conditions,
> but it can't compete with Visual Basic in user interfaces, Erlang in
> distributed processing, and Python in scripting

Well, I would say that this has nothing to do with the language as such but 
with a current lack of certain libraries.  I even think that with appropriate 
libraries, Haskell will often have advantages over the existing solutions.

> [...]

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


Re[2]: [Haskell-cafe] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 6:42:32 PM, you wrote:
JR> On Dec 6, 2005, at 1:47 PM, Bulat Ziganshin wrote:

>> either
>> 1) use MVars/TMVars instead of Channels. in any case your logging
>> thread must consume data not slower than other channels produce then.
>> in fact, using Chan have meaning only to smooth temporary speed
>> differences between different threads. are you really need this??

btw, why not pass to worker thread just the logging action itself?

and, about waitForChildren:

waitForChildren :: IO ()
waitForChildren = 
do logDead <- newEmptyMVar
   forkIO (logger `finally` putMVar logDead ())
   c <- takeMVar children
   mapM_  takeMVar c
   ...send Nothing to logger thread
   takeMVar logDead

as simple as possible

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: Re[2]: [Haskell-cafe] What's a thread doing / Erlang-style processes / Message passing

2005-12-06 Thread Joel Reymont
Assuming I typed events like that I think I would need a typed sink  
for them as well. I only have one sink for the events and that is my  
message queue. I expect users to want User X, User Y, User Z within  
the same module and that's why I used Dynamic.


On Dec 6, 2005, at 4:07 PM, Bulat Ziganshin wrote:


creators of Data.List library also don't know about all your types,
but nevertheless you are use all theirs functions ;)

if set of messages is defined at compile time, then it's just:

data Event a = Quit
 | 
 | User a


--
http://wagerlabs.com/





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


[Haskell-cafe] Optimistic Evaluation was Re: Can't Haskell catch up with Clean's uniqueness typing?

2005-12-06 Thread Shae Matijs Erisson
[EMAIL PROTECTED] writes:

> being occupied with learning both languages, I'm getting curious if
> Haskell couldn't achieve most of the performance gains resulting from
> uniqueness typing in Clean by *automatically* determining the reference
> count of arguments wherever possible and subsequently allowing them to
> be physically replaced immediately by (the corresponding part of) the
> function's result. Are there any principal obstacles, or *could* this be
> done, or *is* this even done already, e. g. in ghc?

Maybe you're describing speculative evaluation? 

Optimistic Evaluation: An Adaptive Evaluation Strategy for Non-Strict Programs
http://citeseer.ist.psu.edu/ennals03optimistic.html
--
Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said:
You could switch out the unicycles for badgers, and the game would be the same.

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


RE: [Haskell-cafe] Re: :t main

2005-12-06 Thread Scherrer, Chad

> From: Simon Peyton-Jones [mailto:[EMAIL PROTECTED] 

> 
> I've not been following this thread, but I wanted to check: 
> you do know about Tarmo Uustalu's stuff about comonads, don't you?
> 
> http://www.cs.helsinki.fi/u/ekarttun/comonad/  summarises 
> (link to "The essence of dataflow programming" at the bottom)
> 
> Simon
> 

Thanks, Simon. I've seen it, but I haven't fully digested it yet.
Dataflow programming is new to me, and it's not immediately obvious how
it ties in with IO in general. I'll take another look, though.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Retrieving the caught signal within a handler

2005-12-06 Thread Joel Reymont

Thanks Bulat! This is what I ended up doing before you posted.
Sometimes just the mere fact of asking makes you come up with a  
solution.

I use #haskell for that alot :-).

On Dec 6, 2005, at 4:17 PM, Bulat Ziganshin wrote:


Hello Joel,

Tuesday, December 06, 2005, 1:39:10 PM, you wrote:

JR> Is there a way to retrieve the signal within the signal handler?

JR> I would like to know the signal that I caught.

just pass signal number to the handler you installs :)

installHandler sigPIPE Ignore Nothing
flip mapM_ [sigINT, sigHUP, sigABRT, sigTERM] $ \sig -> do
  installHandler sig handler Nothing
  where handler = Catch $ exitWith (ExitFailure 1)


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Learning Haskell

2005-12-06 Thread Donn Cave
Quoth Lemmih <[EMAIL PROTECTED]>:
...
| You might wanna have a look at Don's FastPackedString library:
| http://www.cse.unsw.edu.au/~dons/fps.html

Thanks, that's actually what got me thinking about trying this again.

| > | I am also hoping to use it for web development.
| >
| > Wonder how `links' is coming along.  (Hope they figured out a better
| > name, anyway.)
|
| Got an url for the project?

http://homepages.inf.ed.ac.uk/wadler/links/

Having looked it up, of course I looked at it.  Please forget I asked.

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Can't Haskell catch up with Clean's uniqueness typing?

2005-12-06 Thread haskell-cafe . mail . zooloo
Hi all,

being occupied with learning both languages, I'm getting curious if Haskell 
couldn't achieve most of the performance gains
resulting from uniqueness typing in Clean by *automatically* determining the 
reference count of arguments wherever
possible and subsequently allowing them to be physically replaced immediately 
by (the corresponding part of) the
function's result. Are there any principal obstacles, or *could* this be done, 
or *is* this even done already, e. g. in
ghc?


Regards,

zooloo






-- 
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.362 / Virus Database: 267.13.12/192 - Release Date: 05.12.2005

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


Re: [Haskell-cafe] Retrieving the caught signal within a handler

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 1:39:10 PM, you wrote:

JR> Is there a way to retrieve the signal within the signal handler?

JR> I would like to know the signal that I caught.

just pass signal number to the handler you installs :)

installHandler sigPIPE Ignore Nothing
flip mapM_ [sigINT, sigHUP, sigABRT, sigTERM] $ \sig -> do
  installHandler sig handler Nothing
  where handler = Catch $ exitWith (ExitFailure 1)

replace for example last line with

  where handler = Catch $ exitWith (ExitFailure sig)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell-cafe] What's a thread doing / Erlang-style processes / Message passing

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 5:12:55 PM, you wrote:

>> using "Dynamic" have meaning only if you don't know at compile time
>> what
>> messsages can be sent. is that really the case?

JR> That is correct. I deliver a "scripting library" and users can create
JR> messages of their own.

creators of Data.List library also don't know about all your types,
but nevertheless you are use all theirs functions ;)

if set of messages is defined at compile time, then it's just:

data Event a = Quit
 | 
 | User a

user of your library defines additional set of messages with

data UserEvent = Beer Int | Cola | ...

and use smthg like

do chan <- newChan
   sendChan chan (User $ Beer 5)
   sendChan chan Quit

it seems like magic but Haskell will guess what `chan` have type
"Chan (Event UserEvent)" here :)

>> imho, you are think in Erlang style, which is ultimately dynamic and
>> run-time oriented.

JR> I think in the style most suitable to my task at hand. I have a variable
JR> number of poker clients that talk to the server. These all run  
JR> concurrently
JR> so I'm starting threads for them. They can send/receive messages, so  
JR> I added
JR> mailboxes to the threads, etc. Is there anything wrong with this  
JR> approach?

hm, may be that you are mixing interfaces and implementation details.
for example, poker client in my taste must be a record which supports all
operations on this client via its fields, which is just an actions
which accepts/returns some values

in general, your questions contain too few details about your
problems and too much details about solutions you are assume


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Connecting to a running process (REPL)

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 1:35:50 PM, you wrote:

JR> Is there a good standard way of supplying a read-eval prompt in a  
JR> program?

just fork a thread to do it :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Re: TChan implementation: Why TVarList

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 2:46:24 PM, you wrote:

JR> I need to implement a mailbox where messages can be pulled out based
JR> on a predicate or in order of arrival. I'm thinking of using a Map  
JR> keyed on ClockTime.

JR> Do you have any suggestions?

it depends. what is the usage scenario?



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Joel Reymont

On Dec 6, 2005, at 1:47 PM, Bulat Ziganshin wrote:


either
1) use MVars/TMVars instead of Channels. in any case your logging
thread must consume data not slower than other channels produce then.
in fact, using Chan have meaning only to smooth temporary speed
differences between different threads. are you really need this??


This makes total sense for the logger thread. I will implement this.


2) i hope that you already replaced passing a Chan to subroutines with
passing an actions that read/write this Chan. in this case you can go
further and add to this actions incrementing/decrementing MVar
counter. but even without tests it's evident that 1000 producer  
threads

will get 1000 times more attention than 1 consumer thread if you don't
have any restrictions on producing and consuming data.


The problem is that I have hundreds of other network client threads
that do not directly read from a socket. They communicate through  
TChans instead.
I believe they block someplace and I'm trying to troubleshoot this.  
Of course

moving the logger to use TMVars instead of TChan might immediately solve
my problems.

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Joel Reymont
I must eat crow :-(. Moving the thread and logger mailboxes from  
TChan to TMVar reduced memory consumption by an order of magnitude. I  
found my space leak. Moving serialization from [Word8] to unboxed  
arrays did not hurt either.


On Dec 6, 2005, at 1:47 PM, Bulat Ziganshin wrote:


either
1) use MVars/TMVars instead of Channels. in any case your logging
thread must consume data not slower than other channels produce then.
in fact, using Chan have meaning only to smooth temporary speed
differences between different threads. are you really need this??


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Joel Reymont

Well, I do need to have access to all those thread handles.

On Dec 6, 2005, at 2:43 PM, Maarten Hazewinkel wrote:

I apologise if this doesn't make sense (I'm fairly new to Haskell),  
but

wouldn't a single shared counter be sufficient for this?

Increment for each child launched.
Decrement by each finished child.
When it's back down to zero, you're done.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Maarten Hazewinkel
On 12/6/05, Joel Reymont <[EMAIL PROTECTED]> wrote:
> I'm trying to implement a better waitForChildren from the docs for
> Control.Concurrent.
>
> I would like to know when all the children exit, basically, and I
> thought it would be neat to try to do that with STM.

I apologise if this doesn't make sense (I'm fairly new to Haskell), but
wouldn't a single shared counter be sufficient for this?

Increment for each child launched.
Decrement by each finished child.
When it's back down to zero, you're done.

Regards,

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


Re: [Haskell-cafe] What's a thread doing / Erlang-style processes / Message passing

2005-12-06 Thread Joel Reymont

On Dec 6, 2005, at 1:49 PM, Bulat Ziganshin wrote:


JR> #1 reading messages from a socket and posting to #3,
JR> #2 reading messages sent by #3 and writing to the socket,
JR> #3 reading messages sent by #1, processing them and posting to #2.

what you get by dividing this into 3 threads? i think that this have
meaning ONLY if you then join all socket reading threads together and
use one select to wait on them all


I get an abstraction of a thread with two STM-based mailboxes.
My workhorse threads don't need to care what is done with the messages
that they generate and where the ones that they are consuming come from.


JR>  | Custom Dynamic -- can't pattern-match on this?
JR>  deriving Show

using "Dynamic" have meaning only if you don't know at compile time  
what

messsages can be sent. is that really the case?


That is correct. I deliver a "scripting library" and users can create
messages of their own.


imho, you are think in Erlang style, which is ultimately dynamic and
run-time oriented.


I think in the style most suitable to my task at hand. I have a variable
number of poker clients that talk to the server. These all run  
concurrently
so I'm starting threads for them. They can send/receive messages, so  
I added
mailboxes to the threads, etc. Is there anything wrong with this  
approach?


Thanks, Joel

--
http://wagerlabs.com/


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


Re[2]: [Haskell-cafe] Learning Haskell

2005-12-06 Thread Bulat Ziganshin
Hello Jimmie,

Tuesday, December 06, 2005, 9:14:37 AM, you wrote:

JH> I would like to thank all who have replied to my inquiry.

my two cents :)

i'm not mathematician, but instead a professional programmer. i found
that Haskell allow to write shorter, concise and robust programs. as
Wirth says, "program = datastructures plus algorithms" and Haskell is
excellent at expressing both data types and algorithms processing them

the larger the project, the there is more meaning to use Haskell to
implement it, because you get the possibility to construct language
"dialect" which is better suits pecularities of this concrete project.
just for example - even control structures i use in my program are
written by me (and it is implemented very easy, just several lines each)

but for the small projects real difference created not by general
language features, but by features and environment, oriented toward
this concrete field of application. and in area of scripting and web
programming perl/ruby/python have much more specialization

one time i tried to write Haskell and Ruby variants of small script that
runs programs and bencmark its results. the main part of program was
equally sized, but Haskell implementation required from me writing
some small library of functions which are already present in all
abovementioned languages - getFileSize, trimSpaces and so on

so, for small scripting tasks you will not get benefits unless you are
need to organize complex dataprocessing. and even to make par-to-par
comparision with scripting languages, you are need to obtain libraries
for RegEx matching, String processing, and filesystem operations

i think, that the same applies to web programming - you need an
additional libraries and even with them you will not get all benefits
of Zope and RubyOnRails

so, in my feel, Haskell is better in areas where there is no standard
quick-and-dirty solutions and all languages are in equal conditions,
but it can't compete with Visual Basic in user interfaces, Erlang in
distributed processing, and Python in scripting

JH> I've seen much of what OO provides, good and bad. I'm interested in a
JH> good FP experience and it seems that Haskell can provide that.

nevertheless, if you not only search for the faster way to create
these scripts, but also to improve your programming skills, i
recommend you to teach Haskell :)  i even recommend you to spend just
one day to read book about Python (or Ruby, which i love more :) just
to get taste, and then go to teach Haskell seriously. these scripting
languages are not very complex, nor very different from other languages.
and in big contrast with Perl, they contains very little number of
"special rules". so, reading the whole book about Python/Ruby in just
one day is entirely possible

to learn Haskell and run scripts i recommend to use Hugs (WinHugs to
learn, if you are under Windows). my CMD instructed to run .hs files
with "runhugs.exe +st.qkoOuI -98"

i learned Haskell by "gentle introduction" but afair it had bad
explanation of imperative programming in Haskell. if your book have a
bad explanation of I/O in Haskell, try another book, or ask here. this
area really not seriously more complicated than in other languages,
despite its complex (but completelly hidden!) theoretical basis

JH> Thanks again. We'll see if I can fit Haskell into my brain. Or at least
JH> a sufficiently workable portion. :)

to my taste, Haskell have the features from ususal languages (say,
Java or Ruby) plus something more in areas of defining datastructures
and algorithms. if you don't need to use more features in these areas
than traditional languages provide, then there is no great meaning to
learn Haskell


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] What's a thread doing / Erlang-style processes / Message passing

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 1:27:58 PM, you wrote:

JR> #1 reading messages from a socket and posting to #3,
JR> #2 reading messages sent by #3 and writing to the socket,
JR> #3 reading messages sent by #1, processing them and posting to #2.

what you get by dividing this into 3 threads? i think that this have
meaning ONLY if you then join all socket reading threads together and
use one select to wait on them all

JR> data Event
JR>  = Enter
JR>  | Exit
JR>  | Quit
JR>  | Timeout String
JR>  | Connected
JR>  | Disconnected
JR>  | Error String
JR>  | Cmd Command
JR>  | Custom Dynamic -- can't pattern-match on this?
JR>  deriving Show

using "Dynamic" have meaning only if you don't know at compile time what
messsages can be sent. is that really the case?

JR> Last but not least, to be able to send messages to any thread I would  
JR> need to keep those around in some sort of a table. I would need to  
JR> create records and keep the thread id, the mailbox and possibly some  
JR> sort of a per-thread string so that threads can update me on their   
JR> doings.

imho, you are think in Erlang style, which is ultimately dynamic and
run-time oriented. what you really need - is an abstraction "Poker
server" which have interface consisting of several functions, which
includes ability to create new server, send it a fixed (at compile
time) set of messages, and that's all (may be i don't know about
something more). plus abstraction "Logger", which have facility "log
to me", this facility passed to routine which creates "Poker server"

data Logger = Logger {log :: String -> IO () }

createLogger = do c <- newChan
  forkIO $ loggerThread (readChan c)
  return $ Logger (log = writeChan c}

data Server = Server { send :: Event -> IO ()
 , kill :: IO ()
 }

createServer logger socket = do
  c <- newChan
  t <- forkIO $ serverThread (log logger) socket (readChan c)
  return $ Server {send = writeChan c, kill = killThread t}

main = do l <- createLogger
  s <- mapM (createServer l) [1..1000]
  ...


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Bulat Ziganshin
Hello Joel,

Tuesday, December 06, 2005, 12:54:57 PM, you wrote:

JR> Is there a way to check the number of outstanding messages in a Chan  
JR> or TChan?

either
1) use MVars/TMVars instead of Channels. in any case your logging
thread must consume data not slower than other channels produce then.
in fact, using Chan have meaning only to smooth temporary speed
differences between different threads. are you really need this??

2) i hope that you already replaced passing a Chan to subroutines with
passing an actions that read/write this Chan. in this case you can go
further and add to this actions incrementing/decrementing MVar
counter. but even without tests it's evident that 1000 producer threads
will get 1000 times more attention than 1 consumer thread if you don't
have any restrictions on producing and consuming data. if you
absolutely don't want to use MVars instead of channels, then at least you
can modify these actions so that number of Chan elements will be
limited (use additional "MVar full" which is filled in case of too
large number of elements in channel and emptied by logger thread)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] Learning Haskell

2005-12-06 Thread Mark T.B. Carroll
Jimmie Houchin <[EMAIL PROTECTED]> writes:
(snip)
> I have been perusing the haskell.org site and reading some of the
> tutorials. I just didn't want to expend lots of time just to find out
> that my math skills were woefully inadequate. I am grateful to learn
(snip)

Right. My math background isn't good enough for me to understand
(without much effort) some of the list traffic here - there's a lot I'm
still wrapping my head around. With much of the Haskell I've figured
out, I've done so by studying examples of others' code. Still, the
Haskell I do know is more than enough for me to do plenty of things
with, and it certainly covers everything I'd normally have coming to
mind from my use of other languages.

> The reason I asked about programming in the small, was my desire to
> spend my time and energy in a single direction. The ability to move what
> I do in Python to Haskell aids in that goal. It also promotes my
(snip)

Yes. I've ported a number of little Perl and bash scripts to Haskell
with very pleasing results. (Most recently, a little script that does
AUTHINFO GENERIC authentication by MD5 to an NNTP server.) It's even
quite easy to slap together little one-off programs once you're
comfortable with using "do" and the IO monad (which is pretty easy for
single-threaded stuff, and forkProcess works nicely too IMLE).

-- Mark

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


Re: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Joel Reymont
I'm trying to implement a better waitForChildren from the docs for  
Control.Concurrent.


I would like to know when all the children exit, basically, and I  
thought it would be neat to try to do that with STM.


Is there an advantage to STM here?

Thanks, Joel

On Dec 6, 2005, at 1:29 PM, Simon Marlow wrote:

I'm not sure what you're using all those TMVars for, but it sounds  
like

it might be better to multiplex them all into a single channel, or
something.


--
http://wagerlabs.com/





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


RE: [Haskell-cafe] What's a thread doing / Erlang-style processes /Message passing

2005-12-06 Thread Simon Marlow
On 06 December 2005 10:28, Joel Reymont wrote:

> I'm finding myself in dire need of monitoring the Haskell runtime.
> More precisely, I would like to know what each that I launch is doing
> at a given point in time.
> 
> Is there a way to obtain this information now? I would be fine with
> knowing if a thread is blocking on a foreign call, MVar or something
> like that.

If you compile with -debug, and run with +RTS -Ds you get a scheduler
trace which might help.

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


RE: [Haskell-cafe] Signal 2 and -threaded

2005-12-06 Thread Simon Marlow
On 06 December 2005 10:59, Joel Reymont wrote:

> I'm seeing some funky behavior in my program compiled with -threaded.
> It runs for a little while and then catches signal 2 and quits. This
> does not happen when -threaded is not used.
> 
> I'm compiling my library with -threaded so that is always constant.
> The above applies to my main module and another module that is part
> of it.
> 
> Any ideas?

I don't know any reason your program should be getting signal 2 (SIGINT,
I assume), unless the program sends itself SIGINT or someone else does.
Maybe on your system a process gets SIGINT when it exceeds some resource
limit?

Have you tried strace or equivalent (truss?)?

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


RE: [Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Simon Marlow
On 06 December 2005 10:02, Joel Reymont wrote:

> Is it efficient to wait on a few thousand TMVars?

That depends... while waiting your thread consumes no CPU at all (of
course), and simply waiting on all those TVars only imposes a small
constant overhead on anyone updating one of the TVars (a TMVar is just a
TVar).  However, checking all those TVars is O(n), and this happens
twice each time you wake up: once to find which TVar was modified, and
once again to go back to sleep on all of them.

I'm not sure what you're using all those TMVars for, but it sounds like
it might be better to multiplex them all into a single channel, or
something.
 
> How would I write something like that, assuming that my TMVars were
> in a list.

perhaps something along the lines of

  foldr orElse (return ()) . map takeTMVar

it depends what you want to return.

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


Re: [Haskell-cafe] Re: TChan implementation: Why TVarList

2005-12-06 Thread Joel Reymont

I think I could fake it on top of Data.Map keyed on ClockTime.

findMax :: Map k a -> (k, a) 
O(log n). The maximal key of the map.

This would give me the maximum key which I can then proceed to remove.

On Dec 6, 2005, at 12:35 PM, Simon Peyton-Jones wrote:


sounds as if you need a priority queue, so you can say "give me the
message with the earliest time" but otherwise yes.



--
http://wagerlabs.com/





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


RE: [Haskell-cafe] Re: TChan implementation: Why TVarList

2005-12-06 Thread Simon Peyton-Jones
sounds as if you need a priority queue, so you can say "give me the
message with the earliest time" but otherwise yes.

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Joel
| Reymont
| Sent: 06 December 2005 11:46
| To: Simon Peyton-Jones
| Cc: Haskell Cafe
| Subject: [Haskell-cafe] Re: TChan implementation: Why TVarList
| 
| Well, I meant more like TVar [a] but I see that you are pulling from
| the front and appending to the rear.
| 
| I need to implement a mailbox where messages can be pulled out based
| on a predicate or in order of arrival. I'm thinking of using a Map
| keyed on ClockTime.
| 
| Do you have any suggestions?
| 
|   Thanks, Joel
| 
| On Dec 6, 2005, at 11:31 AM, Simon Peyton-Jones wrote:
| 
| > The mutable cell is in the tail.  A [TVar a] would be quite
different.
| > You can read about a very similar impl (based on MVars) in the
| > original
| > "Concurrent Haskell" paper (on my papers page)
| 
| --
| http://wagerlabs.com/
| 
| 
| 
| 
| 
| ___
| 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: TChan implementation: Why TVarList

2005-12-06 Thread Joel Reymont
Well, I meant more like TVar [a] but I see that you are pulling from  
the front and appending to the rear.


I need to implement a mailbox where messages can be pulled out based  
on a predicate or in order of arrival. I'm thinking of using a Map  
keyed on ClockTime.


Do you have any suggestions?

Thanks, Joel

On Dec 6, 2005, at 11:31 AM, Simon Peyton-Jones wrote:


The mutable cell is in the tail.  A [TVar a] would be quite different.
You can read about a very similar impl (based on MVars) in the  
original

"Concurrent Haskell" paper (on my papers page)


--
http://wagerlabs.com/





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


[Haskell-cafe] RE: TChan implementation: Why TVarList

2005-12-06 Thread Simon Peyton-Jones
The mutable cell is in the tail.  A [TVar a] would be quite different.
You can read about a very similar impl (based on MVars) in the original
"Concurrent Haskell" paper (on my papers page)

S

| -Original Message-
| From: Joel Reymont [mailto:[EMAIL PROTECTED]
| Sent: 06 December 2005 11:28
| To: Simon Peyton-Jones
| Cc: Haskell Cafe
| Subject: TChan implementation: Why TVarList
| 
| Simon,
| 
| Why did you guys implement TChan on top of your own TVarList instead
| of a regular list?
| 
| -- | 'TChan' is an abstract type representing an unbounded FIFO
channel.
| data TChan a = TChan (TVar (TVarList a)) (TVar (TVarList a))
| 
| type TVarList a = TVar (TList a)
| data TList a = TNil | TCons a (TVarList a)
| 
|   Thanks, Joel
| 
| --
| http://wagerlabs.com/
| 
| 
| 
| 

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


[Haskell-cafe] TChan implementation: Why TVarList

2005-12-06 Thread Joel Reymont

Simon,

Why did you guys implement TChan on top of your own TVarList instead  
of a regular list?


-- | 'TChan' is an abstract type representing an unbounded FIFO channel.
data TChan a = TChan (TVar (TVarList a)) (TVar (TVarList a))

type TVarList a = TVar (TList a)
data TList a = TNil | TCons a (TVarList a)

Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Signal 2 and -threaded

2005-12-06 Thread Joel Reymont
I'm seeing some funky behavior in my program compiled with -threaded.  
It runs for a little while and then catches signal 2 and quits. This  
does not happen when -threaded is not used.


I'm compiling my library with -threaded so that is always constant.  
The above applies to my main module and another module that is part  
of it.


Any ideas?

I decided to compile with -threaded because otherwise killThread  
seems to block when a thread is in a foreign call.


Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Retrieving the caught signal within a handler

2005-12-06 Thread Joel Reymont

Is there a way to retrieve the signal within the signal handler?

I would like to know the signal that I caught.

Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Connecting to a running process (REPL)

2005-12-06 Thread Joel Reymont
Is there a good standard way of supplying a read-eval prompt in a  
program?


I would like to a running process with something ghci-like to be able  
to inspect the state and possibly modify it. The running process  
would be heavily multi-threaded.


Thanks, Joel

--
http://wagerlabs.com/





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


RE: [Haskell-cafe] GADT question

2005-12-06 Thread Simon Peyton-Jones
 
| I would like the type system to distinguish the three types and
enforce
| their properties. so far, I have come up with the following:
| 
| 
| data Sigma
| data Tau
| data Rho
| 
| data Type a where
| ForAll :: [Id] -> Type Rho -> Type Sigma
| Fun :: Type a -> Type a -> Type a
| TyCon :: TyCon -> Type Tau
| TyVar :: TyVar -> Type Tau

It looks as if you want a kind of subtyping relationship, so that Tau <
Rho < Sigma.  The standard way to achieve that is using polymorphism
(see, for example, papers about FFI to object-oriented languages)

data Sigma a = S a
data Rho a = R a
data Tau = Tau

data Type a where
| ForAll :: [Id] -> Type (Sigma (Rho a)) -> Type (Sigma b)
| Fun :: Type a -> Type a -> Type a
| TyCon :: TyCon -> Type (Sigma (Rho Tau))
| TyVar :: TyVar -> Type (Sigma (Rho Tau))

I'm not sure if this would work.

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


Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-12-06 Thread Benjamin Franksen
On Sunday 27 November 2005 11:28, [EMAIL PROTECTED] 
wrote:
> Andrew Pimlott:
>
> //about my highly spiritual essay on lazy computing of PI//:
> > In addition to being clever and terribly funny, the conclusion
> > foreshadows (inspired?) later work on Enron [1].
>
> Come on, it is improbable that Master Simon ever read my essay...
>
> No,... no comparison.
> His work on contracts and the usage of FP for this funny branch of
> math which serves to generate (and to destroy...) *real* money, is
> based on a very serious formal research.

Hmm, do you mean the 'real' money that gets destroyed (for instance) 
every time a loan is payed back? (like in: bank assets minus 
outstanding loan; bank liabilities minus amount payed back from 
checking account (= M1 money).) These are the wonders of double entry 
bookkeeping... 'real' money gone with the push of a button... ;)

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


[Haskell-cafe] What's a thread doing / Erlang-style processes / Message passing

2005-12-06 Thread Joel Reymont
I'm finding myself in dire need of monitoring the Haskell runtime.  
More precisely, I would like to know what each that I launch is doing  
at a given point in time.


Is there a way to obtain this information now? I would be fine with  
knowing if a thread is blocking on a foreign call, MVar or something  
like that.


The question is prompted by my current project and the issues I'm  
facing now. I believe I minimized the amount of garbage that I'm  
generating by moving to unboxed arrays from lists (thanks dcoutts)  
but I still have memory utilization issues.


I currently have each thread associated with a TChan and I'm going to  
try to abstract that today by creating a special type of a thread  
object that is associated with two mailboxes (in and out). When  
starting this thread you would supply the event loop to read from the  
inbox and another one to write to the mailbox. I would also add stats  
to the TChan mailboxes so that I know the number of messages pending  
in each mailbox and can monitor it.


This mirrors my current architecture where I have each poker bot as  
three threads:


#1 reading messages from a socket and posting to #3,
#2 reading messages sent by #3 and writing to the socket,
#3 reading messages sent by #1, processing them and posting to #2.

I suppose I'm trying to implement Erlang-like processes where each  
process has a mailbox for incoming messages and can send messages to  
any other process. In Erlang you can also check how many messages are  
pending to each process, etc. I don't think implementing message  
passing on top of exceptions is a good idea but please correct me if  
I'm wrong.


In Erlang you are tasked with implementing the message loop yourself  
and retrieve messages by using a "receive" construct where you can  
pattern-match on the type of message inside. It seems that custom  
messages would need to be implemented on top of Dynamic but is there  
a way to pattern-match on that?


I have messages implemented like this now but is there a better  
abstraction?


data Event
= Enter
| Exit
| Quit
| Timeout String
| Connected
| Disconnected
| Error String
| Cmd Command
| Custom Dynamic -- can't pattern-match on this?
deriving Show

Last but not least, to be able to send messages to any thread I would  
need to keep those around in some sort of a table. I would need to  
create records and keep the thread id, the mailbox and possibly some  
sort of a per-thread string so that threads can update me on their   
doings.


Do you have any suggestions?

Thanks, Joel

--
http://wagerlabs.com/





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


RE: [Haskell-cafe] Re: :t main

2005-12-06 Thread Simon Peyton-Jones
I've not been following this thread, but I wanted to check: you do know
about Tarmo Uustalu's stuff about comonads, don't you?

http://www.cs.helsinki.fi/u/ekarttun/comonad/  summarises (link to "The
essence of dataflow programming" at the bottom)

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| David Menendez
| Sent: 06 December 2005 07:13
| To: Scherrer, Chad
| Cc: haskell-cafe@haskell.org
| Subject: RE: [Haskell-cafe] Re: :t main
| 
| Scherrer, Chad writes:
| 
| > > From: Cale Gibbard [mailto:[EMAIL PROTECTED]
| > > See:
| > > http://haskell.org/pipermail/haskell-cafe/2003-January/003794.html
| > >
| > > The OI comonad as previously envisioned breaks referential
| > > transparency. I/O just doesn't seem to be something which one
| > > can easily do comonadically, since once coeval/extract is
| > > applied, you're back to plain values, and there's no
| > > imposition of sequencing.
| > >
| > >  - Cale
| >
| > Hmm, I hadn't seen that. The asymmetry is pretty frustrating in that
| > case.
| >
| > After poking around a bit more, I (re)discovered some discussion of
| > this on Hawiki:
| > http://www.haskell.org/hawiki/CoMonad
| >
| > After reading Dave Menendez's comments, I'm wondering...
| > If we consider
| > IO a = Realworld -> (Realworld, a)
| > then wouldn't we dually have something like
| > OI a = (Realworld, Realworld -> a)?
| >
| > Could this be what screws things up? Right now it seems like OI is
| > acting like it has the same type as IO, with a different name.
| 
| Aside from the product comonad and the exponent (reader) monad, I
don't
| think we'll find much overlap between monad and comonad functionality.
| It's been said that monads describe effects that propagate outwards,
| whereas comonads describe effects that propagate inwards.
| 
| My guess is that comonadic IO would look more like dataflow
programming.
| --
| David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the
laws
|   |of thermodynamics!"
| ___
| 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] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Tomasz Zielonka
On Tue, Dec 06, 2005 at 09:54:57AM +, Joel Reymont wrote:
> Is there a way to check the number of outstanding messages in a Chan  
> or TChan?
> 
> I suspect my problem is related to not reading messages fast enough  
> and I'd like to troubleshoot this by scanning my channels once every  
> few seconds and dumping statistics.

I would create a new ADT consisting of a TChan and TVar Int, increased
on writeTChan and decreased on readTChan.

Indeed, not reading messages fast enough can cause something similar
to space leak. Perhaps use a bounded TChan, it should be quite easy
to do in STM.

Best regards
Tomasz

-- 
I am searching for a programmer who is good at least in some of
[Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] STM and `orElse` on a few thousand TMVars

2005-12-06 Thread Joel Reymont

Is it efficient to wait on a few thousand TMVars?

How would I write something like that, assuming that my TMVars were  
in a list.


Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Number of outstanding messages in Chan or TChan

2005-12-06 Thread Joel Reymont
Is there a way to check the number of outstanding messages in a Chan  
or TChan?


I suspect my problem is related to not reading messages fast enough  
and I'd like to troubleshoot this by scanning my channels once every  
few seconds and dumping statistics.


Thanks, Joel

--
http://wagerlabs.com/





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