On Mon, Oct 11, 2004 at 04:35:30PM +0100, Simon Peyton-Jones wrote:
> Ah I see. You get earlier results, but the overall computation is
> unchanged.
>
> Hmm. I can't say I'm persuaded. The transformation is unsound in
> general and, because it makes programs lazier, it'll slow programs down
>
Hi,
If I have two modules which are mutually recursive;
module A where
data TA = TA String deriving (Data, Typeable)
module B where
data TB = TB TA deriving (Data, Typeable)
How do I got about writing a hi-boot that will work in GHC? The problem
is that to do proper XML Schema mappi
I cvs-updated my copy moments ago, but I still get this
error when compiling my ADNS.hsc bindings with the new
version:
> /tmp/ghc12865.hc: In function `s8Ej_ret':
> /tmp/ghc12865.hc:6355: error: `ADNS_d7gS' undeclared (first use in this function)
> /tmp/ghc12865.hc:6355: error: (Each undeclare
Ah I see. You get earlier results, but the overall computation is
unchanged.
Hmm. I can't say I'm persuaded. The transformation is unsound in
general and, because it makes programs lazier, it'll slow programs down
a bit; in exchange there's the possibility of earlier output (which may
or may n
On Mon, Oct 11, 2004 at 04:32:08PM +0400, Serge D. Mechveliani wrote:
> First, thanks to the people who correct me about `equivalence',
> (I skip the name because the letter was addressed privately).
>
> Because we do not mean to compile each program to the equivalent
> one of
> error "bot
First, thanks to the people who correct me about `equivalence',
(I skip the name because the letter was addressed privately).
Because we do not mean to compile each program to the equivalent
one of
error "bottom"
On Mon, Oct 11, 2004 at 12:44:49PM +0100, Simon Peyton-Jones wrote:
> Can y
Can you give a small program that runs 1000x faster in one form compared
with the other?
Currently, if foo is strict, GHC transforms (2) into (1), not the other
way round. In general, transforming (1) into (2) looks hard, because it
means finding the common portions of two expressions. But I'd b
On Mon, 11 Oct 2004, Serge D. Mechveliani wrote:
> How do you think, is the program (1) equivalent to (2)
> in the meaning of Haskell-98 ?
Not at all. If foo is non-strict and p partial, (2) may yield a result
where (1) would not. You identify the possibility yourself: (2) is lazier.
> (1) (\
Serge,
How do you think, is the program (1) equivalent to (2)
in the meaning of Haskell-98 ?
(1) (\ x -> (if p x then foo (g x) else foo (h x))
where
p ... g ... h ... foo ...
)
(2) (\ x -> foo ((if p x then g x else h x)
where
On 11 October 2004 05:37, Serge D. Mechveliani wrote:
> I am not sure but have such an impression that the -K option
> (for the stack size) appears and disappears between the GHC
> versions.
Nope, the -K option has always been there.
> ghc-6.2.2-September-26 requires -K to be set independentl
On 10 October 2004 02:01, Peter Simons wrote:
> in a module I am writing, I am using a 'StateT st IO' monad
> with a state like this:
>
> data MyState st = ST !Int !st
>
> My own monad is yet-another wrapper for ... another state
> monad. And that's getting inconvenient.
>
> So I wondered whe
Dear Haskell implementors,
Consider the compilation flag -allow-extension-for-bottom
which changes the language meaning so that allows to ignore
the bottom value. For example, the programs
(1) (\ x -> (if p x then foo (g x) else foo (h x)) )
and
(2) (\ x -> foo ((if p x then g x
Hi!
On Mon, Oct 11, 2004 at 02:19:45PM +0400, Serge D. Mechveliani wrote:
> Dear Haskell implementors,
>
> How do you think, is the program (1) equivalent to (2)
> in the meaning of Haskell-98 ?
>
> (1) (\ x -> (if p x then foo (g x) else foo (h x))
> where
> p
Dear Haskell implementors,
How do you think, is the program (1) equivalent to (2)
in the meaning of Haskell-98 ?
(1) (\ x -> (if p x then foo (g x) else foo (h x))
where
p ... g ... h ... foo ...
)
(2) (\ x -> foo ((if p x then g x else h x)
14 matches
Mail list logo