Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
On 01.09 18:30, MR K P SCHUPKE wrote:
   while channel not empty
   read next event
   if event high priority process now
   else queue event in FIFO
   process first event in FIFO

That suffers from the same problem as I described.

do e - isEmptyChan ch -- is the channel empty?
   case e of
True - processFifo
False- readChan ch = highPriorityOrPush

Now there is danger of blocking on the readChan. (consider a case
where we create two similar server processes reading the same
channel). Now we create a tryReadChan, but we cannot implement
it with tryTakeMVar, as that would break dupChan. Rather we
need a tryReadMVar or a different channel abstraction.

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


Re: [Haskell-cafe] Implementing tryReadMVar

2004-09-02 Thread Einar Karttunen
On 01.09 13:09, Jan-Willem Maessen - Sun Labs East wrote:
 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.

I was trying to implement safe tryReadChan, which seems to be 
very simple with tryReadMVar, without it it seems to suffer
from various concurrency problems.

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


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

2004-09-02 Thread Shae Matijs Erisson
Jorge Adriano Aires [EMAIL PROTECTED] writes:

 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.

You may be interested in a QuickCheck hack of mine that saves the offending
data value to use immediately in the next test run.

You can get the current version with 
darcs get http://thunderbird.scannedinavian.com/repos/quickcheck;
I've only used this for my own code, so I'd be interested in any feedback.

In some cases it's a lot easier to generate a value from a seed and size rather
than saving the value in some way that you can restore (ie functions).

I've been investigating doing test-driven-development with QuickCheck, saving
failing test cases is one step towards that goal. If you have more ideas on
that topic, I'd like to hear about it.

 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.

This isn't clear to me, can you give other examples?
-- 
Shae Matijs Erisson - Programmer - http://www.ScannedInAvian.org/
I will, as we say in rock 'n' roll, run until the wheels come off, 
because I love what I do. -- David Crosby

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


Re: [Haskell-cafe] Stack overflow in ghci

2004-09-02 Thread Ron de Bruijn

--- Tomasz Zielonka [EMAIL PROTECTED]
wrote:

 On Thu, Sep 02, 2004 at 08:47:51AM -0700, Ron de
 Bruijn wrote:
  I heard of the +RTS option. I used:
  ghci SomeModule.hs -someoptions +RTS -K150,
 but
  this doesn't seem to have any effect. 
 
 Try +RTS -K150M.
 -K150 means 150 bytes.
 
 Best regards,
 Tom
 
 -- 
 .signature: Too many levels of symbolic links
 
Ok, it works. I thought the K was equivalent to 1000,
but the first K doesn't have that meaning. Thanks.




__
Do you Yahoo!?
Yahoo! Mail is new and improved - Check it out!
http://promotions.yahoo.com/new_mail
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Partially-applied type synonyms?

2004-09-02 Thread Lyle Kopnicky
Chung-chieh,
Well, I tried what you suggested, and it seems to work.  Unfortunately, 
it's not very useful.  The point of creating MonadPCont, was, like 
MonadCont or MonadState, to automatically provide features to a monad 
built from a transformer, without having to redefine them.  Since ContT 
is the monad transformer, I want any monad created from it to 
automatically support the MonadPCont operations.  But they can't, 
because I can't make ContT an instance of MonadPCont.

I can make FlipContT an instance of MonadPCont, but I can't make 
FlipContT a monad transformer.  So what you have to do is create your 
layered monadwith ContT on top, and then apply the FlipCont constructor 
to get a monad with the methods of MonadPCont.  Now since FlipContT 
isn't a monad transformer, you can't lift things into it.  You can lift 
them into ContT and then write a wrapper around that.

My point is that, unfortunately,  I don't think it's very practical to 
create this type class.  I think the problem is that, although MonadCont 
attempts to describe a monad as having certain operations, MonadPCont 
attempts to describe a group of related monads as having certain 
operations.  They are related by being formed from the same type 
constructor.

Here's the modified code:
module MonadPCont where
import Control.Monad
import Control.Monad.Cont
import Control.Monad.Trans
import Control.Monad.Reader
import Control.Monad.Writer
import Control.Monad.State
import Control.Monad.RWS 

class (Monad (mc a), Monad (mc r)) = MonadPCont mc a r where
   shift :: ((forall b. Monad (mc b) = a - mc b r) - mc r r) - mc r a
   reset :: mc a a - mc r a
instance MonadPCont Cont a r where
   shift f = Cont (\c - runCont (f (\x - Cont (\c' - c' (c x id)
   reset m = Cont (\c - c (runCont m id))
data FlipContT m r a = FlipContT { unFlipContT :: (ContT r m a)}
instance Monad m = Monad (FlipContT m r) where
   return x = FlipContT $ return x
   (FlipContT m') = f = FlipContT $ m' = (unFlipContT . f)
runFlipContT :: FlipContT m r a - (a - m r) - m r
runFlipContT (FlipContT m) = runContT m
 
instance Monad m = MonadPCont (FlipContT m) a r where
   shift f = FlipContT $ ContT $ \c -
   runFlipContT (f (\x - FlipContT $ ContT $ \c' - c x 
= c'))
return
   reset m = FlipContT $ ContT $ \c - runFlipContT m return = c

- Lyle
Chung-chieh Shan wrote:
On 2004-08-31T09:55:10-0700, Lyle Kopnicky wrote:
 

Sorry, I don't think I made myself clear.  I'm not defining PI, it's the 
standard type binding operator, like lambda is the variable binding 
operator.  Maybe I could write it as 'II' so it looks more like a 
capital pi.  It's not a feature of Haskell, but part of type theory 
(dependent types).  I was mixing and matching and making it look like 
Haskell.  So instead of 'PI r - ContT r m', I could write 'flip ContT', 
except that 'flip' needs to work on a type level instead of a value 
level.  Or I could write '(`ContT` m)', or 'ContT _ m', where the '_' is 
a hole.  Does this make sense now?
   

Yes, it makes sense now.  You need to define
   newtype FlipContT m r a = FlipContT (ContT r m a)
or more generally,
   newtype Flip c (m :: * - *) r a = Flip (c r m a)
The rationale for disallowing matching partially-applied type synonyms
is that higher-order unification is undecidable.
See also:
Neubauer, Matthias, and Peter Thiemann. 2002.  Type classes with
more higher-order polymorphism.  In ICFP '02: Proceedings of the ACM
international conference on functional programming. New York: ACM Press.
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.pdf
http://www.informatik.uni-freiburg.de/~neubauer/papers/icfp02.ps.gz
 

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


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

2004-09-02 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.

 You may be interested in a QuickCheck hack of mine that saves the offending
 data value to use immediately in the next test run.

Nice!
It's different from what I was looking for but also quite usefull.

 You can get the current version with
 darcs get http://thunderbird.scannedinavian.com/repos/quickcheck;
 I've only used this for my own code, so I'd be interested in any feedback.

Ok.

 In some cases it's a lot easier to generate a value from a seed and size
 rather than saving the value in some way that you can restore (ie
 functions).

 I've been investigating doing test-driven-development with QuickCheck,
 saving failing test cases is one step towards that goal. If you have more
 ideas on that topic, I'd like to hear about it.

Well, returning (part of) the generated data is one of them :)

  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.

 This isn't clear to me, can you give other examples?


Not sure which part is not clear... I'll just try to explain each of them.
Lets say I'm implementing a generators for Graphs.

  Also, even when I'm implementing a generator, I want to see how it is
  working.
I want to check if the generated Graphs are like I intended them to be.

  Running a verboseCheck on some dummy property helps, but I may
verboseCheck by default prints all the data.
I can run it on a dummy function that always returns True to see what kind of 
data I'm getting.


  want to analyse the data, or some parts of it better
May want to print the 'actual graphs' on the screen (ASCII art, or maybe using 
some function that calls Gnuplot). Then I may want to check in more detail 
the info in contained in some of the nodes. Then I may decide to run some 
functions on it.

  many data structures I have alternative show functions that take
  parameters as arguments.
Like I just said, I may want to show the graph in many ways.


But there are more possibilities.
Why limitate the usefulness of QuickCheck? Suppose I just implemented 
generators for a few kinds of terms and formulas to test some properties. Now 
I want to benchmark a couple of different unification functions... I'd expect 
to be able to use my generator for that. Unless I'm missing something, I 
cannot. Am I right?

J.A.

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