[Haskell-cafe] Re: [Haskell] Matrix multiplication

2008-04-29 Thread Don Stewart
> droundy 
> On Wed, Apr 23, 2008 at 05:24:20PM +0100, Sebastian Sylvan wrote:
> > On Wed, Apr 23, 2008 at 5:01 PM, Tillmann Vogt  
> > rwth-aachen.de>
> > wrote:
> > 
> > > Hi,
> > >
> > > I am currently experimenting with parallelizing C-programs. I have
> > > therefore written a matrix vector multiplication example that needs 13
> > > seconds to run (5 seconds with OpenMP). Because I like Haskell I did the
> > > same in this language, but it takes about 134 seconds. Why is it so slow?
> > > Does someone have an idea?
> > >
> > Yes, in the C version you use unboxed arrays, in the Haskell version you use
> > a linked list of linked lists. Naturally the latter will take up more space,
> > require more work to index, and will thrash the cache quite a bit.
> 
> In fact, I'm impressed that Haskell can come within a factor of 10, given
> that it's using such a challenging data type! (I wonder if this may be due
> to inefficiencies in the C code, although I haven't looked at it.)

I had a look at this code, using the (unboxed, strict, fused) data parallel
arrays library (http://darcs.haskell.org/packages/ndp). 

We get rather nice code. The original C program (modified, to sum the result,
rather than just filling the array and throwing it out):


#include 
#include 
#include 

#define M 4000
#define N 4000
#define IT 100

double a[M], b[M][N], c[N];

int main(int argc, char *argv[])
{
  double d;
  double sum;
  int i, j, l;
  time_t start,end;

  printf("Initializing matrix B and vector C\n");
  for(j=0; jhttp://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell


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


Re: [Haskell-cafe] approximating pi

2008-04-29 Thread Benjamin L. Russell
I was thinking of how to represent this process graphically on a computer 
screen.  Assuming one wanted to perform a demo of this algorithm (in the spirit 
of XTANGO, an algorithm animator that I had used for my senior project in 
1994), in order to represent the square and the circle on-screen, one would 
need to represent the objects with pixels.  Many desktop and laptop computer 
screens these days have a minimum resolution of 800x600 pixels; assuming this 
resolution, I wanted to see how this algorithm could be animated using a square 
with 100 pixels per side.

The problem is how to define "reasonable."  As you stated, since the relative 
error falls as 1/sqrt(N), where N is the number of samples, and 100x100=1 
pixels, then for, say, even a relative error of 1/100, we would need to fill up 
the entire square (1 pixels).  I would really like a relative error of 
1/1000, in which case we would need 1000x1000=100 samples, which would 
require filling up a square ten times longer per side.

This is unlikely to work in practice with most desktop and laptop computer 
screens; so, I'll lower my expectations slightly.  I'll be very lenient and set 
my acceptable relative error to 1/10.  Then, since the relative error falls as 
1/sqrt(N), since sqrt(100)=10, N can be 100.  The square has an area of 
100x100=1 pixels.

This would allow a very rough estimate of pi that could actually be 
demonstrated graphically using an algorithm animator.

Benjamin L. Russell

--- On Mon, 4/28/08, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

> Benjamin L. Russell: 
> 
> > Assuming the square had 100 pixels per side, on the
> average, approximately 
> > how many random pixels should be plotted in the square
> before obtaining a 
> > reasonably good estimate of pi?
> 
> Nothing to do with Haskell... 
> 
> What do you mean by "reasonable"? This
> Monte-Carlo procedure is very
> inefficient anyway. The relative error falls as 1/sqrt(N)
> where N is the
> number of samples, so, several hundred thousands of samples
> may give you
> just three significant digits.
> And, at any rate, this has nothing to do with pixels, what,
> introduce
> one more source of errors through the truncation of real
> randoms? 
> 
> Jerzy Karczmarczuk 
> 
> ___
> 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] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur
Alright, I have tested it now. I still feel funny about most of the  
names I chose for the types and functions, and it's still very ugly,  
but the code appears to work correctly. In this version I have also  
added "retry" and "orElse" functions so that it can feel more like the  
STM monad. I think the biggest downside to this monad is the potential  
confusion about whether to use "could" or "must," but I have a feeling  
that better naming choices would reduce the ambiguity.


Thoughts?


module CachedSTM where

import Control.Applicative
import Control.Concurrent.STM as S
import Control.Monad

data CachedSTM a = CSTM {
  getMust :: STM (),
  getCould :: STM a
}

instance Functor CachedSTM where
f `fmap` (CSTM m s) = CSTM m $ f <$> s

joinCSTM :: CachedSTM (CachedSTM a) -> CachedSTM a
joinCSTM cstm = CSTM m s
where m = do cstm' <- getCould cstm
 getMust cstm' `S.orElse` return ()
 getMust cstm `S.orElse` return ()
  s = getCould =<< getCould cstm

instance Applicative CachedSTM where
pure = return
(<*>) = ap

instance Monad CachedSTM where
return = CSTM (return ()) . return
x >>= f = joinCSTM $ f <$> x

maybeAtomicallyC :: CachedSTM a -> IO (Maybe a)
maybeAtomicallyC cstm = atomically $ do
  getMust cstm
  liftM Just (getCould cstm) `S.orElse`  
return Nothing


could :: STM a -> CachedSTM a
could stm = CSTM (return ()) stm

must :: STM () -> CachedSTM ()
must stm = CSTM (stm `S.orElse` return ()) $ return ()

retry :: CachedSTM a
retry = could S.retry

orElse :: CachedSTM a -> CachedSTM a -> CachedSTM a
orElse a b = do must $ getMust a
temp <- could newEmptyTMVar
must $ (getCould a >>= putTMVar temp) `S.orElse`  
getMust b

could $ takeTMVar temp `S.orElse` getCould b


I don't think the IVar code has changed (no version control for this),  
but here it is again for quick reference:



module IVal where

import CachedSTM
import Control.Applicative
import Control.Concurrent.STM
import Control.Monad
import System.IO.Unsafe

newtype IVal a = IVal (TVar (Either (CachedSTM a) a))

newIVal :: CachedSTM a -> CachedSTM (IVal a)
newIVal = fmap IVal . could . newTVar . Left

newIValIO :: CachedSTM a -> IO (IVal a)
newIValIO = fmap IVal . newTVarIO . Left

cached :: CachedSTM a -> IVal a
cached = unsafePerformIO . newIValIO

force :: IVal a -> CachedSTM a
force (IVal tv) = could (readTVar tv) >>= either compute return
where compute wait = do x <- wait
must . writeTVar tv $ Right x
return x

instance Functor IVal where
f `fmap` x = cached $ f <$> force x

instance Applicative IVal where
pure = return
(<*>) = ap

instance Monad IVal where
return = cached . return
x >>= f = cached (force x >>= force . f)


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


[Haskell-cafe] Couple of formal questions

2008-04-29 Thread Creighton Hogg
Hello Haskell,
So there's two questions that have been bothering me lately & while they
are, as usual, a little off topic I figured this might be a good forum:

Where could I find a good treatment on data vs. codata & the difference
between well-founded recursion & well-founded(?) corecursion?

Where could I find a proof that the initial algebras & final coalgebras of
CPO coincide?  I saw this referenced in the "Bananas.." paper as a fact, but
am not sure where this comes from.

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


Re: [Haskell-cafe] A bright future for Haskell

2008-04-29 Thread Don Stewart
ajb:
> G'day all.
> 
> Quoting John Peterson <[EMAIL PROTECTED]>:
> 
> >Especially if SPJ decides to grow a beard.  Unfortunately Paul is   
> >now clean shaven so maybe Haskell is in trouble.
> 
> This explains why Clean never made it: Rinus Plasmeijer can't compete
> with Phil Wadler in the beard department.
> 
> I should point out, for fairness, tht Mark Jones has suitable facial
> hair, and John Hughes and Ralf Hinze are not fair behind.  John Peterson
> clearly should complete his beard, though.

And in the younger generation, Ian Lynagh is surely critical to
Haskell's on going success... 

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


Re: [Haskell-cafe] A bright future for Haskell

2008-04-29 Thread ajb

G'day all.

Quoting John Peterson <[EMAIL PROTECTED]>:

Especially if SPJ decides to grow a beard.  Unfortunately Paul is   
now clean shaven so maybe Haskell is in trouble.


This explains why Clean never made it: Rinus Plasmeijer can't compete
with Phil Wadler in the beard department.

I should point out, for fairness, tht Mark Jones has suitable facial
hair, and John Hughes and Ralf Hinze are not fair behind.  John Peterson
clearly should complete his beard, though.

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


[Haskell-cafe] A bright future for Haskell

2008-04-29 Thread John Peterson
Especially if SPJ decides to grow a beard.  Unfortunately Paul is now clean 
shaven so maybe Haskell is in trouble.

http://blogs.microsoft.co.il/blogs/tamir/archive/2008/04/28/computer-languages-and-facial-hair-take-two.aspx

   John

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


Re: [Haskell-cafe] question about GHC and Unicode

2008-04-29 Thread Albert Y. C. Lai

John Goerzen wrote:
That's a wonderful interface, but unfortunately it appears to assume that 
your Unicode I/O is always UTF-8, and never UTF-16.  I happen to deal with 
more UTF-16 data than UTF-8 over here at the moment.


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/encoding

seems to have UTF-16.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: catching fails on read

2008-04-29 Thread Jacques Bergeron
Don Stewart  galois.com> writes:

> 
> jbergeron:
> > I'm new to Haskell and have a stupid question.
> > 
> > How can a catch a parsing error on a read? Something like 
> > 
> > let s = "e"
> > in read s :: Int
> > 
> > I've been searching for a trick and couldn't find one. I want to enter 
> > commands directly from the keyboard and don't want the program to abort if 
I 
> > do a typing error.
> 
>   maybeRead :: Read a => String -> Maybe a
>   maybeRead s = case reads s of
>   [(x, rest)] | all isSpace rest -> Just x
>   _ -> Nothing
> 
> There's an open ticket to add this to the base library.
> 


So reads (or readsPrec) is the "parser" equivalent to read. Should have 
catched that, sorry.

Thanks for your time.

Jacques


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


Re: [Haskell-cafe] catching fails on read

2008-04-29 Thread Don Stewart
jbergeron:
> I'm new to Haskell and have a stupid question.
> 
> How can a catch a parsing error on a read? Something like 
> 
> let s = "e"
> in read s :: Int
> 
> I've been searching for a trick and couldn't find one. I want to enter 
> commands directly from the keyboard and don't want the program to abort if I 
> do a typing error.

  maybeRead :: Read a => String -> Maybe a
  maybeRead s = case reads s of
  [(x, rest)] | all isSpace rest -> Just x
  _ -> Nothing

There's an open ticket to add this to the base library.

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


[Haskell-cafe] catching fails on read

2008-04-29 Thread Jacques Bergeron
I'm new to Haskell and have a stupid question.

How can a catch a parsing error on a read? Something like 

let s = "e"
in read s :: Int

I've been searching for a trick and couldn't find one. I want to enter 
commands directly from the keyboard and don't want the program to abort if I 
do a typing error.

Regards,

Jacques

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


Re: AW: [Haskell-cafe] Something like optimistic evaluation

2008-04-29 Thread Daniil Elovkov

Nicu Ionita wrote:


I don't know if this would be worth, but theoretically one could go on 
and evaluate those thunks that:
 
a) would be evaluated anyway (after the current IO operation have been 
completed)

b) do not depend on the result of the current operation
 
And, of course, the GC could work in this time also.


Yes, and btw, this work would _definitely_ not be wasted, unlike 
evaluating thunks.





Nicu

-Ursprüngliche Nachricht-
*Von:* [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] *Im Auftrag von *Brent Yorgey
*Gesendet:* Dienstag, 29. April 2008 16:42
*An:* Daniil Elovkov
*Cc:* haskell-cafe@haskell.org
*Betreff:* Re: [Haskell-cafe] Something like optimistic evaluation


On Mon, Apr 28, 2008 at 6:09 PM, Daniil Elovkov
<[EMAIL PROTECTED]
> wrote:

Hello

Somewhat on the topic of optimistic evaluation, I've just
thought of another way to evaluate thunks.

When the program is about to block on some IO, what if we start
a thread to evaluate (any) unevaluated thunks. We'll have
additional system thread, but the blocked one will not actually
consume any processor time.

This would take place only when the program is compiled as
threaded and run with -N k, k>1.

The RTS knows at least about some operations that will block,
those which IO operations are implemented with. for example. It
could merely start a process of evaluating any (or something
more clever) outstanding thunks right before going into one of
those operations and stop it when it's back.

Of course, it's not like optimistic evaluation because we don't
avoid creating thunks. But in a sense it's similar. It could
also be compared with incremental garbage collection :)

Has something like that been done, discussed?


This sounds like it could be helpful in certain circumstances, but
in many cases it could probably lead to unpredictable (and
uncontrollable!) memory usage.  I could imagine a situation where my
program is running along just fine, and then one day it takes a long
time to do a read from the network due to latency or whatever, and
suddenly memory usage shoots through the roof, due to evaluation of
some infinite (or even just very large) data structure. 


-Brent


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


Re: [Haskell-cafe] Something like optimistic evaluation

2008-04-29 Thread Daniil Elovkov

Brent Yorgey wrote:


On Mon, Apr 28, 2008 at 6:09 PM, Daniil Elovkov 
<[EMAIL PROTECTED] > 
wrote:


Hello

Somewhat on the topic of optimistic evaluation, I've just thought of
another way to evaluate thunks.

When the program is about to block on some IO, what if we start a
thread to evaluate (any) unevaluated thunks. We'll have additional
system thread, but the blocked one will not actually consume any
processor time.

This would take place only when the program is compiled as threaded
and run with -N k, k>1.

The RTS knows at least about some operations that will block, those
which IO operations are implemented with. for example. It could
merely start a process of evaluating any (or something more clever)
outstanding thunks right before going into one of those operations
and stop it when it's back.

Of course, it's not like optimistic evaluation because we don't
avoid creating thunks. But in a sense it's similar. It could also be
compared with incremental garbage collection :)

Has something like that been done, discussed?


This sounds like it could be helpful in certain circumstances, but in 
many cases it could probably lead to unpredictable (and uncontrollable!) 
memory usage.  I could imagine a situation where my program is running 
along just fine, and then one day it takes a long time to do a read from 
the network due to latency or whatever, and suddenly memory usage shoots 
through the roof, due to evaluation of some infinite (or even just very 
large) data structure. 



Yes, well, optimistic evaluation itself, as I understand, already 
exploits some mechanisms for avoiding that kind of thing. For example it 
stops evaluating a thunk if it starts to take too long. In case of OE we 
have to care about time (and memory). In this 'behind IO' case we only 
have to care about memory usage.


There can be some rules, like have an upper bound of amount of memory 
taken by new thunks. Also, of course it would make sense to do a sort of 
'breadth first' evaluation.


After all, the research has already been done on OE, its trade-offs, 
what happens with infinite data structures, etc. This would be just a 
relatively minor tweak. And, in terms of real execution time it would be 
simply free, it seems.


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


AW: [Haskell-cafe] Something like optimistic evaluation

2008-04-29 Thread Nicu Ionita
I don't know if this would be worth, but theoretically one could go on and
evaluate those thunks that:
 
a) would be evaluated anyway (after the current IO operation have been
completed)
b) do not depend on the result of the current operation
 
And, of course, the GC could work in this time also.
 
Nicu

-Ursprüngliche Nachricht-
Von: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] Im Auftrag von Brent Yorgey
Gesendet: Dienstag, 29. April 2008 16:42
An: Daniil Elovkov
Cc: haskell-cafe@haskell.org
Betreff: Re: [Haskell-cafe] Something like optimistic evaluation



On Mon, Apr 28, 2008 at 6:09 PM, Daniil Elovkov
<[EMAIL PROTECTED]> wrote:


Hello

Somewhat on the topic of optimistic evaluation, I've just thought of another
way to evaluate thunks.

When the program is about to block on some IO, what if we start a thread to
evaluate (any) unevaluated thunks. We'll have additional system thread, but
the blocked one will not actually consume any processor time.

This would take place only when the program is compiled as threaded and run
with -N k, k>1.

The RTS knows at least about some operations that will block, those which IO
operations are implemented with. for example. It could merely start a
process of evaluating any (or something more clever) outstanding thunks
right before going into one of those operations and stop it when it's back.

Of course, it's not like optimistic evaluation because we don't avoid
creating thunks. But in a sense it's similar. It could also be compared with
incremental garbage collection :)

Has something like that been done, discussed?



This sounds like it could be helpful in certain circumstances, but in many
cases it could probably lead to unpredictable (and uncontrollable!) memory
usage.  I could imagine a situation where my program is running along just
fine, and then one day it takes a long time to do a read from the network
due to latency or whatever, and suddenly memory usage shoots through the
roof, due to evaluation of some infinite (or even just very large) data
structure.  

-Brent


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


Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur
*sigh* As is usual with my untested code, the code I just sent was  
wrong. I will be able to actually test, correct, and refine it  
tonight. If nobody else has picked it up by then I will do so.


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


Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur

On Apr 28, 2008, at 10:01 PM, Ryan Ingram wrote:


The problem I have with all of these STM-based solutions to this
problem is that they don't actually cache until the action fully
executes successfully.


I just hacked together a new monad that I think might solve this, at  
least with a little extra work. I haven't tested it yet though because  
I have to do some studying now. I just want to go ahead and put it up  
for review and see if you guys think this is a good approach.


To use it you use the "could" and "must" functions to specify which  
STM actions may be rolled back and which ones must be permanent. When  
you apply maybeAtomicallyC to a CachedSTM action, all the "must"  
actions are performed individually, where any that fail do not affect  
any of the others. Once the "must" actions are done, the "could"  
actions are performed, returning Just the result. If that fails then  
the whole thing simply returns Nothing, but the "must" actions are  
still committed.


At least, I _hope_ the above is what it actually does!


module CachedSTM where

import Control.Applicative
import Control.Concurrent.STM
import Control.Monad

data CachedSTM a = CSTM {
  getMust :: STM (),
  getShould :: STM a
}

instance Functor CachedSTM where
f `fmap` (CSTM m s) = CSTM m $ f <$> s

joinCSTM :: CachedSTM (CachedSTM a) -> CachedSTM a
joinCSTM cstm = CSTM m s
where m = do cstm' <- getShould cstm
 getMust cstm' `orElse` return ()
 getMust cstm `orElse` return ()
  s = getShould =<< getShould cstm

instance Applicative CachedSTM where
pure = return
(<*>) = ap

instance Monad CachedSTM where
return = CSTM (return ()) . return
x >>= f = joinCSTM $ f <$> x

maybeAtomicallyC :: CachedSTM a -> IO (Maybe a)
maybeAtomicallyC cstm = atomically $ do
  getMust cstm
  liftM Just (getShould cstm) `orElse`  
return Nothing


could :: STM a -> CachedSTM a
could stm = CSTM (return ()) stm

must :: STM () -> CachedSTM ()
must stm = CSTM stm $ return ()



Now the IVal stuff might look something like:


module IVal where

import CachedSTM
import Control.Applicative
import Control.Concurrent.STM
import Control.Monad
import System.IO.Unsafe

newtype IVal a = IVal (TVar (Either (CachedSTM a) a))

newIVal :: CachedSTM a -> CachedSTM (IVal a)
newIVal = fmap IVal . could . newTVar . Left

newIValIO :: CachedSTM a -> IO (IVal a)
newIValIO = fmap IVal . newTVarIO . Left

cached :: CachedSTM a -> IVal a
cached = unsafePerformIO . newIValIO

force :: IVal a -> CachedSTM a
force (IVal tv) = could (readTVar tv) >>= either compute return
where compute wait = do x <- wait
must . writeTVar tv $ Right x
return x

instance Functor IVal where
f `fmap` x = cached $ f <$> force x

instance Applicative IVal where
pure = return
(<*>) = ap

instance Monad IVal where
return = cached . return
x >>= f = cached (force x >>= force . f)



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


Re: [Haskell-cafe] Mutual recursive data types

2008-04-29 Thread Luke Palmer
On Tue, Apr 29, 2008 at 8:54 AM, rodrigo.bonifacio
<[EMAIL PROTECTED]> wrote:
> Hi all,
>
>  I have the following data types:
>
>  type Id = String
>  type Action = String
>  type State = String
>  type Response = String
>
>  data Scenario = Scenario Description [Step]
>  data Step = Step Id Scenario Action State Response
>
>  So, there is a mutual recursion between Scenario and Step. Now, consider the 
> following function:
>
>  xmlScenario2Scenario :: XmlScenario -> Scenario
>  xmlScenario2Scenario (XmlScenario description steps) =
>   Scenario  description [xmlStep2Step x | x <-steps]
>
>  How can I send "scenario" as an argument for xmlStep2Step?

Like this:

   let scenario = Scenario description [xmlStep2Step scenario x | x <- steps]
in scenario

>  I've tried let and where but I get in a loop.

So it sounds like you already tried what I suggested.  If you get in a
loop, then whatever you are doing is too strict to handle this kind of
self-reference.  But it's hard to give suggestions without seeing more
of the code.

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


[Haskell-cafe] Mutual recursive data types

2008-04-29 Thread rodrigo.bonifacio
Hi all,

I have the following data types:

type Id = String
type Action = String
type State = String
type Response = String

data Scenario = Scenario Description [Step]
data Step = Step Id Scenario Action State Response

So, there is a mutual recursion between Scenario and Step. Now, consider the 
following function:

xmlScenario2Scenario :: XmlScenario -> Scenario
xmlScenario2Scenario (XmlScenario description steps) =
 Scenario  description [xmlStep2Step x | x <-steps]

How can I send "scenario" as an argument for xmlStep2Step?

I've tried let and where but I get in a loop.

Thanks a lot,

Rodrigo.



---
Rodrigo Bonifácio de Almeida
Universidade Católica de Brasília
 - Grupo de Engenharia de Software
 - JavaComBr (www.ucb.br/java)

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


Re: [Haskell-cafe] Something like optimistic evaluation

2008-04-29 Thread Brent Yorgey
On Mon, Apr 28, 2008 at 6:09 PM, Daniil Elovkov <
[EMAIL PROTECTED]> wrote:

> Hello
>
> Somewhat on the topic of optimistic evaluation, I've just thought of
> another way to evaluate thunks.
>
> When the program is about to block on some IO, what if we start a thread to
> evaluate (any) unevaluated thunks. We'll have additional system thread, but
> the blocked one will not actually consume any processor time.
>
> This would take place only when the program is compiled as threaded and run
> with -N k, k>1.
>
> The RTS knows at least about some operations that will block, those which
> IO operations are implemented with. for example. It could merely start a
> process of evaluating any (or something more clever) outstanding thunks
> right before going into one of those operations and stop it when it's back.
>
> Of course, it's not like optimistic evaluation because we don't avoid
> creating thunks. But in a sense it's similar. It could also be compared with
> incremental garbage collection :)
>
> Has something like that been done, discussed?
>

This sounds like it could be helpful in certain circumstances, but in many
cases it could probably lead to unpredictable (and uncontrollable!) memory
usage.  I could imagine a situation where my program is running along just
fine, and then one day it takes a long time to do a read from the network
due to latency or whatever, and suddenly memory usage shoots through the
roof, due to evaluation of some infinite (or even just very large) data
structure.

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


Re: [Haskell-cafe] pls help about subtree

2008-04-29 Thread Brent Yorgey
2008/4/28 cetin tozkoparan <[EMAIL PROTECTED]>:

> Assume a tree is a subtree of the other if all elements of the first tree
> is included in the second with the exact structure; all parent-child
> relations are preserved with their order.
>
> data Tree = Empty | Leaf Int | Node (Int,Tree,Tree)
> subtree:: Tree -> Tree -> Bool
>

Let me also point out that since you store an Int at each Node, there is no
need for the explicit Leaf constructor; for example, Leaf 5 can be
represented as  Node 5 Empty Empty.  Simplifying your data structure in this
way will make writing code for it much simpler and more elegant.

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


Re: [Haskell-cafe] force inlining in GHC

2008-04-29 Thread Bulat Ziganshin
Hello Henning,

Tuesday, April 29, 2008, 2:01:39 PM, you wrote:

> However, in the Core output 'doubleFunc' does not get the __inline_me tag
> and thus will not be inlined, too. :-(

ghc is so smart that sometimes it fool itself :D  i bet that in this case
generic and specific functions are considered as equivalent :)

ps: why you not wrote to ghc users list?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] force inlining in GHC

2008-04-29 Thread Simon Peyton-Jones
As luck would have it, I'm working on INLINE pragmas for Roman right at this 
moment.

Could you spare a moment to give me a concrete test case, to make sure I hit 
your case too? If you can give me a program that doesn't optimise as you 
expect, I'm much more likely to get it right.

Thanks

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Henning
| Thielemann
| Sent: 29 April 2008 11:02
| To: Haskell Cafe
| Subject: [Haskell-cafe] force inlining in GHC
|
|
| Whenever I try to inline a lot of nested function calls, GHC decides to
| specialise one of the functions and the specialised function is no longer
| inlined. I hoped to get the function inlined anyway by specialising it
| manually. Say, I want to inline genericFunc
|
| {-# INLINE genericFunc #-}
| genericFunc :: RealFrac a => a -> Int
|
| but GHC inserts a call to genericFunc1 specialised to a=Double where I
| apply genericFunc to a Double argument.
|
| Now I define
|
| {-# INLINE doubleFunc #-}
| doubleFunc :: Double -> Int
| doubleFunc = genericFunc
|
| However, in the Core output 'doubleFunc' does not get the __inline_me tag
| and thus will not be inlined, too. :-(
| ___
| 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] force inlining in GHC

2008-04-29 Thread Henning Thielemann


Whenever I try to inline a lot of nested function calls, GHC decides to 
specialise one of the functions and the specialised function is no longer 
inlined. I hoped to get the function inlined anyway by specialising it 
manually. Say, I want to inline genericFunc


{-# INLINE genericFunc #-}
genericFunc :: RealFrac a => a -> Int

but GHC inserts a call to genericFunc1 specialised to a=Double where I 
apply genericFunc to a Double argument.


Now I define

{-# INLINE doubleFunc #-}
doubleFunc :: Double -> Int
doubleFunc = genericFunc

However, in the Core output 'doubleFunc' does not get the __inline_me tag 
and thus will not be inlined, too. :-(

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