RE: [Haskell-cafe] Higher-order unification

2004-09-01 Thread Simon Peyton-Jones
| Yeah, here's a program which causes GHC to hang on compilation, but
| causes no problem for hugs.  Does this qualify as higher-order
unification?
| 
| newtype X a = X (X a - a)
| 
| selfapp :: X a - a
| selfapp self@(X f) = f self

It's a documented bug in GHC.  
http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html
Nothing to do with h-o unification

Simon


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


Re: [Haskell-cafe] Haskell Naming Conventions ?

2004-09-01 Thread Henning Thielemann

On Tue, 31 Aug 2004, Koray Can wrote:

 I can imagine once one gets used to them, they don't pose any problems. 
 Nevertheless, while I still learn, these names are quite awkward for me 
 to read and talk about haskell.

Yep, I agree absolutely.

 I searched the mailing list archives for a similar discussion, but I 
 couldn't fine one. Is there a reason why things are named in such a way 
 that conflicts with what's being followed for other languages ?

I've searched the mailing archives, too, and found nothing. But I've
recently tried to start a discussion about pairs of identifiers:

http://www.haskell.org/pipermail/libraries/2004-August/002420.html

There's even some more to discuss about:

 - get_value vs. getValue

 - current Prelude styleModula-3 style
   import DataType   vs.import qualified DataType
   value :: DataTypevalue :: DataType.T



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


[Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
Hello

Is it possible to implement an operation like 
tryReadMVar :: MVar a - IO (Maybe a)
in a good fashion? The semantics should be 
Read the value of the MVar without taking
it if it is filled, otherwise return Nothing.

There are several easy and flawed implementations:

tryReadMvar mv = do e - isEmptyMVar mv
case e of
 True - return Nothing
 False- readMVar mv = return . Just

This does not work because there can be a thread switch 
between the isEmpty and readMVar.

tryReadMVar mv = do mc - tryTakeMVar mv
case mc of
 Nothing - return mc
 Just v  - putMVar mv v  return mc

Now this can block on the putMVar if there was a thread switch 
and someone filled the MVar behind our back. 

Using tryPutMVar does not help much as it just creates another 
race condition:

tryReadMVar mv = do mc - tryTakeMVar mv
case mc of
 Nothing - return mc
 Just c  - tryPutMVar mv v  return mc

Consider what happens if the tryPutMVar fails:

-- read till we get the value with foobar in the middle
loopTill mv = do foobar 
 mc - tryReadMVar mv
 case mc of
  Nothing - loopTill mv
  Just v  - return v

maybe (loopTill mv) process (tryReadMVar mv)

error = do mv - newEmptyMVar
   forkIO (mapM_ (\i - putMVar mv i) [1..10])
   mapM_ (\_ - loopTill mv = print  takeMVar mv = print) [1..10]

If a tryPutMVar fails, then there will be less than ten values to 
read which will make the process block in takeMVar.

This seems quite straightforward in C with GHC (might be wrong
in the SMP case with locking?):

tryReadMVarzh_fast
{
W_ mvar, info;

/* args: R1 = MVar closure */
mvar = R1;
info = GET_INFO(mvar);

if (info == stg_EMPTY_MVAR_info) 
  RET_NP(0, stg_NO_FINALIZER_closure);

RET_NP(1, vStgMVar_value(mvar);
}

What is the best way to do this?

- Einar Karttunen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Jan-Willem Maessen - Sun Labs East
Einar Karttunen wrote:
Hello
Is it possible to implement an operation like 
tryReadMVar :: MVar a - IO (Maybe a)
in a good fashion? The semantics should be 
Read the value of the MVar without taking
it if it is filled, otherwise return Nothing.

There are several easy and flawed implementations:
...
tryReadMVar mv = do mc - tryTakeMVar mv
case mc of
 Nothing - return mc
 Just v  - putMVar mv v  return mc
Now this can block on the putMVar if there was a thread switch 
and someone filled the MVar behind our back. 
This sets off alarm bells in my head.  What are you actually trying to 
do, and why is correct for mutiple threads to race to putMVar?

Like locks, MVars require a certain discipline of usage (though 
several such disciplines are possible for MVars, whereas with locks 
you pretty much want to nest them in lock/unlock pairs).  I'm curious 
which discipline you are actually trying to use.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread MR K P SCHUPKE
tryReadMVar mv = do mc - tryTakeMVar mv


The normal reason people want tryRead is to do something 
like unix's 'select' function, where you want to wait on
one of several signals...

In my opinion it is better to do this with a _single_
channel and have one thread taking from the channel,
whilst all sources of the 'events' write to the same 
channel... so the refactoring would be like:

data Event = Even1 | Event2 | Event3 ...

c - newChan
forkIO (...)
a - readChan c
case a of
Event1 - ...
Event2 - ...


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


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Einar Karttunen
On 01.09 09:27, Jan-Willem Maessen - Sun Labs East wrote:
 Einar Karttunen wrote:
 Hello
 
 Is it possible to implement an operation like 
 tryReadMVar :: MVar a - IO (Maybe a)
 in a good fashion? The semantics should be 
 Read the value of the MVar without taking
 it if it is filled, otherwise return Nothing.
 
 There are several easy and flawed implementations:
 ...
 tryReadMVar mv = do mc - tryTakeMVar mv
 case mc of
  Nothing - return mc
  Just v  - putMVar mv v  return mc
 
 Now this can block on the putMVar if there was a thread switch 
 and someone filled the MVar behind our back. 
 
 This sets off alarm bells in my head.  What are you actually trying to 
 do, and why is correct for mutiple threads to race to putMVar?

There are several cases in which multiple threads racing putMVar is
correct. Consider e.g. a server thread encapsulating state, which 
needs to rate limit its clients. The server is put behind a MVar
to which all the clients putMVar and thus block until the server 
is ready e.g. 

plumbIn :: MVar SCoreT - HId - Handle - IO ()
plumbIn mv hid h = hGetContents h = loop
where loop s = let (m,r) = readInput s in putMVar mv (Msg m hid)  loop r

The server thread uses tryTakeMVar for its job. 

Now add a debug function:

debug :: MVar SCoreT - IO ()
debug mv = tryReadMVar mv = maybe (putStrLn Nothing) print

And suddenly we have a created a subtle bug in the code with 
flawed tryReadMVar implementation.

- Einar Karttunen 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Jan-Willem Maessen - Sun Labs East
MR K P SCHUPKE wrote:
tryReadMVar mv = do mc - tryTakeMVar mv

The normal reason people want tryRead is to do something 
like unix's 'select' function, where you want to wait on
one of several signals...
Combining the channels into one is certainly a bit nicer, but there 
might be a reason to want to prefer one event over another.

But wouldn't it be better to write this using just tryTakeMVar, rather 
than tryRead followed by blocking take?  This would guarantee that the 
events matched, and that the code would continue to work as expected 
in the multiple-reader case.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread Jan-Willem Maessen - Sun Labs East
Einar Karttunen wrote:
There are several cases in which multiple threads racing putMVar is
correct. Consider e.g. a server thread encapsulating state, which 
needs to rate limit its clients. The server is put behind a MVar
to which all the clients putMVar and thus block until the server 
is ready
 ...
The server thread uses tryTakeMVar for its job. 

Now add a debug function:
debug :: MVar SCoreT - IO ()
debug mv = tryReadMVar mv = maybe (putStrLn Nothing) print
And suddenly we have a created a subtle bug in the code with 
flawed tryReadMVar implementation.
Indeed, but depending upon the vagaries of scheduling, you may in fact 
be guaranteed *never* to see any output (eg, when tryTakeMVar yields 
on empty and putMVar yields unconditionally).

I was, however, curious what use you had in mind where writes were 
racing, but where you nonetheless wanted to perform blind non-blocking 
reads.  Such situations are generally fraught with peril.  In this 
case, the peril is starvation of the debug thread---which you may or 
may not actually care about.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-01 Thread MR K P SCHUPKE
might be a reason to want to prefer one event over another.

You can still use a single channel... If you read all pending events on the
channel into a FIFO (lazy list) then you can check for high priority events
on read, and then deal with the next item on the top of the FIFO... something
like the following (in pseudo code)

while channel not empty
read next event
if event high priority process now
else queue event in FIFO
process first event in FIFO

So inbetween processing low priority events we check ahead for any high
priority ones...

This could be extended with multiple FIFO's to deal with multiple priority
levels... but this ensures all events are dealt with sequentially (if out
of order)#

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


[Haskell-cafe] QuickCheck - Extracting data values from tests

2004-09-01 Thread Jorge Adriano Aires
Hello all,
When using Quickcheck, is there some way to extract generated data values to 
the IO Monad? 

I know I can collect and print information about test cases, but that's not 
enough. Data may be pretty complex, and there may be no parsers for it. If a 
test suddenly goes wrong, just having it displayed doesn't seem that useful.

I'd expect quickCheck to have type:
quickCheck :: forall a. (Testable a) = a - IO [a]

Show I could just get the offending data with:
please_be_empty - quickCheck prop_foo

Also, even when I'm implementing a generator, I want to see how it is working. 
Running a verboseCheck on some dummy property helps, but I may want to 
analyse the data, or some parts of it better - for instance, for many data 
structures I have alternative show functions that take parameters as 
arguments. 

Thanks in advance,
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe