[Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Thomas Hartman

I just thought this was interesting, so I would share it.

Thanks to whoever it was on #haskell who helped me, sorry I can't remember who.

-- horribly slow. try slow_fibs 30, not too much higher than that and it hangs
slow_fibs = map slow_fib [1..]
slow_fib 1 = 1
slow_fib 2 = 1
slow_fib n = ( slow_fib (n-2) )  + (slow_fib(n-1))

-- versus, try memoized_fibs !! 1
memoized_fibs = map memoized_fib [1..]
memoized_fib = ((map fib' [0 ..]) !!)
   where
 fib' 0 = 0
 fib' 1 = 1
 fib' n = memoized_fib (n - 1) + memoized_fib (n - 2)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Felipe Almeida Lessa

On 2/18/07, Thomas Hartman [EMAIL PROTECTED] wrote:

-- versus, try memoized_fibs !! 1
memoized_fibs = map memoized_fib [1..]
memoized_fib = ((map fib' [0 ..]) !!)
where
  fib' 0 = 0
  fib' 1 = 1
  fib' n = memoized_fib (n - 1) + memoized_fib (n - 2)


How about this:
zip_fibs = 0 : 1 : [x+y | ~(x,y) - zip zip_fibs (tail zip_fibs)]
zip_fib = (!!) zip_fibs



A naïve performance test:


module Main (main) where

import System (getArgs)

zip_fibs = 0 : 1 : [x+y | ~(x,y) - zip zip_fibs (tail zip_fibs)]
zip_fib = (!!) zip_fibs

memoized_fibs = map memoized_fib [1..]
memoized_fib = ((map fib' [0 ..]) !!)
  where
fib' 0 = 0
fib' 1 = 1
fib' n = memoized_fib (n - 1) + memoized_fib (n - 2)

main = do
 [func,arg] - getArgs
 let n = read arg
 case func of
   zip_fib - do
 putStrLn $ Using 'zip_fib' to calculate fib of  ++ arg
 putStrLn $  -  ++ show (zip_fib n)
   memoized_fib - do
 putStrLn $ Using 'memoized_fib' to calculate fib of  ++ arg
 putStrLn $  -  ++ show (memoized_fibs !! n)



$ rm *.o

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.4.2

$ ghc -O fib.hs

$ time ./a.out zip_fib 2
Using 'zip_fib' to calculate fib of 2
- 25311623237323612422[...]39857683971213093125

real0m0.140s
user0m0.106s
sys 0m0.001s

$ time ./a.out memoized_fib 2
Using 'memoized_fib' to calculate fib of 2
- 25311623237323612422[...]39857683971213093125

real0m30.787s
user0m29.509s
sys 0m0.156s

$ time ./a.out zip_fib 20
Using 'zip_fib' to calculate fib of 20
- 15085683557988938992[...]52246259408175853125
real0m24.790s
user0m23.649s
sys 0m0.159s

No, I *won't* try './a.out memoized_fib 20'  ;-).

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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Yitzchak Gale

Besides memoizing, you might want to use the fact
that:

fib (2*k) == (fib (k+1))^2 - (fib (k-1))^2
fib (2*k-1) == (fib k)^2 + (fib (k-1))^2

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


[Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
Why do I have to specify (Monad m) here again?

class (Monad m) = GetMV m a where
...

instance GetMV m c where
...

No instance for (Monad m)
   arising from the superclasses of an instance declaration
possible fix:
   add (Monad m) to the instance declaration superclass context

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


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Sebastian Sylvan

On 2/18/07, Marc Weber [EMAIL PROTECTED] wrote:

Why do I have to specify (Monad m) here again?

class (Monad m) = GetMV m a where
...

instance GetMV m c where
...

No instance for (Monad m)
   arising from the superclasses of an instance declaration
possible fix:
   add (Monad m) to the instance declaration superclass context



The class just says that any instance *requires* an instance in Monad.
Nothing more.
So when you try to instantiate something in the class you have to
ensure that it has an instance in Monad. A type variable m has no
instance in the class Monad unless you constrain it to do so in the
instance declaration (by doing Monad m =).

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to solve this problem?It's quite easy in PHP.

2007-02-18 Thread Henk-Jan van Tuyl

On Fri, 16 Feb 2007 22:44:25 +0100, David House [EMAIL PROTECTED] wrote:


On 16/02/07, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:

Yet simpler:
 formatTableItems (a,b) = a :  =  ++ (show b) ++ \n


You can drop the parentheses around 'show b'; infix function
application always binds tighter than pretty much everything else.


I missed that one; of course I knew it, but you could say it's in my  
passive vocabulary.




--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
--

Using Opera's revolutionary e-mail client:
https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

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


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
On Sun, Feb 18, 2007 at 05:06:33PM +0300, Bulat Ziganshin wrote:
 Hello Marc,
 
 Sunday, February 18, 2007, 5:21:36 PM, you wrote:
 
  Why do I have to specify (Monad m) here again?
 
  class (Monad m) = GetMV m a where
 
  instance GetMV m c where
 
 because you can find another way to ensure that m is monad. for
 example,
 
 instance (MonadIO m) = GetMV m c where
 
 if i not yet proposed you to read
 http://haskell.org/haskellwiki/OOP_vs_type_classes
 then now it is time to do it :)

I think I've read it once. But I'll do it again more thoroughly ..

I'll try to explain why I don't get it yet

class (Monad m) = GetMV m a where (1)

tells that the first param called 'm' is an instance of class m, right?
Then it doesn't matter wether I use
instance GetMV m  c where 
or
instance GetMV any name c where

If the class sepecification (1) forces m to be a monad, any name has to be
one, too(?)

When using your example (Monad IO):
class (Monad m) = MonadIO m where
liftIO :: IO a - m a
it it basically the same, isn't it?  This declaration forces m to be monad..
which would't hurt if GHC would infer m beeing a monad automatically?

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


Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Bulat Ziganshin
Hello Marc,

Sunday, February 18, 2007, 7:32:54 PM, you wrote:

 When using your example (Monad IO):
 class (Monad m) = MonadIO m where
 liftIO :: IO a - m a
 it it basically the same, isn't it?  This declaration forces m to be monad..
 which would't hurt if GHC would infer m beeing a monad automatically?

it is more explicit. for example, this simplifies understanding of
error messages generated by compiler. and, if you change 'class'
declaration, this will not silently change meaning of 'instance' declaration


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
On Sun, Feb 18, 2007 at 06:59:32PM +0300, Bulat Ziganshin wrote:
 Hello Marc,
 
 Sunday, February 18, 2007, 7:32:54 PM, you wrote:
 
  When using your example (Monad IO):
  class (Monad m) = MonadIO m where
  liftIO :: IO a - m a
  it it basically the same, isn't it?  This declaration forces m to be monad..
  which would't hurt if GHC would infer m beeing a monad automatically?
 
 it is more explicit. for example, this simplifies understanding of
 error messages generated by compiler. and, if you change 'class'
 declaration, this will not silently change meaning of 'instance' declaration

Is there a difference at all wehter specifying (Monad m) in the class
declaration or not? I have to add it to the instance declaration
anyway..
And if you don't want to change the meaning of instance declaration you
would be able to add this constraint to indicate this.

I don't see why it simplifies error messages.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David Tolpin

 which would't hurt if GHC would infer m beeing a monad automatically?

 it is more explicit. for example, this simplifies understanding of
 error messages generated by compiler. and, if you change 'class'
 declaration, this will not silently change meaning of 'instance' declaration


Hello Bulat,

do you mean that the fact that one must keep class and instance declaration in 
agreement manually is an advantage and not just a limitation of the Haskell 
type system? Why then not just require that all constraints be declared 
explicitly. The following code compiles: is it a bad thing that it does?

class (Eq a) = Eql a where
(=:=) :: a - a - Bool
x =:= y = x == y

eql :: Eql a = a - a - Bool
eql x y = x == y


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


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David House

On 18/02/07, Marc Weber [EMAIL PROTECTED] wrote:

Is there a difference at all wehter specifying (Monad m) in the class
declaration or not? I have to add it to the instance declaration
anyway..


If you have, say:

class Monad m = Foo m where ...

Then it's illegal to say:

instance Foo Data.Set.Set where ...

Because Data.Set.Set doesn't instantiate Monad. Including the
constraint in the class header forces every instance to satisfy that
constraint in order for it to be a valid instance. In effect, Monad is
a superclass of Foo. Similarly, you can't say:

instance Foo m where ...

Because, in general, m doesn't instatiate Monad. You have to use
(Monad m = m) instead:

instance Foo (Monad m = m) where ...

Which is more normally written:

instance Monad m = Foo m where ...

Incidentally, you're here saying that:

i) Every type T that instantiates Foo must also instantiate Monad (due
to the constraint on the class head).
ii) Every type T that instantiates Monad also instantiates Foo (due to
the instance Monad m = Foo m).

So Foo and Monad both have exactly the same member types.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David House

On 18/02/07, David Tolpin [EMAIL PROTECTED] wrote:

The following code compiles: is it a bad thing that it does?

class (Eq a) = Eql a where
(=:=) :: a - a - Bool
x =:= y = x == y

eql :: Eql a = a - a - Bool
eql x y = x == y


The reason this typechecks:

1) The compiler infers that x and y must have a type which instantiates Eq.
2) Therefore, it infers the type eql :: Eq a = a - a - Bool
3) This doesn't match up with the type you specified for eql, though,
so we need to check that your specified type is a specialisation of
the inferred type (see below for a more thorough explanation).
4) It is; if we know that x has a type which instantiates Eql, then we
can prove that this type also instantiates Eq, by the constraint on
the class head of Eql.
5) The program is accepted.

Step 3 may need more explanation. We can use type signatures to
specify a polymorphic type down to a less polymorphic one. For
example, if you wrote:

id x = x

Then the compiler infers id :: a - a. However, if you only wanted id
to work on Ints, then you could write:

id :: Int - Int
id x = x

This program would still be accepted, because Int - Int is less
polymorphic than a - a, i.e., you can get from a - a to Int - Int
by chosing the substitution a = Int. You could also decide that you
only wanted id to work on instances of Show:

id :: Show s = s - s
id x = x

This'd work, again, because you can get from a - a to Show s = s -
s by chosing the substitution a = Show s = s (note that (Show s = s)
- (Show s = s) is the same as Show s = s - s). Show s = s - s is
still a polymorphic type, but it's less polymorphic than a - a (the
latter is defined over all types, the former only over types that are
instances of Show).

HTH.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David House

On 18/02/07, David Tolpin [EMAIL PROTECTED] wrote:

how is this different from inferring that if a type variable is an instance of 
class it is subject to constraints imposed on the class?


I think you, and probably Marc Weber as well, are confusing what a
constraint on a class head means. Suppose you have:

class Monad m = Foo m

That constraint means that every instance of class Foo must also be an
instance of class Monad. So, as I explained in my email to Marc, we
must use:

instance Monad m = Foo m

And not:

instance Foo m

Because, in general, m isn't an instance of Monad. In your example, we
already have two types with instances of Eql, which means, by the
constraint on the class head of Eql, these types are also instances of
Eq, which makes the program valid. If you like, think about it this
way: in order for your function body to be valid, the compiler has to
prove that the types of the arguments to eql are instances of Eq
(because you're using == on them). It knows they're instances of Eql
by the type signature you provided, and from that it can prove that
they're also instance of Eq by the constraint on class head of Eql.

I think these are two completely different things to compare and say
'how are they different', but if you wanted a pithy sentence to try
and explain the differences between them, perhaps it's that in Marc's
example we're declaring an instance of a type where the class required
that the instance type must also instantiate some other class (Monad).
With your example, we're declaring a function, not an instance, that
requires an instance of Eql and needs one of Eq, but can find the
latter because of the class constraint.

HTH more this time :)

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
David: Thanks again for your explanation
 
 Because, in general, m isn't an instance of Monad. 

Talking about my example:

class (Monad m) = GetMV m a where
...
instance GetMV m c where (2)

(2) There are only 2 cases:
ghc supposes m does instantiates Monad
  = success
ghc doesn't suppose this
  = failure becuase the class head of GetMV does require it.
 fix: adding (Monad m) = (3)

That's why it would be save to assume that the programmer doesn't want a
failure but success.
Thus ghc could infer (3) automatically but doesn't

Do I still miss a point?

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


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Matthew Brecknell
Marc Weber said:
 I'll try to explain why I don't get it yet
 
   class (Monad m) = GetMV m a where (1)
 
 tells that the first param called 'm' is an instance of class m, right?
 Then it doesn't matter wether I use
   instance GetMV m  c where 
 or
   instance GetMV any name c where
 
 If the class sepecification (1) forces m to be a monad, any name has to
 be
 one, too(?)

Let's look at this from another angle: What are you achieving with your
class/instance definitions that you couldn't achieve with a simple
function?

I'm not sure what methods you have, so I'll use the following for the
purpose of discussion. I'm reverting to a single-parameter type class,
since the multi-parameter type class might be clouding the issue:

 class Monad m = MonadFoo m where
   foo :: m Int
 
 instance Monad m = MonadFoo m where
   foo = return 42

How is the above different from just writing the following?

 foo' = return 42

Well, they do have slightly different types:

 foo :: MonadFoo m = m Int
 foo' :: Monad m = m Int

But practically speaking, the MonadFoo class is no different to the
Monad class. For a start, every member of the Monad class is also a
member of the MonadFoo class, according to the sole instance
declaration. Further, you can't define any other instance of MonadFoo,
because it would conflict with the above instance. You're stuck with a
single instance, which means you don't gain anything over the standalone
function.

My point is that the case you're trying to save a few keystrokes on is
not really that useful. Indeed, the point of classes and instances is to
allow different types to inhabit the same class with different
implementations, and to allow other types to not inhabit the class at
all.

Contexts on instance declarations allow you to write an instance which
covers a range of types, but usually the range of types is a proper
subset of the class. It would be rare (if ever) that you would write an
instance declaration covering the entire class, as I've done above.
(Actually, you might do this if you start using overlapping and
undecidable instances, but that's over my head).

I suggest you look through the base libraries to see how contexts on
instance declarations are used in practice.

 When using your example (Monad IO):
   class (Monad m) = MonadIO m where
   liftIO :: IO a - m a
 it it basically the same, isn't it?  This declaration forces m to be
 monad..
 which would't hurt if GHC would infer m beeing a monad automatically?

And here's a concrete example. The class definition requires that m be a
Monad before it can be a MonadIO, but here's the important bit: not
every Monad will be a MonadIO. So you would not want an instance
declaration that makes that assumption.


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


Re: [Haskell-cafe] Looking for documentation on Control.Parallel.Strategies

2007-02-18 Thread Cale Gibbard

On 16/02/07, Pepe Iborra [EMAIL PROTECTED] wrote:

There is also an excellent paper in tutorial style which imho is very
useful to understand the interaction of lazyness with the
Control.Parallel.Strategies combinators:

Algorithm + Strategy = Parallelism
Philip W. Trinder, Kevin Hammond, Hans-Wolfgang Loidl, and Simon L.
Peyton Jones. Journal of Functional Programming, 8(1), Jan 1998.
http://www.macs.hw.ac.uk/~dsg/gph/papers/abstracts/strategies.html


Indeed, it would be good if the new Haddock linked to this as well.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[4]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Bulat Ziganshin
Hello Marc,

 That's why it would be save to assume that the programmer doesn't want a
 failure but success.

generally speaking, languages like Haskell introduces strong typing
exactly to avoid false successes


-- 
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] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Yitzchak Gale

Hi Marc,

Marc Weber wrote:

class (Monad m) = GetMV m a where
...
instance GetMV m c where (2)

...it would be save to assume that the programmer doesn't want a
failure but success.
Thus ghc could infer (3) automatically but doesn't


The Monad m on the class declaration does
not mean that the programmer _wants_ m to be
a monad. It means that the programmer _promises_
to make m a monad - even more, the programmer
wants the compiler to force anyone using this
class to first make m a monad, and otherwise
enforce type safety by failing to compile.

This is very good, because then any future use
of an instance of GetMV can be safely assumed
to have also a Monad instance, no matter what its
type. One place you can use that nice assumption
is in the method declarations within the original
class declaration itself. Another is in function
definitions, as you say.

But when writing an instance declaration, it is
time to pay up. You made a promise. Now you
have to show the compiler where to get that Monad
instance. There are two ways of doing that.
One way is if the type itself already has a separate
Monad instance. The other way is if the type is
not fully specified - it is a variable - then you can
pass the buck and say that whoever uses this
instance must first make sure that the value of
the type variable is a type that already has a
Monad instance.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Yitzchak Gale

I wrote:

The other way is if the type is
not fully specified - it is a variable - then you can
pass the buck and say that whoever uses this
instance must first make sure that the value of
the type variable is a type that already has a
Monad instance.


In this case, you are creating an obligation
on users of this instance - they are required
to provide the Monad instance themselves.

So it makes sense that you need to write the
constraint Monad m = on the instance
declaration, to make sure this obligation is
clear to the users of the instance.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Sebastian Sylvan

On 2/18/07, David Tolpin [EMAIL PROTECTED] wrote:



 I think you, and probably Marc Weber as well, are confusing what a
 constraint on a class head means. Suppose you have:

 class Monad m = Foo m

 That constraint means that every instance of class Foo must also be an
 instance of class Monad. So, as I explained in my email to Marc, we
 must use:

 instance Monad m = Foo m

 And not:

 instance Foo m

 Because, in general, m isn't an instance of Monad.

Hi David,

Why the compiler cannot infer  class constraint on m from class definition in 
instance definition while it can in function type definition?


But it can't! If you give a type to a function, it will assume zero
class constraints unless you specify them (just like it will when you
give a type to an instance declaration). If you do something like:

foo :: [a] - a
foo  = head . sort

It will *not* compile. sort requires Ord, but that does *not* mean
that you can write a type declaration with just a type variable and
have it automatically infer that you need an Ord constraint and add
it for you (in fact, that's a good thing, it will tell you that you
forgot an Ord constraint, which may be symptomatic of some other
problem).

If you write down a type explicitly, Haskell will not change it for
you into something else just to make the program compile. It *could*
infer that the type for foo above needs to have an Ord constraint
and just add it, but if it did then the whole point of type checking
would be disappear. You *want* an error when types don't match!
With functions you can leave out the type and Haskell will infer a
type (which will have the correct constraints), but we don't have the
option of leaving out the types when declaring instances. Haskell
doesn't have any instance inference (and I'm not sure what that
would even mean), you have to give the type of your instance
explicitly, and when doing so you are not allowed to skip parts of the
type because they are required elsewhere. Again, just like with
functions, Haskell will not change your supplied type into something
else if there is a mismatch, it will give you an error instead (which
is what you want).

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Fwd: Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David Tolpin


--- Forwarded message ---
From: David Tolpin [EMAIL PROTECTED]
To: Sebastian Sylvan [EMAIL PROTECTED]
Cc: David House [EMAIL PROTECTED], haskell-cafe@haskell.org
Subject: Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here 
again?
Date: Sun, 18 Feb 2007 23:38:59 +0400

 Why the compiler cannot infer  class constraint on m from class definition 
 in instance definition while it can in function type definition?

 But it can't! If you give a type to a function, it will assume zero
 class constraints unless you specify them (just like it will when you
 give a type to an instance declaration). If you do something like:


Hi Sebastian,

it is not the example I brought. In the example I brought I showed how in
function type declaration assertion that an instance of a class is also an
instance of the other class is used. Take a look at my example. According
to what part of the type system logic type inference in instances is not
implemented?

David


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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Felipe Almeida Lessa

On 2/18/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

Besides memoizing, you might want to use the fact
that:

fib (2*k) == (fib (k+1))^2 - (fib (k-1))^2
fib (2*k-1) == (fib k)^2 + (fib (k-1))^2


Nice one:
$ time ./a.out another_fib 20
Using 'another_fib' to calculate fib of 20
- 15085683557988938992[...]52246259408175853125

real0m1.177s
user0m1.051s
sys 0m0.017s


Implementation details:
-
another_fibs = 0 : 1 : 1 : map f [3..]
   where
 square x = x * x
 sqfib = square . another_fib
 f n | even n = sqfib (k+1) - sqfib (k-1) where k = n `div` 2
 f n  = sqfib k + sqfib (k-1) where k = (n + 1) `div` 2
another_fib = (!!) another_fibs
-

Conclusion: it's often better to improve the algorithm than the
implementation =).

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Sebastian Sylvan

On 2/18/07, David Tolpin [EMAIL PROTECTED] wrote:

 Why the compiler cannot infer  class constraint on m from class
 definition in instance definition while it can in function type
 definition?

 But it can't! If you give a type to a function, it will assume zero
 class constraints unless you specify them (just like it will when you
 give a type to an instance declaration). If you do something like:


Hi Sebastian,

it is not the example I brought. In the example I brought I showed how in
function type declaration assertion that an instance of a class is also an
instance of the other class is used. Take a look at my example. According
to what part of the type system logic type inference in instances is not
implemented


That's completely different. The class in that case guarantees that
the type has an Eq class, so it's okay to use the functions in the
Eq class. You're using the guarantees supplied by the class. When
you write instances, it's the other way around, the class has
*requirements* that you must fulfill -- and there are multiple ways of
doing it (Haskell won't guess, it will obey what you tell it -- if you
don't give any class constraints it won't assume that they are there).

The point I'm trying to make is that if you say that something is of a
given type, Haskell will assume that you know what you're talking
about. I.e. if you give a type which has no class constraints, Haskell
will assume that you don't want any class constraints -- if this
conflicts with something else, you will get an error.

I think maybe this is where you're missing the point. *Leaving out*
class constraints says something about the type. In other words, if
you leave out a class constraint that does *not* mean that you don't
care what class constraints the type variable has, it explicitly means
that there are *no* class constraints on it (and using it in a context
where a class constraint is required, is thus an error).

In this case you *require* that any instances of a class is also an
instance of the Monad class. But then you try to instantiate a type
which is *not* in the monad class in this class. This is a conflict,
and you should get an error. If you want to construct a type which is
in the Monad class by constraining the type variable m to the Monad
class, then that's fine, but you have to tell Haskell that this is
what you want to do -- if you say that your type has *no* class
constraints, it will take your word for it an report the conflict.
Another alternative is that you want to produce the type by using a
concrete type called, say,  M which is in the Monad class, then
that's also fine. Haskell won't guess what you meant (it can either be
a spelling error, m for M, or that you forgot to add Monad m =
in the instance declaration, or anynumber of other errors) and change
it for you. Whenever you write something out, Haskell will take your
word for it, if it fails, it's your fault, and Haskell will tell you
what the problem is.


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David Tolpin

 That's completely different. The class in that case guarantees that
 the type has an Eq class, so it's okay to use the functions in the
 Eq class. You're using the guarantees supplied by the class. When
 you write instances, it's the other way around, the class has
 *requirements* that you must fulfill -- and there are multiple ways of
 doing it (Haskell won't guess, it will obey what you tell it -- if you
 don't give any class constraints it won't assume that they are there).

Hi Sebastian,

could you please point me to a reference (paper/note/something else) that 
explains that class constraint
in a class definition is a guarantee with regard to a type declaration but a 
requirement with regard to an instance
declaration?

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


Re: [Haskell-cafe] Very fast loops. Now!

2007-02-18 Thread Henning Thielemann

On Sun, 11 Feb 2007, Donald Bruce Stewart wrote:

 The following C program was described on #haskell

 #include stdio.h

 int main()
 {
 double x = 1.0/3.0;
 double y = 3.0;
 int i= 1;
 for (; i=10; i++) {
 x = x*y/3.0;
 y = x*9.0;
 }
 printf(%f\n, x+y);
 }


 Which was translated to the following Haskell:

 {-# OPTIONS -fexcess-precision #-}

 import Text.Printf

 main = go (1/3) 3 1

 go :: Double - Double - Int - IO ()
 go !x !y !i
 | i == 10 = printf %f\n (x+y)
 | otherwise   = go (x*y/3) (x*9) (i+1)

No one doubts, that it is possible to write efficient code in Haskell. But
how does idiomatic Haskell code perform?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
 i mean that it makes error message more obvious - you don't need to
 remember that this context is implied due to class declaration

The error might look like
Missing instance (Ord m) araising from use of ...  imposed by
automatically infered class constraint from context line xy ? ;)

Something like this is done anyway if you omit the type declaration..
(And I have to admit that there were times I had trouble understanding
them .. *g* )

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Sebastian Sylvan

On 2/18/07, David Tolpin [EMAIL PROTECTED] wrote:


 That's completely different. The class in that case guarantees that
 the type has an Eq class, so it's okay to use the functions in the
 Eq class. You're using the guarantees supplied by the class. When
 you write instances, it's the other way around, the class has
 *requirements* that you must fulfill -- and there are multiple ways of
 doing it (Haskell won't guess, it will obey what you tell it -- if you
 don't give any class constraints it won't assume that they are there).

Hi Sebastian,

could you please point me to a reference (paper/note/something else) that 
explains that class constraint
in a class definition is a guarantee with regard to a type declaration but a 
requirement with regard to an instance
declaration?



Well, I guess the H98 report would be a good start. But there are
multiple tutorials on type classes that will cover this, most of which
are available from haskell.org

The key point is that Haskell won't guess, and in particular it won't
contradict what you tell it. I think that's the major flaw in your
reasoning, you expect Haskell to take an explicit type that you, the
programmer, supplies, and change it into something else. That's
obviously not a very good idea -- when there's a conflict, it should
give an error.
In the original example you are explicitly telling Haskell that m is
*not* in the Monad (or any other) class. Why would you want Haskell to
ignore what you are telling it and go behind your back?

Another way to view this specific issue is that it's two-sided -- if
you on the one hand have a guarantee that something holds, then
logically on the other side there must be a requirement to fulfill
that guarantee.
Now, if you have a guarantee (e.g. if a variable is in the Ord class,
you are allowed to use (==) due to Eq being a super class), you can
just make use of that guarantee without any further fuss. But if you
have a *requirement* then it's a completely different story since
there are any number of ways to fulfill that requirement (Haskell is,
sadly, incapable of reading the programmer's mind). Take the example I
gave earlier; maybe the m in the original example was supposed to be
M (a type in the Monad class), or maybe it was supposed to be
constrained to Monad, or any other class which has Monad in its
class hierarchy. Haskell has *no* way of knowing how you intend to
fulfill the requirement that any instance in your class is a Monad
(which is required to fulfill the guarantee that the functions in
Monad can be used on any instance of your class), and it won't guess.


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread David Tolpin
On Mon, 19 Feb 2007 00:30:47 +0400, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 Well, I guess the H98 report would be a good start. But there are
 multiple tutorials on type classes that will cover this, most of which
 are available from haskell.org

Sebastian,

I did read H98 and would like an exact reference.


 The key point is that Haskell won't guess, and in particular it won't
 contradict what you tell it. I think that's the major flaw in your
 reasoning, you expect Haskell to take an explicit type that you, the
 programmer, supplies, and change it into something else.

Why is this rule applied differently to type declarations and to instances?


 In the original example you are explicitly telling Haskell that m is
 *not* in the Monad (or any other) class.

I am not telling that. I am telling that m is an instance of a class all 
instances of which are in the Monad class. How is this different from 
specifying class constraint in type declarations?

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Sebastian Sylvan

On 2/18/07, David Tolpin [EMAIL PROTECTED] wrote:

On Mon, 19 Feb 2007 00:30:47 +0400, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 Well, I guess the H98 report would be a good start. But there are
 multiple tutorials on type classes that will cover this, most of which
 are available from haskell.org

Sebastian,

I did read H98 and would like an exact reference.


I'm sorry, I don't have the time to look it up for you. There are tons
of resource on this issue. I'm trying to explain it to you, if you
don't believe me then you'll just have to make do without my help.




 The key point is that Haskell won't guess, and in particular it won't
 contradict what you tell it. I think that's the major flaw in your
 reasoning, you expect Haskell to take an explicit type that you, the
 programmer, supplies, and change it into something else.

Why is this rule applied differently to type declarations and to instances?



It isn't. What makes you think it is? If you supply a type it will
trust you with that type. It won't change it into something else.
That's always true.



 In the original example you are explicitly telling Haskell that m is
 *not* in the Monad (or any other) class.

I am not telling that. I am telling that m is an instance of a class all 
instances of which are in the Monad class. How is this different from 
specifying class constraint in type declarations?


No, you're saying I want to instantiate this type into a class which
*requires* that all instances are in the Monad class. The thing is
that there are multiple ways of meeting this requriement, and Haskell
has no way of guessing which way you intended to do it.

A type variable m without any class constraints means exactly that,
here's a type variable, it has no class constraints. The *absence*
of class constraints is significant -- it doesn't mean I don't care,
it means I care, and there are no constraints. And a type variable
with no constraints in a context which requires constraints is a type
error.

How is Haskell supposed to know if you want to inject a Monad class
constraint or not, in your original example? You could just as well
add, say, MonadIO or MonadPlus or any other classes which have
Monad in their class hierarchy, any one of which would satisfy the
requirement that m needs to be in the Monad class. Also, the
misstake might be due to a spelling error, or any number of other
errors. I don't understand why you would want Haskell to ignore the
explicit type you are giving (in the instance declaration), which has
no constraints, and do something else instead.


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Summarize of Why do I have to specify (Monad m) here again?

2007-02-18 Thread Marc Weber
Thanks for all the feedback. It did help me a lot.

Now I know that if there is something left to discuss the topic should
be:
Would it make sense to specify partial type declarations ?
I don't need an answer right now.

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


Re: [Haskell-cafe] Summarize of Why do I have to specify (Monad m) here again?

2007-02-18 Thread David Tolpin
On Mon, 19 Feb 2007 02:17:34 +0400, Marc Weber [EMAIL PROTECTED] wrote:

 Thanks for all the feedback. It did help me a lot.

 Now I know that if there is something left to discuss the topic should
 be:
 Would it make sense to specify partial type declarations ?
 I don't need an answer right now.

Hi Marc,

no, it wouldn't. It would make sense to draw the arrow in the class definition 
in the opposite direction. It does not point in the direction it should in the 
class case.

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Dean Herington

At 12:42 AM +0400 2/19/07, David Tolpin wrote:
On Mon, 19 Feb 2007 00:30:47 +0400, Sebastian Sylvan 
[EMAIL PROTECTED] wrote:

 Well, I guess the H98 report would be a good start. But there are
 multiple tutorials on type classes that will cover this, most of which
 are available from haskell.org


Sebastian,

I did read H98 and would like an exact reference.


See section 4.3.2, the third bullet item in the bulleted list.  (Note 
that the last sentence of that bullet item says that context 
inference--though often possible--is deliberately eschewed.)






 The key point is that Haskell won't guess, and in particular it won't
 contradict what you tell it. I think that's the major flaw in your
 reasoning, you expect Haskell to take an explicit type that you, the
 programmer, supplies, and change it into something else.


Why is this rule applied differently to type declarations and to instances?



 In the original example you are explicitly telling Haskell that m is
 *not* in the Monad (or any other) class.


I am not telling that. I am telling that m is an instance of a class 
all instances of which are in the Monad class. How is this different 
from specifying class constraint in type declarations?


David

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


Re: Re[2]: [Haskell-cafe] Why do I have to specify (Monad m) here again?

2007-02-18 Thread Yitzchak Gale

David Tolpin wrote:

could you please point me to a reference
(paper/note/something else) that explains
that class constraint in a class definition
is a guarantee with regard to a type declaration
but a requirement with regard to an instance
declaration?


Sebastian Sylvan wrote:

Well, I guess the H98 report would be a good start.


I'm not sure that is a good place to start.

True, it is likely possible to deduce both
of those facts from the Report. But the Report
is a language spec. It assumes that you
already know about the type system, and
it is difficult to read if you don't.


...there are multiple tutorials on type classes
that will cover this, most of which
are available from haskell.org


That sounds like a much better idea.
Any particular suggestions?

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


[Haskell-cafe] Re: Summarize of Why do I have to specify (Monad m) here again?

2007-02-18 Thread Benjamin Franksen
David Tolpin wrote:
 On Mon, 19 Feb 2007 02:17:34 +0400, Marc Weber [EMAIL PROTECTED]
 wrote:
 
 Would it make sense to specify partial type declarations ?
 I don't need an answer right now.
 
 no, it wouldn't. 

I think it would, and it seems there are others. See e.g.
http://www.mail-archive.com/haskell%40haskell.org/msg10677.html

There is even a hack that allows you to do it in Haskell98, see
http://okmij.org/ftp/Haskell/partial-signatures.lhs

(hey, google rulez!)

Cheers
Ben

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread P. R. Stanley

Brandon, Chris, Don,
gentlemen,
Thank you all for your swift and well-written answers.
I should point out that I'm coming to functional programming with a 
strong background in programming in C and C-type languages. I am also 
very new to the whole philosophy of functional programming. Hence my 
bafflement at some of the very elementary attributes of Haskell. I 
thought that would give you chaps a better idea of where I'm coming 
from with my queries.

Back to mylen. Here is the definition once more:
mylen [] = 0
mylen (x:y) = 1 + mylen y
The base case, if that is the right terminology, stipulates that the 
recursion ends with an empty list and returns 0. Simple though one 
question - why does mylen require the parentheses even when it is 
evaluating the length of [...]? I can understand the need for them 
when dealing with x:... because of the list construction function 
precedence but not with [2,3,etc]. I thought a [e] was treated as a 
distinct token.


I'm assuming that the interpreter/compiler is equipped to determine 
the type and value of xs subsequent to which it calls itself and 
passes the object minus the first element as argument unless the 
object is an empty list.


going back to Don's formal definition of the list data structure:
data [a] = [] | a : [a]
A list is either empty or contains an element of type a? Correct, 
wrong or very wrong?


By the way, what branch of discrete math - other than the obvious 
ones such as logic and set theory - does functional programming fall under?


Many thanks in advance for your help
Paul

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Brandon S. Allbery KF8NH


On Feb 18, 2007, at 21:26 , P. R. Stanley wrote:


mylen (x:y) = 1 + mylen y
The base case, if that is the right terminology, stipulates that  
the recursion ends with an empty list and returns 0. Simple though  
one question - why does mylen require the parentheses even when it  
is evaluating the length of [...]? I can understand the need for  
them when dealing with x:... because of the list construction


Because it would expect three parameters without the parentheses.   
: is a perfectly valid variable name; the convention in Haskell is  
that such names represent infix functions, but this is only a  
convention.  The ability to use such names is convenient when passing  
operators or functions as parameters (this is, after all, functional  
programming!).


BTW, it might also help to understand how mylen is rewritten by the  
compiler:


mylen xx = case xx of
[] - 0
(x:xs) - 1 + mylen xs

(xx being actually an internal identifier which will never conflict  
with any name you use)



going back to Don's formal definition of the list data structure:
data [a] = [] | a : [a]
A list is either empty or contains an element of type a? Correct,  
wrong or very wrong?


Either empty, or an a consed with (the : is pronounced cons) a  
list of a.  This is a recursive definition.  a is an unspecified  
type; the formal definition allows any number (including zero, via  
[]) of values of the same unspecified type to be combined into a list  
recursively as a : a : a : ... : [].


The [a,a,a...] syntax is a convenient alternative syntax for  
a:a:a:...:[]; the two forms are completely equivalent, but the cons  
syntax is more convenient for pattern matching a list as (head:tail).


--
brandon s. allbery[linux,solaris,freebsd,perl] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier



P. R. Stanley wrote:

Brandon, Chris, Don,
gentlemen,
Thank you all for your swift and well-written answers.
I should point out that I'm coming to functional programming with a 
strong background in programming in C and C-type languages. I am also 
very new to the whole philosophy of functional programming. Hence my 
bafflement at some of the very elementary attributes of Haskell. I 
thought that would give you chaps a better idea of where I'm coming from 
with my queries.

Back to mylen. Here is the definition once more:
mylen [] = 0
mylen (x:y) = 1 + mylen y
The base case, if that is the right terminology, stipulates that the 
recursion ends with an empty list and returns 0. Simple though one 
question - why does mylen require the parentheses even when it is 
evaluating the length of [...]? I can understand the need for them when 
dealing with x:... because of the list construction function precedence 
but not with [2,3,etc]. I thought a [e] was treated as a distinct token.


I'm assuming that the interpreter/compiler is equipped to determine the 
type and value of xs subsequent to which it calls itself and passes the 
object minus the first element as argument unless the object is an empty 
list.


I think what you're asking here is why you need the parens around (x:y) in the 
second case.  Function application doesn't use parentheses, but it has a very 
high precedence, so mylen x:y would be parsed as (mylen x) : y, since the 
: constructor has a lower precedence.




going back to Don's formal definition of the list data structure:
data [a] = [] | a : [a]
A list is either empty or contains an element of type a? Correct, wrong 
or very wrong?


A list is either empty, or consists of the first object, which is of type a 
(just called a here) and the rest of the list, which is also a list of type a 
(called [a] here).  The syntax is an impediment to understanding here; a 
clearer version of the list type would be


data List a = Empty | Cons a (List a)

The left-hand case says that a list can be just Empty.  The right-hand case says 
that a list can also be a Cons of a value of type a (the first element) and a 
List of type a (the rest of the list).


So, for instance, in my definition these are all lists:

Empty
Cons 10 Empty  -- list of Int
Cons 10 (Cons 20 Empty)
Cons foo (Cons bar (Cons baz Empty))  -- list of String

Using normal Haskell lists these are:

[]
10 : Empty  -- also written as [10]
10 : 20 : Empty -- also written as [10, 20]
foo : bar : baz : Empty -- also written as [foo, bar, baz]

The list syntax e.g. [1, 2, 3] is just syntactic sugar; the real syntax would 
be with the : operator e.g. 1 : 2 : 3 : [].  We use the sugar because it's 
easier to read and write.




By the way, what branch of discrete math - other than the obvious ones 
such as logic and set theory - does functional programming fall under?




The usual answer to this is category theory which is an extremely abstract 
branch of mathematics.  But you don't really need to know category theory to 
program in Haskell (though it helps for reading Haskell papers).  Also, lambda 
calculus is useful, and there is a field called type theory which is also 
useful.  Pierce's book _Types and Programming Languages_ will get you up to 
speed on lambda calculus and type theory, though it doesn't use Haskell.


Mike

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Brandon S. Allbery KF8NH


On Feb 18, 2007, at 21:44 , Michael Vanier wrote:

I think what you're asking here is why you need the parens around  
(x:y) in the second case.  Function application doesn't use  
parentheses


Function application never applies to pattern matching.

The usual answer to this is category theory which is an extremely  
abstract branch of mathematics.  But you


Actually, no; my understanding is that category theory as applied to  
Haskell is a retcon introduced when the notion of monads was imported  
from category theory, and the original theoretical foundation of  
Haskell came from a different branch of mathematics.


Lambda calculus is pretty fundamental to Haskell or any functional  
programming language, as is type theory (although that you really  
don't have to understand in detail unless you're hacking the type  
system; most of us leave that to Oleg :) and the Curry-Howard  
isomorphism (simply stated:  computer programs can be converted into  
mathematical proofs, and vice versa; this is most clearly  
demonstrated when the programs are described in terms of the lambda  
calculus, which is where the original formulation of Curry-Howard  
came from).


--
brandon s. allbery[linux,solaris,freebsd,perl] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier



Brandon S. Allbery KF8NH wrote:


On Feb 18, 2007, at 21:44 , Michael Vanier wrote:

I think what you're asking here is why you need the parens around 
(x:y) in the second case.  Function application doesn't use parentheses


Function application never applies to pattern matching.


You're right; I take it back.  However, : is not an acceptable variable name 
as such either:


ghci let foo x : y = x
interactive:1:4: Parse error in pattern

: needs to be surrounded by parens to be treated as a function; otherwise it's 
an operator.  OK, we can try:


ghci let foo x (:) y = x

interactive:1:10:
Constructor `:' should have 2 arguments, but has been given 0
In the pattern: :
In the definition of `foo': foo x : y = x

Bottom line: foo x:y is not a valid pattern.

The usual answer to this is category theory which is an extremely 
abstract branch of mathematics.  But you


Actually, no; my understanding is that category theory as applied to 
Haskell is a retcon introduced when the notion of monads was imported 
from category theory, and the original theoretical foundation of Haskell 
came from a different branch of mathematics.




Nevertheless, a lot of Haskell papers do refer to category theory, and lambda 
calculus can be put into that framework as well, so I don't think my statement 
is invalid.  But as you say, it's a bit of an after-the-fact realization.


Mike


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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread P. R. Stanley

Chaps,
is there another general pattern for mylen, head or tail?
mylen [] = 0
mylen (x:xs) = 1 + mylen (xs)

head [] = error what head?
head (x:xs) = x

tail [] = error no tail
tail (x:xs)= xs

This pattern matching reminds me of a module on formal spec I studied 
at college.

What are the pre-requisites for Lambda calculus?
Thanks
Paul

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Michael Vanier

P. R. Stanley wrote:


What are the pre-requisites for Lambda calculus?
Thanks
Paul



Learning lambda calculus requires no prerequisites other than the ability to 
think clearly.  However, don't think that you need to understand all about 
lambda calculus in order to learn Haskell.  It's more like the other way around: 
by the time you've learned Haskell, you've already unwittingly absorbed a good 
deal of lambda calculus.  Once again, I recommend Pierces _Types and Programming 
Languages_ as a reference if you really feel you need to learn this now.


For absorbing the functional style of programming (which is what you really 
should be working on at this point), the book _Structure and Interpretation of 
Computer Programs_ by Abelson and Sussman (which uses Scheme, not Haskell) is 
very valuable.  For learning about recursion, the book _The Little Schemer_ by 
Friedman and Felleisen is also very good (and quite short); it also uses Scheme. 
 However, most of the insights of both books carry over into Haskell (with a 
change of syntax, of course).


Mike

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


Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Brandon S. Allbery KF8NH


On Feb 18, 2007, at 22:22 , P. R. Stanley wrote:


is there another general pattern for mylen, head or tail?


Those are basically it, aside from optionally replacing the unused  
variables with _.



What are the pre-requisites for Lambda calculus?


Lambda calculus isn't related to what's normally called calculus;  
while some basic math and logic are useful, you don't really need  
much of a formal or complex math background to unravel it.  See for  
example the early parts of http://en.wikipedia.org/wiki/ 
Lambda_calculus for an introduction.  (The later parts quickly become  
hard to digest until you've understood the earlier ones; the  
Wikipedia article is more a reference than an introduction.)


--
brandon s. allbery[linux,solaris,freebsd,perl] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Stefan O'Rear
Prior art trumps all.  (by a few %)  granted it doesn't do much memoizing 
anymore :)

gs  ajb  f  d  u, it, z  s  n

[EMAIL PROTECTED]:/tmp$ ./h n 42
28.92user 0.14system 0:29.85elapsed 97%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+494minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h d 42
0.00user 0.00system 0:00.00elapsed 0%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+254minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h z 100
0.00user 0.00system 0:00.00elapsed 200%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+259minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h z 1
0.03user 0.00system 0:00.03elapsed 105%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+746minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h z 10
3.46user 0.02system 0:03.48elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+1981minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h d 10
1.00user 0.00system 0:01.01elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+759minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h s 10
3.70user 0.03system 0:03.73elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+2175minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h it 10
3.43user 0.02system 0:03.46elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+1981minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h u 10
3.41user 0.03system 0:03.45elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+1981minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h u 20
17.34user 0.05system 0:17.44elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3200minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h it 20
17.38user 0.06system 0:18.99elapsed 91%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3199minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h it 20
17.31user 0.06system 0:17.70elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3200minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h z 20
17.34user 0.07system 0:17.42elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3199minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h s 20
20.15user 0.09system 0:20.25elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3591minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h d 20
4.20user 0.02system 0:04.24elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+758minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h d 10
1.02user 0.01system 0:01.03elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+758minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h f 20
0.12user 0.02system 0:00.14elapsed 102%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+2301minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h f 100
0.64user 0.08system 0:00.72elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+8456minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h f 300
2.58user 0.38system 0:02.96elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+33037minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h f 500
3.46user 0.40system 0:03.87elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+33036minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h ajb 500
0.52user 0.02system 0:00.54elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+2181minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h gs 500
0.39user 0.01system 0:00.41elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+1747minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h gs 5000
5.85user 0.11system 0:05.96elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+11183minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h f 1000
6.93user 0.91system 0:07.95elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+66059minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h gs 1000
0.90user 0.04system 0:00.97elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3379minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h ajb 1000
1.08user 0.04system 0:01.12elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+3584minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h ajb 1
14.09user 0.25system 0:14.42elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+23586minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h gs 1
13.17user 0.20system 0:13.48elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+19588minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ ./h ajb 3
49.05user 0.80system 0:50.71elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
0inputs+0outputs (0major+64948minor)pagefaults 0swaps
[EMAIL PROTECTED]:/tmp$ 

Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Donald Bruce Stewart
Would someone please update the entries on our 'archive of fibs' page?

http://www.haskell.org/haskellwiki/The_Fibonacci_sequence

Cheers.


stefanor:
 Prior art trumps all.  (by a few %)  granted it doesn't do much memoizing 
 anymore :)
 
 gs  ajb  f  d  u, it, z  s  n
 
 [EMAIL PROTECTED]:/tmp$ ./h n 42
 28.92user 0.14system 0:29.85elapsed 97%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+494minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h d 42
 0.00user 0.00system 0:00.00elapsed 0%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+254minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h z 100
 0.00user 0.00system 0:00.00elapsed 200%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+259minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h z 1
 0.03user 0.00system 0:00.03elapsed 105%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+746minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h z 10
 3.46user 0.02system 0:03.48elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+1981minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h d 10
 1.00user 0.00system 0:01.01elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+759minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h s 10
 3.70user 0.03system 0:03.73elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+2175minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h it 10
 3.43user 0.02system 0:03.46elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+1981minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h u 10
 3.41user 0.03system 0:03.45elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+1981minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h u 20
 17.34user 0.05system 0:17.44elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3200minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h it 20
 17.38user 0.06system 0:18.99elapsed 91%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3199minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h it 20
 17.31user 0.06system 0:17.70elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3200minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h z 20
 17.34user 0.07system 0:17.42elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3199minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h s 20
 20.15user 0.09system 0:20.25elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3591minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h d 20
 4.20user 0.02system 0:04.24elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+758minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h d 10
 1.02user 0.01system 0:01.03elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+758minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h f 20
 0.12user 0.02system 0:00.14elapsed 102%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+2301minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h f 100
 0.64user 0.08system 0:00.72elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+8456minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h f 300
 2.58user 0.38system 0:02.96elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+33037minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h f 500
 3.46user 0.40system 0:03.87elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+33036minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h ajb 500
 0.52user 0.02system 0:00.54elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+2181minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h gs 500
 0.39user 0.01system 0:00.41elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+1747minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h gs 5000
 5.85user 0.11system 0:05.96elapsed 100%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+11183minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h f 1000
 6.93user 0.91system 0:07.95elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+66059minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h gs 1000
 0.90user 0.04system 0:00.97elapsed 98%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3379minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h ajb 1000
 1.08user 0.04system 0:01.12elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+3584minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h ajb 1
 14.09user 0.25system 0:14.42elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 0inputs+0outputs (0major+23586minor)pagefaults 0swaps
 [EMAIL PROTECTED]:/tmp$ ./h gs 1
 13.17user 0.20system 0:13.48elapsed 99%CPU (0avgtext+0avgdata 0maxresident)k
 

Re: [Haskell-cafe] Recursion in Haskell

2007-02-18 Thread Derek Elkins

Michael Vanier wrote:

P. R. Stanley wrote:


What are the pre-requisites for Lambda calculus?
Thanks
Paul



Learning lambda calculus requires no prerequisites other than the 
ability to think clearly.  However, don't think that you need to 
understand all about lambda calculus in order to learn Haskell.  It's 
more like the other way around: by the time you've learned Haskell, 
you've already unwittingly absorbed a good deal of lambda calculus.  
Once again, I recommend Pierces _Types and Programming Languages_ as a 
reference if you really feel you need to learn this now.


For absorbing the functional style of programming (which is what you 
really should be working on at this point), the book _Structure and 
Interpretation of Computer Programs_ by Abelson and Sussman (which uses 
Scheme, not Haskell) is very valuable.  For learning about recursion, 
the book _The Little Schemer_ by Friedman and Felleisen is also very 
good (and quite short); it also uses Scheme.  However, most of the 
insights of both books carry over into Haskell (with a change of syntax, 
of course


How to Design Programs (HtDP) www.htdp.org is another Scheme teaching 
text that is lower level, slower paced.  It may be too low level for 
you, i.e. rather boring, or it may be helpful.  I'd definitely recommend 
reading SICP after it. Programming Languages: Application and 
Interpretation (PLAI) 
http://www.cs.brown.edu/~sk/Publications/Books/ProgLangs/ is a good book 
for either before or after SICP (which is also available online at 
http://mitpress.mit.edu/sicp/).  All of these use Scheme, but most of it 
uses a very functional style and it should transfer to Haskell very 
easily, especially the PLAI one.  It would be very nice to see a 
HtDP-style online book for Haskell; none of the currently available 
introductions really fit this role in my opinion.

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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread William Lee Irwin III
On Sun, Feb 18, 2007 at 06:15:25PM -0500, [EMAIL PROTECTED] wrote:
 Now that's an industrial-strength Fibonacci.  It's O(log n) not
 including the cost of adding and multiplying large Integers, and
 uses a bounded amount of memory between calls, making it suitable
 for a library.
 The slowest part of the test program is actually the bit that prints
 the number.  So I used this driver program:

I've been here before.

http://www.haskell.org/pipermail/haskell-cafe/2005-January/008839.html


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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread ajb
G'day all.

Quoting Stefan O'Rear [EMAIL PROTECTED]:

 Prior art trumps all.  (by a few %)  granted it doesn't do much memoizing
 anymore :)

Ah, butbutbut... of course the Gosper/Salamin one is going to be
faster if you only compute one Fibonacci number per instance.  The
memoed version is optimised for programs that want more than one.

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


Re: [Haskell-cafe] Re: Does laziness make big difference?

2007-02-18 Thread Nick




Peter,
Roughly, I'd say you can fudge laziness in data structures
in a strict language without too much bother. (I don't have much
experience with this, but the existence of a streams library for OCaml
is the sort of thing I mean. There are plenty of papers on co-iterative
streams and suchlike that show the general pattern.)

Yes, agree. And this was my initial point.

If you wish to add control structures you would need to use the lazy
keyword a lot, e.g.:
  
  
if cond then *lazy* S1 else *lazy* S2
  
  
and for more complicated structures it's not going to be always clear
what needs to be suspended. Laziness is a conservative default here.
(If you want to write an EDSL in a non-lazy language, you'll need to
use some kind of preprocessor / macros / ... - in other words, a
two-level language - or do thunking by hand, as above, or live with
doing too much evaluation.)
One way to gauge how useful laziness really is might be to look through
big ML projects and see how often they introduce thunks manually. A
thunk there is usually something like "fn () = ..." IIRC. Also
IIRC, Concurrent ML is full of them.
Probably, dealing with macros is not so scary and Paul Graham and Piter
Siebel show that it is quite easy. :-)

Ok, let's go from the another side:
I have searched through Darcs source and found 17 datastructures with
strict members (for example data Patch = NamedP !PatchInfo ![PatchInfo]
!Patch) and 36 occurrence of this dreaded seq. And Darcs is an
application being not speed critical.

And if one try to write cipher decoder on Haskell, I guess he has to
make his program full of '!' and 'seq' (or FFI).

Dare I say the tradeoff is between a relatively simple
operational model (so you can judge space and time usage easily) and
semantic simplicity (e.g. the beta rule is unrestricted, easing program
transformation).

Cool! Thank you.

Best regards,
Nick.


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


Re: [Haskell-cafe] Does laziness make big difference?

2007-02-18 Thread Nick

Jerzy Karczmarczuk,


You have strict languages as Scheme or ML, with some possibilities to do
lazy programming. Go ahead! (But you will pay a price. The laziness in
Scheme introduced by the delay macro can produce a lot of inefficient
code, much worse than coded at the base level).

Maybe I am not clear enough, but this is the price I try to measure. :-)

The question is NOT open. The question has been answered a long time ago
in a liberal manner. You have both. You *choose* your programming 
approach.

You choose your language, if you don't like it, you go elsewhere, or you
produce another one, of your own.
Yes, I agree, the world of programming is very rich. But you probably 
know, there are quite a few of curious people (at least in the Russian 
community) that begin to be interested in other (than mainstream) 
languages. Of course, one moment they meet Haskell, and get exited of 
its excellent expressive capabilities, but finally ask the same question:


   What advantages does lazy language have?

And you see, it is incorrect to answer: Relax, no advantages at all, 
take a look at ML or Scheme, because it is just not true. But in order 
to invite new members to the community, we have to answer this question 
(and plus 100 other boring questions) over and over again. Especially it 
is even harder to avoid another holy war, because on the other side 
there are languages with advanced expressiveness features and macrosystem.
Haskell chose a particular schema, that implied a *very concrete* 
decision

concerning the underlying abstract machine model, and the implementation.
It is a bit frustrating reading over and over the complaints of people 
who
never needed, so they dont appreciate laziness, who want to revert 
Haskell

to strict. As if we were really obliged to live inside of a specific Iron
Curtain, where only one paradigm is legal.
You misunderstood me, I don't try to revert Haskell to strict. I like 
Haskell as is. My motivation is different.


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


Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread Mikael Johansson

On Sun, 18 Feb 2007, Yitzchak Gale wrote:

Besides memoizing, you might want to use the fact
that:

fib (2*k) == (fib (k+1))^2 - (fib (k-1))^2
fib (2*k-1) == (fib k)^2 + (fib (k-1))^2



Or, you know, go straight to the closed form for the fibonacci numbers! :)

--
Mikael Johansson | To see the world in a grain of sand
[EMAIL PROTECTED]|  And heaven in a wild flower
http://www.mikael.johanssons.org | To hold infinity in the palm of your hand
 |  And eternity for an hour
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe